An Outline Code Editor First Steps

Laurence Rozier lrozier at thepattern.com
Thu Aug 19 17:19:57 UTC 1999


Hi All,

Being a big proponent of outliners, excited by the idea of a Frontier like editor
for Squeak and inspired by SyntaxMorph(thanks Bob!), I put together the
beginnings of an outline-based code editor. I've been working with extending
ObjectExplorer(thanks again Bob!). My first, quick and dirty approach was to
subclass ListItemWrapper, overriding the contents method in the same way
ObjectExplorerWrapper does. Not surprisingly that's not a very flexible approach.
It expects that all nodes displayed will be homogeneous. So I changed
ObjectExplorerWrapper contents to:

^ item getChildNodes

Then I implemented the behavior of the original ObjectExplorerWrapper>>contents
as a method of Object named getChildNodes. ObjectExplorer works as it did before
except that now any class can determine its appearance in an Explorer by
overriding getChildNodes. I've never spent much time in the Compiler related
classes, but looking at SyntaxMorph their behavior, relationship and structure
came into focus so I started implementing getChildNodes for some of the ParseNode
subclasses. If you evaluate the following:

 | tree source |
 source _ (MessageNode compiledMethodAt: #asMorphicSyntax:) getSourceFromFile.
 tree _ Compiler new
    parse: source
    in: SyntaxMorph
    notifying: nil.
 tree explore.

you'll get an Explorer that *shows* a method as an outline the way Frontier
works. Aside from making the nodes editable, there are many things that
should/could be done from here. For starters:

1. Get rid of the curly braces!
2. Have AssignmentNodes display the reciever with the statement as a child
3. Implement SytaxMorph like popups
4. Add comments to ballon help

Comments, suggestions? Any Compiler savvy folks want to pitch in here?

Regards,
-Laurence
Bijan Parsia wrote:

> At 12:55 PM -0400 8/14/99, Toby Watson wrote:
>
> >Alan Kay said:
> >
> >>      Suggestion: turn all the energy worrying about formatting
> >Smalltalk-80
> >> conventions into good ideas for making real OOP inviting to look at and we
> >> can make these happen right from the parse tree ....
> >
> >OK, let me throw in a couple of artifacts that I come across everyday for
> >perusal.
> >
> >1. Dave Winer's Frontier, which uses an outliner for scripting in UserTalk,
> >and has a certain 'look'.
> >
> >http://www.scripting.com/frontier/snippets/nerdsguide.html (scroll down to
> >see editor)
> >
> >http://frontier.userland.com/ (general)
> >
> >(actually Frontier may be of interest to the Squeak community wrt. the way
> >it deals with being a hot system. Guest Databases, Suites, etc. )
>
> Michael Starke's Golgi in fact was inspired by Frontier and implements (in
> an alpha way) outlining code panes in Squeak, with the added advantage that
> the outline widgets are semantically significant.
>
> Cheers,
> Bijan Parsia.

'From Squeak 2.5 of August 6, 1999 on 19 August 1999 at 9:43:08 am'!

!Object methodsFor: 'Outlining' stamp: 'LPR 8/19/1999 00:50'!
canBeDragged
	^ false! !

!Object methodsFor: 'Outlining' stamp: 'LPR 8/19/1999 00:53'!
contents
	^ self getChildNodes! !

!Object methodsFor: 'Outlining' stamp: 'LPR 8/18/1999 04:37'!
getChildNodes
	| answer |
	answer _ OrderedCollection new.
	self class allInstVarNames asArray doWithIndex: [:each :index | answer add: (ObjectExplorerWrapper
				with: (self instVarAt: index)
				name: each
				model: self)].
	1 to: self basicSize do: [:index | answer add: (ObjectExplorerWrapper
				with: (self basicAt: index)
				name: index printString
				model: self)].
	^ answer! !

!Object methodsFor: 'Outlining' stamp: 'LPR 8/19/1999 00:55'!
handlesMouseOver: evt 
	^ false! !

!Object methodsFor: 'Outlining' stamp: 'LPR 8/18/1999 18:06'!
hasContents
	^ self hasContentsInExplorer! !

!Object methodsFor: 'Outlining' stamp: 'LPR 8/18/1999 18:09'!
preferredColor
	^ nil! !


!BlockNode methodsFor: 'Outlining' stamp: 'LPR 8/19/1999 09:42'!
getChildNodes
^statements! !


!MessageNode methodsFor: 'Outlining' stamp: 'LPR 8/19/1999 08:48'!
getChildNodes
	"was taken from asMorphicSyntax: originally"
	| theChildNodes keywords prev arg thisKey |
	theChildNodes _ OrderedCollection new.
	special > 0
		ifTrue: 
			[arguments size = 0 ifTrue: [^ theChildNodes].
			keywords _ selector key keywords.
			prev _ receiver.
			1 to: keywords size do: 
				[:part | 
				arg _ arguments at: part.
				thisKey _ keywords at: part.
				(prev isMemberOf: BlockNode)
					| ((prev isMemberOf: MessageNode)
							and: [prev precedence >= 3]) | ((arg isMemberOf: BlockNode)
						and: [arg isComplex and: [thisKey ~= #do:]]) | (arguments size > 2) | (selector key = #ifTrue:ifFalse:) ifTrue: [theChildNodes add: arg]]].
^theChildNodes! !


!MethodNode methodsFor: 'outlining' stamp: 'LPR 8/18/1999 18:02'!
getChildNodes

^block statements! !


!ObjectExplorerWrapper methodsFor: 'as yet unclassified' stamp: 'LPR 8/18/1999 04:39'!
contents
"	| answer |
	answer _ OrderedCollection new.
	item class allInstVarNames asArray doWithIndex: [:each :index | answer add: (ObjectExplorerWrapper
				with: (item instVarAt: index)
				name: each
				model: item)].
	1 to: item basicSize do: [:index | answer add: (ObjectExplorerWrapper
				with: (item basicAt: index)
				name: index printString
				model: item)].
	^ answer"
^ item getChildNodes! !





More information about the Squeak-dev mailing list