[squeak-dev] Tree graph/diagram drawing

Stéphane Rollandin lecteur at zogotounga.net
Tue Sep 14 14:46:43 UTC 2021


> Does anybody know an algorithm for drawing tree graph nodes so they
> don't clump in one place but rather form a (vertical) tree? I plan on
> visualizing a few ASTs. Example included in attachment.
> 
> It's not related to Squeak per se, but I have no idea where to begin;
> what to type into Google.
> 


See the attached file. It defines TreeMorph, illustrating a simple 
recursive algorithm that I just made up for you - it seems to work fine.

Try it with:

	TreeMorph example openInWorld

You can use it to display any tree-like object. Just define visiting 
blocks #morphicGetter and #nodesGetter accordingly.

Stef
-------------- next part --------------
'From Squeak5.3 of 3 March 2020 [latest update: #19431] on 14 September 2021 at 4:40 pm'!
Morph subclass: #TreeMorph
	instanceVariableNames: 'tree nodesGetter morphicGetter'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TreeMorph'!
!TreeMorph commentStamp: 'spfa 9/14/2021 16:34' prior: 0!
TreeMorph example openInWorld!
]style[(29)!


!TreeMorph methodsFor: 'accessing' stamp: 'spfa 9/14/2021 13:13'!
morphicGetter

	^ morphicGetter ifNil: [[:t | t printString asMorph]]! !

!TreeMorph methodsFor: 'accessing' stamp: 'spfa 9/14/2021 13:20'!
morphicGetter: aBlock

	morphicGetter := aBlock! !

!TreeMorph methodsFor: 'accessing' stamp: 'spfa 9/14/2021 13:12'!
nodesGetter

	^ nodesGetter ifNil: [#nodes]! !

!TreeMorph methodsFor: 'accessing' stamp: 'spfa 9/14/2021 13:26'!
nodesGetter: aBlock

	nodesGetter := aBlock! !


!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 16:29'!
depthOfTree: aTree

	| nodes |

	nodes := self nodesForTree: aTree.

	nodes ifEmpty: [^ 1].

	^ 1 + (nodes collect: [:ea | self depthOfTree: ea]) max! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 16:33'!
displayTree: aTree depth: anInteger from: x

	| m dx mx |

	m := self morphForTree: aTree.
	
	m center: (((self nodesWidthForTree: aTree) * 0.5) + x) @ (anInteger * self rowHeight).

	self addMorph: m.
	dx := 0.
	mx := x.
	(self nodesForTree: aTree) do: [:ea | 
		| spec |
		spec :=  self displayTree: ea depth: anInteger + 1 from: mx.
		self addMorph: (LineMorph from: m bottomCenter + (0@ self linkMargin) 
							to: spec first topCenter - (0@ self linkMargin) 
							color: Color black width: 1).
		mx := mx + spec second].

	^ {m . self nodesWidthForTree: aTree}! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 16:39'!
displayWidthForTree: aTree

	"ugly, as the morph is rebuilt every time"

	^ (self morphForTree: aTree) width + self spacing! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 13:16'!
morphForTree: aTree

	^ self morphicGetter value: aTree! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 13:15'!
nodesForTree: aTree

	^ self nodesGetter value: aTree! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 13:14'!
nodesWidthForTree: aTree

	| nodes |

	nodes := self nodesForTree: aTree.

	nodes ifEmpty: [^ self displayWidthForTree: aTree].

	^ nodes inject: 0 into: [:sum :ea | sum + (self nodesWidthForTree: ea)]! !

!TreeMorph methodsFor: 'algorithm' stamp: 'spfa 9/14/2021 16:29'!
tree: aTree

	self extent: (self nodesWidthForTree: aTree) 
					@ ((self depthOfTree: aTree) + 1 * self rowHeight).

	self displayTree: aTree depth: 1 from: self left! !


!TreeMorph methodsFor: 'parameters' stamp: 'spfa 9/14/2021 16:37'!
initialize

	super initialize.

	self color: Color blue muchLighter! !

!TreeMorph methodsFor: 'parameters' stamp: 'spfa 9/14/2021 13:11'!
linkMargin

	^ 5! !

!TreeMorph methodsFor: 'parameters' stamp: 'spfa 9/14/2021 12:54'!
rowHeight

	^ 60! !

!TreeMorph methodsFor: 'parameters' stamp: 'spfa 9/14/2021 12:26'!
spacing

	^ 60! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TreeMorph class
	instanceVariableNames: ''!

!TreeMorph class methodsFor: 'as yet unclassified' stamp: 'spfa 9/14/2021 16:34'!
example

	^ TreeMorph new
		nodesGetter: [: t | t isArray ifTrue: [t] ifFalse: [#()] ];
		morphicGetter: [: t | (t isArray ifTrue: [t] ifFalse: [t]) asString asMorph];
		tree: #((4 8 4) (12 (2 (5 8 77 4)) 45) 5)
! !


More information about the Squeak-dev mailing list