Added PluggableHierarchicalList to define ad-hoc tree models. jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 21 May 2015 21:14:57 +0100
branchjv
changeset 4770 6634b540fea2
parent 4769 17172bc64232
child 4774 2d80e1e7b714
Added PluggableHierarchicalList to define ad-hoc tree models. This is especially handy for creating tree-like representations for inspector
AssistantApplication.st
ColoredListEntry.st
ComboBrowseView.st
ComboUpDownView.st
GraphColumn.st
GraphColumnView.st
GraphColumnView2D.st
GraphColumnView2DSpec.st
GraphColumnView3D.st
GraphColumnView3DSpec.st
GraphColumnViewSpec.st
HorizontalScale.st
ImageSelectionBox.st
KeyboardView.st
LinkButton.st
ListEditor.st
Make.proto
Make.spec
MenuButton.st
MotionButton.st
NoteBookFrameView.st
ParagraphSpecification.st
PluggableHierarchicalList.st
RoundButton.st
Ruler.st
Scale.st
SelectionInHierarchyView.st
StrokeView.st
TabControl.st
TabView.st
TextRuler.st
VT52TerminalView.st
VerticalRuler.st
abbrev.stc
bc.mak
libInit.cc
stx_libwidg2.st
--- a/AssistantApplication.st	Thu May 21 21:00:16 2015 +0100
+++ b/AssistantApplication.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 ToolApplicationModel subclass:#AssistantApplication
 	instanceVariableNames:'currentPageSpecHolder backButtonEnabled forwardButtonEnabled
 		backButtonVisible forwardButtonVisible finishButtonVisible
@@ -14,6 +27,20 @@
 
 !AssistantApplication class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     an easy to use framework for assistant-dialog applications.
--- a/ColoredListEntry.st	Thu May 21 21:00:16 2015 +0100
+++ b/ColoredListEntry.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 ListEntry subclass:#ColoredListEntry
 	instanceVariableNames:'color string bgColor'
@@ -179,3 +180,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ColoredListEntry.st,v 1.14 2006-11-13 16:11:29 cg Exp $'
 ! !
+
--- a/ComboBrowseView.st	Thu May 21 21:00:16 2015 +0100
+++ b/ComboBrowseView.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 ComboBoxView subclass:#ComboBrowseView
 	instanceVariableNames:'browseAction'
@@ -154,3 +155,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ComboBrowseView.st,v 1.4 2006-11-13 16:11:29 cg Exp $'
 ! !
+
--- a/ComboUpDownView.st	Thu May 21 21:00:16 2015 +0100
+++ b/ComboUpDownView.st	Thu May 21 21:14:57 2015 +0100
@@ -9,10 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libwidg2' }"
 
-'From Smalltalk/X, Version:3.2.1 on 25-oct-1997 at 9:33:18 pm'                  !
+"{ NameSpace: Smalltalk }"
 
 ComboBoxView subclass:#ComboUpDownView
 	instanceVariableNames:'minValue maxValue step currentValue values valueIndex'
@@ -287,3 +286,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ComboUpDownView.st,v 1.5 2006-11-13 16:11:29 cg Exp $'
 ! !
+
--- a/GraphColumn.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumn.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 Model subclass:#GraphColumn
 	instanceVariableNames:'aspects functionYblock'
 	classVariableNames:''
@@ -733,3 +735,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumn.st,v 1.4 2006-11-13 16:11:29 cg Exp $'
 ! !
+
--- a/GraphColumnView.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnView.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 View subclass:#GraphColumnView
 	instanceVariableNames:'columns listHolder references referenceHolder referenceSelector
 		referenceColor showReferences zoomY zoomYHolder oldMenuMessage
@@ -1054,3 +1056,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView.st,v 1.7 2003-09-04 18:39:10 stefan Exp $'
 ! !
+
--- a/GraphColumnView2D.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnView2D.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 GraphColumnView subclass:#GraphColumnView2D
 	instanceVariableNames:'colorMap gridXoffset gridX gridY actionBlock doubleClickBlock
 		buttonReleaseBlock menuAccessBlock'
@@ -1696,3 +1698,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView2D.st,v 1.7 2007-09-28 12:02:53 sr Exp $'
 ! !
+
--- a/GraphColumnView2DSpec.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnView2DSpec.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 GraphColumnViewSpec subclass:#GraphColumnView2DSpec
 	instanceVariableNames:'gridX gridY actionBlock doubleClickBlock buttonReleaseBlock
 		menuAccessBlock'
@@ -487,3 +489,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView2DSpec.st,v 1.11 2008-01-10 13:00:51 cg Exp $'
 ! !
+
--- a/GraphColumnView3D.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnView3D.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 GraphColumnView subclass:#GraphColumnView3D
 	instanceVariableNames:'glxView showGraph rotateX rotateY rotateZ rotateXHolder
 		rotateYHolder rotateZHolder zoomZ zoomZHolder showAxis'
@@ -8,958 +10,3 @@
 	category:'Views-Graphs'
 !
 
-GLXView subclass:#GLXGraph
-	instanceVariableNames:'graph colorMap maxY minY loVCols loVRefs yValues glxObjFunc
-		glxObjRefs glxObjGrid glxObjAxis removeFunc removeRefs removeGrid
-		removeAxis isInvalid lockCriticalTask criticalTask'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:GraphColumnView3D
-!
-
-!GraphColumnView3D class methodsFor:'documentation'!
-
-documentation
-"
-    The class provides all the functionality for showing, scrolling and manipulating graphs
-    described through to a GraphColumn description. Each change in a graph description
-    immediately take affect.
-
-
-    [See also:]
-	GraphColumn
-	GraphColumnView
-	GraphColumnView2D
-
-    [Author:]
-	Claus Atzkern
-"
-
-! !
-
-!GraphColumnView3D class methodsFor:'menu'!
-
-defaultMenu
-    "this window spec was automatically generated by the ST/X MenuEditor"
-
-    "do not manually edit this - the builder may not be able to
-     handle the specification if its corrupted."
-
-    "
-     MenuEditor new openOnClass:GraphColumnView3D andSelector:#defaultMenu
-     (Menu new fromLiteralArrayEncoding:(GraphColumnView3D defaultMenu)) startUp
-    "
-
-    <resource: #menu>
-
-    ^
-
-       #(#Menu
-
-	   #(
-	     #(#MenuItem
-		#'label:' 'Show Columns'
-		#'indication:' #'showGraph:'
-	    )
-	     #(#MenuItem
-		#'label:' 'Show Grid'
-		#'indication:' #'showGrid:'
-	    )
-	     #(#MenuItem
-		#'label:' 'Show Axis'
-		#'indication:' #'showAxis:'
-	    )
-	     #(#MenuItem
-		#'label:' 'Show References'
-		#'indication:' #'showReferences:'
-	    )
-	     #(#MenuItem
-		#'label:' '-'
-	    )
-	     #(#MenuItem
-		#'label:' 'Zoom Y'
-		#'submenuChannel:' #subMenuZoomY
-	    )
-	  ) nil
-	  nil
-      )
-! !
-
-!GraphColumnView3D class methodsFor:'test'!
-
-test
-"
-self test
-"
-    |top list view x|
-
-    top  := StandardSystemView extent:800 @ 400.
-    view := GraphColumnView3D origin:0@0 extent:1.0@1.0 in:top.
-    list := OrderedCollection new.
-
-    top label:'3D-View'.
-
-    #(  red green yellow blue
-     ) keysAndValuesDo:[:idx :aColor|
-	|col|
-
-	col := GraphColumn name:idx.
-	col foregroundColor:(Color perform:aColor).
-
-	col functionYblock:[:start :anArray|
-	    x := (start - 1) * 0.2.
-	    (idx == 1 or:[idx == 3]) ifTrue:[
-		1 to:(anArray size) do:[:i| anArray at:i put:20 * (x sin). x := x + 0.2 ].
-	    ] ifFalse:[
-		1 to:(anArray size) do:[:i| anArray at:i put:20 * (x cos). x := x + 0.2 ].
-	    ].
-	    anArray
-	].
-	list add:col
-    ].
-    view showGrid:true.
-    view columns:list.
-    view showDefaultMenu:true.
-    top openAndWait.
-
-    [   |o i t c|
-
-	i := 0.
-	t := 0.
-	c := 0.
-
-	[top realized] whileTrue:[
-	    t := t + (Time millisecondsToRun:[ view rotateY:i]).
-	    i := i + 1.
-	    c := c + 1.
-	    c == 90 ifTrue:[
-		Transcript showCR:'Time: ', t printString.
-		t := 0.
-		c := 0.
-	    ].
-	    Delay waitForSeconds:0.05.
-	]
-
-    ] forkAt:8.
-
-
-
-
-
-!
-
-testRun
-    "running view
-
-     start with:
-	 self testRunX
-    "
-    |top list view step x offs time cbox halt xOrigin|
-
-    halt := false.
-    top  := StandardSystemView extent:800 @ 400.
-    view := GraphColumnView3D origin:0@20 extent:1.0@1.0 in:top.
-    cbox := CheckBox origin:0@0.0 corner:50@20 in:top.
-    cbox label:'Stop'.
-    cbox action:[:v| halt := v].
-    xOrigin := 1 asValue.
-
-    offs := 0.
-    step := 2.
-    list := OrderedCollection new.
-
-    top label:'Testing 3D-View: Performance Test'.
-
-    #( 0.25 0.5 0.75 ) do:[:xAxis||aCol|
-	aCol := GraphColumn new.
-	aCol relativeXaxis:xAxis.
-	xAxis ~= 0.5 ifTrue:[
-	    xAxis < 0.5 ifTrue:[aCol foregroundColor:(Color red)]
-		       ifFalse:[aCol foregroundColor:(Color blue)]
-	].
-	aCol hLineStyle:#dashed.
-	aCol hLineList:#( 0 ).
-	aCol scaleY:40.
-
-	aCol functionYblock:[:start :array|
-	    x := start * 0.2.
-	    1 to:(array size) do:[:i| array at:i put:10 * (x sin). x := x + 0.2 ].
-	    array
-	].
-	list add:aCol.
-    ].
-    view windowSize:100.
-    view showGrid:true.
-    view columns:list.
-    view scrollUpdatesOriginX:true.
-    view graphOriginXHolder:xOrigin.
-
-    top openAndWait.
-
-    [   [top realized] whileTrue:[
-	    halt ifFalse:[
-		xOrigin value:(xOrigin value + step).
-	   ].
-	   Delay waitForSeconds:0.05.
-	]
-
-    ] forkAt:8.
-
-! !
-
-!GraphColumnView3D methodsFor:'accessing look'!
-
-showAxis
-    "show or hide the x/y/z axis
-    "
-    ^ showAxis
-!
-
-showAxis:aBool
-    "show or hide the x/y/z axis
-    "
-    showAxis ~~ aBool ifTrue:[
-	showAxis := aBool.
-	glxView invalidate.
-    ].
-!
-
-showGraph
-    "show or hide columns; if the grid is enabled, only the grid will be
-     shown
-    "
-    ^ showGraph
-!
-
-showGraph:aBool
-    "show or hide columns; if the grid is enabled, only the grid will be
-     shown
-    "
-    showGraph ~~ aBool ifTrue:[
-	showGraph := aBool.
-	glxView invalidate.
-    ].
-!
-
-zoomZ
-    "returns the current zoom Z factor
-    "
-    ^ zoomZ
-!
-
-zoomZ:aValue
-    "set the zoom Z factor; if the argument is nil or not valid, the
-     default zoom Z factor is set (1).
-    "
-    |zZ|
-
-    (zZ := self floatFrom:aValue onError:[1]) <= 0 ifTrue:[
-	zZ := 1
-    ].
-
-    zZ = zoomZ ifFalse:[
-	zoomZ := zZ.
-	glxView invalidate.
-    ]
-! !
-
-!GraphColumnView3D methodsFor:'accessing mvc'!
-
-rotateXHolder
-    "returns the valueHolder, which holds the rotation X value
-    "
-    ^ rotateXHolder
-
-!
-
-rotateXHolder:aHolder
-    "set the valueHolder, which holds the rotation X value
-    "
-    rotateXHolder == aHolder ifFalse:[
-	rotateXHolder notNil ifTrue:[
-	    rotateXHolder removeDependent:self
-	].
-	(rotateXHolder := aHolder) notNil ifTrue:[
-	    rotateXHolder addDependent:self
-	]
-    ].
-    self rotateX:(rotateXHolder value)
-!
-
-rotateYHolder
-    "returns the valueHolder, which holds the rotation Y value
-    "
-    ^ rotateYHolder
-
-!
-
-rotateYHolder:aHolder
-    "set the valueHolder, which holds the rotation Y value
-    "
-    rotateYHolder == aHolder ifFalse:[
-	rotateYHolder notNil ifTrue:[
-	    rotateYHolder removeDependent:self
-	].
-	(rotateYHolder := aHolder) notNil ifTrue:[
-	    rotateYHolder addDependent:self
-	]
-    ].
-    self rotateY:(rotateYHolder value)
-
-!
-
-rotateZHolder
-    "returns the valueHolder, which holds the rotation Z value
-    "
-    ^ rotateZHolder
-
-!
-
-rotateZHolder:aHolder
-    "set the valueHolder, which holds the rotation Z value
-    "
-    rotateZHolder == aHolder ifFalse:[
-	rotateZHolder notNil ifTrue:[
-	    rotateZHolder removeDependent:self
-	].
-	(rotateZHolder := aHolder) notNil ifTrue:[
-	    rotateZHolder addDependent:self
-	]
-    ].
-    self rotateZ:(rotateZHolder value)
-
-!
-
-zoomZHolder
-    "returns the valueHolder, which holds the zoom Z factor
-    "
-    ^ zoomZHolder
-
-!
-
-zoomZHolder:aHolder
-    "set the valueHolder, which holds the zoom Z factor
-    "
-    zoomZHolder == aHolder ifFalse:[
-	zoomZHolder notNil ifTrue:[
-	    zoomZHolder removeDependent:self
-	].
-	(zoomZHolder := aHolder) notNil ifTrue:[
-	    zoomZHolder addDependent:self
-	]
-    ].
-    self zoomZ:(zoomZHolder value)
-! !
-
-!GraphColumnView3D methodsFor:'change & update'!
-
-update:what with:aPara from:chgObj
-    "catch and handle a change notification of any object
-    "
-    chgObj == rotateXHolder ifTrue:[ ^ self rotateX:(rotateXHolder value) ].
-    chgObj == rotateYHolder ifTrue:[ ^ self rotateY:(rotateYHolder value) ].
-    chgObj == rotateZHolder ifTrue:[ ^ self rotateZ:(rotateZHolder value) ].
-    chgObj == zoomZHolder   ifTrue:[ ^ self   zoomZ:(zoomZHolder value)   ].
-
-    super update:what with:aPara from:chgObj
-! !
-
-!GraphColumnView3D methodsFor:'converting'!
-
-rotateValueFrom:aNumber
-    "converts a value to a valid rotation value
-    "
-    |r|
-
-    r := self unsignedIntegerFrom:aNumber onError:[0].
-  ^ r < 360 ifTrue:[r] ifFalse:[r \\ 360]
-! !
-
-!GraphColumnView3D methodsFor:'initialization'!
-
-destroy
-    "remove dependencies
-    "
-    super destroy.
-
-    rotateXHolder removeDependent:self.
-    rotateYHolder removeDependent:self.
-    rotateZHolder removeDependent:self.
-    zoomZHolder   removeDependent:self.
-
-!
-
-initialize
-    "setup default values
-    "
-    super initialize.
-
-    rotateX  := 45.
-    rotateY  := 45.
-    rotateZ  := 0.
-    zoomZ    := 1.
-
-    showGraph := true.
-    showAxis  := false.
-
-    glxView   := GLXGraph extent:(1.0 @ 1.0) in:self.
-    glxView for:self.
-
-! !
-
-!GraphColumnView3D methodsFor:'protocol'!
-
-doInvalidateGraph
-    "set graph to invalidate
-    "
-    glxView invalidate
-!
-
-doRecomputeGraph
-    "called to recompute drawable objects and to set the
-     graph to invalidate
-    "
-    glxView deleteAllObjects.
-!
-
-updateColumns:what with:oldValue from:aColumn
-    "called if the list of columns changed
-	 #size      the size of the columns
-	 #color:    color changed
-     or a specific column:( aColumn notNil )
-	 #insert:   insert a new column
-	 #remove:   remove a column
-
-	or a specific attribute derived from the
-	changed column.
-    "
-
-    (what == #color or:[what == #foregroundColor]) ifTrue:[
-	glxView deleteColumns.
-      ^ glxView invalidate.
-    ].
-
-    (   aColumn isNil
-      or:[what == #shown
-      or:[what == #insert:
-      or:[what == #remove:]]]
-    ) ifTrue:[
-	^ self doRecomputeGraph
-    ].
-!
-
-updateGrid:what
-    "called if the grid changed
-     #color     the color of the grid changed
-     #state     the visibility state of the grid changed
-    "
-    what == #color ifTrue:[
-	glxView deleteGrid
-    ].
-    glxView invalidate.
-!
-
-updateReferences:what atRelX:aPhysX
-    "called when the list of references changed.
-	#remove:        the reference at the relative X index is removed
-	#insert:        a reference is inserted at the relative X index
-	#size           the list of references changed
-	#state          visibility state changed
-	#color          the foreground color changed
-    "
-
-    what == #state ifFalse:[
-	glxView deleteReferences
-    ].
-    glxView invalidate.
-! !
-
-!GraphColumnView3D methodsFor:'rotation'!
-
-rotateX
-    "returns the rotation X value; range: 0 .. 360
-    "
-    ^ rotateX
-!
-
-rotateX:aValue
-    "set the rotation X value; range: 0 .. 360
-    "
-    |r|
-
-    (r := self rotateValueFrom:aValue) ~~ rotateX ifTrue:[
-	rotateX := r.
-	glxView invalidate.
-    ]
-!
-
-rotateY
-    "returns the rotation Y value; range: 0 .. 360
-    "
-    ^ rotateY
-
-!
-
-rotateY:aValue
-    "set the rotation Y value; range: 0 .. 360
-    "
-    |r|
-
-    (r := self rotateValueFrom:aValue) ~~ rotateY ifTrue:[
-	rotateY := r.
-	glxView invalidate.
-    ]
-
-!
-
-rotateZ
-    "returns the rotation Z value; range: 0 .. 360
-    "
-    ^ rotateZ
-
-!
-
-rotateZ:aValue
-    "set the rotation Z value; range: 0 .. 360
-    "
-    |r|
-
-    (r := self rotateValueFrom:aValue) ~~ rotateZ ifTrue:[
-	rotateZ := r.
-	glxView invalidate.
-    ]
-
-! !
-
-!GraphColumnView3D::GLXGraph class methodsFor:'constants'!
-
-maxColors
-    ^ 256
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'event handling'!
-
-buttonPress:button x:x y:y
-    "delegate button to graph
-    "
-    graph buttonPress:button x:x y:y
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'initialization'!
-
-destroy
-    "remove dependencies
-    "
-    super destroy.
-    self  deleteAllObjects.
-
-!
-
-for:aGraph
-    graph := aGraph
-!
-
-initialize
-    "setup default values
-    "
-    super initialize.
-
-    type := #colorIndexDoubleBuffer.            "/ works on any device
-    maxY :=  1.0.
-    minY := -1.0.
-
-    removeFunc := false.
-    removeRefs := false.
-    removeGrid := false.
-    removeAxis := false.
-    isInvalid  := false.
-    lockCriticalTask := Semaphore forMutualExclusion.
-
-
-    colorMap := Dictionary new.
-    colorMap at:(Color black)   put:Black.
-    colorMap at:(Color white)   put:White.
-    colorMap at:(Color blue)    put:Blue.
-    colorMap at:(Color cyan)    put:Cyan.
-    colorMap at:(Color magenta) put:Magenta.
-    colorMap at:(Color red)     put:Red.
-    colorMap at:(Color yellow)  put:Yellow.
-    colorMap at:(Color green)   put:Green.
-
-!
-
-realize
-    "define orthogonal projection; switch to back buffer drawing
-    "
-    super realize.
-    device glxOrthoLeft:-1.0 right:1.0 bottom:-1.0 top:1.0 near:10.0 far:-10.0 in:drawableId.
-    self backBuffer.
-
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'making objects'!
-
-make:aSelector
-
-    |id|
-
-    self makeObject:(id := self newObjectId).
-    self perform:aSelector.
-    self closeObject.
-  ^ id
-!
-
-makeAxis
-    |x z|
-
-    x := yValues first size.
-    z := yValues size - 1.
-
-    self setColor:(Color red).
-
-    device glxBeginLineIn:drawableId.
-    device glxV3fX:0 y:minY  z:0 in:drawableId.
-    device glxV3fX:x y:minY  z:0 in:drawableId.
-    device glxEndLineIn:drawableId.
-
-    device glxBeginLineIn:drawableId.
-    device glxV3fX:0 y:minY  z:0 in:drawableId.
-    device glxV3fX:0 y:maxY  z:0 in:drawableId.
-    device glxEndLineIn:drawableId.
-
-    device glxBeginLineIn:drawableId.
-    device glxV3fX:0 y:minY  z:0  in:drawableId.
-    device glxV3fX:0 y:minY  z:z in:drawableId.
-    device glxEndLineIn:drawableId.
-
-
-!
-
-makeFunc
-    "draw the graph and spawn the grid dependend on the enabled
-     attributes
-    "
-    |
-     x "{ Class:SmallInteger }"
-     z "{ Class:SmallInteger }"
-    |
-
-    z := 0.
-
-    yValues keysAndValuesDo:[:i :m|
-	x := 0.
-	self setColor:((loVCols at:i) foregroundColor).
-	device glxBeginLineIn:drawableId.
-
-	m do:[:y|
-	    device glxV3fX:x y:y z:z in:drawableId.
-	    x := x + 1.
-	].
-	device glxEndLineIn:drawableId.
-	z := z + 1
-    ]
-!
-
-makeGrid
-    "draw the graph and spawn the grid dependend on the enabled
-     attributes
-    "
-    |
-     noRows "| Class:SmallInteger }"
-     x      "{ Class:SmallInteger }"
-     z      "{ Class:SmallInteger }"
-    |
-
-    self setColor:(graph gridColor).
-    noRows := graph windowSize.
-    x      := 0.
-
-    1 to:noRows do:[:rI|
-	z := 0.
-	device glxBeginLineIn:drawableId.
-
-	yValues do:[:m|
-	    device glxV3fX:x y:(m at:rI) z:z in:drawableId.
-	    z := z + 1
-	].
-	device glxEndLineIn:drawableId.
-	x := x + 1
-    ].
-
-
-
-
-!
-
-makeRefs
-    "redraw current visible references
-    "
-    |z0 z1
-     noCols "{ Class:SmallInteger }"
-    |
-    noCols := yValues size.
-    z0 := -0.1.
-    z1 := noCols - 0.9.
-
-    self setColor:(graph referenceColor).
-
-    loVRefs do:[:x0|
-	device glxBeginLineIn:drawableId.
-	device glxV3fX:x0  y:maxY  z:z0  in:drawableId.
-	device glxV3fX:x0  y:minY  z:z0  in:drawableId.
-	device glxEndLineIn:drawableId.
-
-	device glxBeginLineIn:drawableId.
-	device glxV3fX:x0  y:maxY  z:z1  in:drawableId.
-	device glxV3fX:x0  y:minY  z:z1  in:drawableId.
-	device glxEndLineIn:drawableId.
-
-	1 to:noCols do:[:j||y|
-	    y := (yValues at:j) at:(x0 + 1).
-	    device glxBeginLineIn:drawableId.
-	    device glxV3fX:x0  y:y  z:z0   in:drawableId.
-	    device glxV3fX:x0  y:y  z:z1   in:drawableId.
-	    device glxEndLineIn:drawableId.
-	]
-    ]
-
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'private redraw'!
-
-criticalRedrawRoutine
-    "update all critical resources
-    "
-    removeFunc ifTrue:[
-	loVCols := nil.
-	loVRefs := nil.
-	yValues := nil.
-
-	glxObjFunc notNil ifTrue:[
-	    self deleteObject:glxObjFunc.
-	    glxObjFunc := nil
-	].
-	removeFunc := false.
-    ].
-
-    removeRefs ifTrue:[
-	loVRefs := nil.
-
-	glxObjRefs notNil ifTrue:[
-	    self deleteObject:glxObjRefs.
-	    glxObjRefs := nil.
-	].
-	removeRefs := false.
-    ].
-
-    removeGrid ifTrue:[
-	glxObjGrid notNil ifTrue:[
-	    self deleteObject:glxObjGrid.
-	    glxObjGrid := nil.
-	].
-	removeGrid := false.
-    ].
-
-    removeAxis ifTrue:[
-	glxObjAxis notNil ifTrue:[
-	    self deleteObject:glxObjAxis.
-	    glxObjAxis := nil.
-	].
-	removeAxis := false.
-    ].
-
-    shown ifTrue:[
-	self redrawInBackBuffer.
-	self swapBuffers.
-    ]
-
-
-!
-
-redrawInBackBuffer
-    "redraw in back
-    "
-    |sY sX sZ noCols dY winSize w2 showRefs showGrid showFunc showAxis gpOrgX|
-
-    self setColor:(graph backgroundColor).
-    self clear.
-
-    winSize := graph windowSize.
-
-    loVCols isNil ifTrue:[
-	(loVCols := graph listOfVisibleColumns) isEmpty ifTrue:[
-	    ^ self
-	].
-	gpOrgX  := graph graphOriginX.
-	yValues := loVCols collect:[:c| c yValuesStartAt:gpOrgX into:(Array new:winSize)].
-	maxY    := minY := (yValues at:1) at:1.
-
-	yValues do:[:m|
-	    m do:[:y|
-		maxY := maxY max:y.
-		minY := minY min:y.
-	    ]
-	]
-    ].
-
-    (noCols := loVCols size) == 0 ifTrue:[
-	^ self
-    ].
-
-    ((showGrid := graph showGrid) and:[glxObjGrid isNil]) ifTrue:[
-	noCols > 1 ifTrue:[glxObjGrid := self make:#makeGrid]
-		  ifFalse:[showGrid   := false]
-    ].
-
-    ((showFunc := graph showGraph) and:[glxObjFunc isNil]) ifTrue:[
-	glxObjFunc := self make:#makeFunc
-    ].
-
-    ((showAxis := graph showAxis) and:[glxObjAxis isNil]) ifTrue:[
-	glxObjAxis := self make:#makeAxis
-    ].
-
-    ((showRefs := graph showReferences) and:[glxObjRefs isNil]) ifTrue:[
-	loVRefs isNil ifTrue:[
-	    loVRefs := graph listOfVisibleRefIndices
-	].
-	loVRefs notEmpty ifTrue:[
-	    glxObjRefs := self make:#makeRefs
-	] ifFalse:[
-	    showRefs   := false
-	]
-    ].
-
-    sZ := graph zoomZ * (1.0 / noCols).
-    w2 := width // 2.
-
-"/  calculate scaleX dependent on height and scaleZ
-"/         and:#glxOrthoLeft:right:bottom:top:near:10.0 far:-10.0
-
-    sX := height // 2 * noCols * graph zoomZ / (20.0 sqrt).
-    sX := (((w2 * w2) + (sX raisedTo:2)) sqrt) - w2.
-    sX := sX / (width / winSize).
-    sX := 2.0 / (winSize + sX).
-
-    dY := (maxY - minY) / 2.
-    sY := ((0.5 / (dY max:2.0)) min:sX) * graph zoomY.
-
-    self pushMatrix.
-
-    self rotateX:(graph rotateX) y:(graph rotateY) z:(graph rotateZ).
-    self  scaleX:sX y:sY z:sZ.
-
-    self translateX:(winSize / -2.0)            "/ rotate center line
-		  y:(dY - maxY)                 "/ translate to center
-		  z:(noCols - 1 / -2.0).        "/ rotate center line
-
-    showGrid ifTrue:[ self callObject:glxObjGrid ].
-    showFunc ifTrue:[ self callObject:glxObjFunc ].
-    showAxis ifTrue:[ self callObject:glxObjAxis ].
-    showRefs ifTrue:[ self callObject:glxObjRefs ].
-
-    self popMatrix.
-
-!
-
-setColor:aColor
-    |index useCol|
-
-    useCol := aColor ? graph foregroundColor.
-    index  := colorMap at:useCol ifAbsent:nil.
-
-    index isNil ifTrue:[
-	index := colorMap size + self class numberOfStandardColors.
-
-	(    (index > self class maxColors)
-	 or:[(useCol := useCol on:device) colorId isNil]
-	) ifTrue:[
-	    Transcript showCR:'cannot allocate more colors'.
-	    index := (useCol brightness > 0.5) ifTrue:[White]
-					      ifFalse:[Black]
-	] ifFalse:[
-	    colorMap at:useCol put:index.
-
-	    self colorRed:(useCol red)
-		    green:(useCol green)
-		     blue:(useCol blue).
-
-	    self mapColor:index
-		      red:(useCol redByte)
-		    green:(useCol greenByte)
-		     blue:(useCol blueByte)
-	]
-    ].
-    self color:index.
-
-
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'redraw'!
-
-invalidate
-
-    lockCriticalTask critical:[
-	isInvalid := true.
-
-	criticalTask isNil ifTrue:[
-	    criticalTask := [
-		[   |repeat|
-
-		    lockCriticalTask critical:[
-			(repeat := isInvalid) ifTrue:[isInvalid    := false]
-					     ifFalse:[criticalTask := nil]
-		    ].
-		    repeat ifTrue:[ self criticalRedrawRoutine ].
-		    repeat
-
-		] whileTrue:[ Processor yield ].
-
-	    ] forkAt:( Processor activePriority - 1 ).
-	]
-    ]
-
-!
-
-redraw
-    "redraw
-    "
-    self invalidate
-! !
-
-!GraphColumnView3D::GLXGraph methodsFor:'removing'!
-
-deleteAllObjects
-    "delete all graphical objects
-    "
-    removeGrid := removeAxis := removeFunc := removeRefs := true.
-    self invalidate.
-!
-
-deleteAxis
-    removeAxis := true.
-!
-
-deleteColumns
-    "delete the columns
-    "
-    removeFunc := true.
-!
-
-deleteGrid
-    "delete the grid
-    "
-    removeGrid := true.
-!
-
-deleteReferences
-    "delete the references
-    "
-    removeRefs := true.
-! !
-
-!GraphColumnView3D class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView3D.st,v 1.9 2006-11-13 16:11:30 cg Exp $'
-! !
--- a/GraphColumnView3DSpec.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnView3DSpec.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 GraphColumnViewSpec subclass:#GraphColumnView3DSpec
 	instanceVariableNames:'rotateX rotateY rotateZ zoomZ'
 	classVariableNames:''
@@ -356,3 +358,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView3DSpec.st,v 1.10 2008-01-10 13:00:52 cg Exp $'
 ! !
+
--- a/GraphColumnViewSpec.st	Thu May 21 21:00:16 2015 +0100
+++ b/GraphColumnViewSpec.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 MenuComponentSpec subclass:#GraphColumnViewSpec
 	instanceVariableNames:'listHolder references referenceSelector showGrid showDefaultMenu
 		zoomY windowSize graphOriginX scrollUpdatesOriginX'
@@ -690,4 +692,5 @@
     ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnViewSpec.st,v 1.13 2008-01-10 13:00:55 cg Exp $'
 ! !
 
+
 GraphColumnViewSpec initialize!
--- a/HorizontalScale.st	Thu May 21 21:00:16 2015 +0100
+++ b/HorizontalScale.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 SimpleView subclass:#HorizontalScale
 	instanceVariableNames:'slider range action'
@@ -143,3 +144,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/HorizontalScale.st,v 1.6 2006-11-13 16:11:30 cg Exp $'
 ! !
+
--- a/ImageSelectionBox.st	Thu May 21 21:00:16 2015 +0100
+++ b/ImageSelectionBox.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 FileSelectionBox subclass:#ImageSelectionBox
 	instanceVariableNames:'previewField preview info'
@@ -19,7 +20,7 @@
 	category:'Views-DialogBoxes'
 !
 
-!ImageSelectionBox  class methodsFor:'documentation'!
+!ImageSelectionBox class methodsFor:'documentation'!
 
 copyright
 "
@@ -183,8 +184,9 @@
     "Modified: 7.6.1996 / 12:25:19 / cg"
 ! !
 
-!ImageSelectionBox  class methodsFor:'documentation'!
+!ImageSelectionBox class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ImageSelectionBox.st,v 1.6 2006-11-13 16:11:30 cg Exp $'
 ! !
+
--- a/KeyboardView.st	Thu May 21 21:00:16 2015 +0100
+++ b/KeyboardView.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 View subclass:#KeyboardView
 	instanceVariableNames:'targetView keyboardImage keyPositions shiftLeftState
 		shiftRightState altLeftState altRightState ctrlLeftState
--- a/LinkButton.st	Thu May 21 21:00:16 2015 +0100
+++ b/LinkButton.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 Button subclass:#LinkButton
 	instanceVariableNames:'labelsAndActions'
 	classVariableNames:'DefaultLinkColor'
@@ -9,6 +22,20 @@
 
 !LinkButton class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     Looks like a Label, but behaves like a button with individually clickable text components.
--- a/ListEditor.st	Thu May 21 21:00:16 2015 +0100
+++ b/ListEditor.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 ApplicationModel subclass:#ListEditor
 	instanceVariableNames:'choiceList choiceSelection selectionList selectionSelection'
@@ -200,3 +201,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ListEditor.st,v 1.5 2006-11-13 16:11:30 cg Exp $'
 ! !
+
--- a/Make.proto	Thu May 21 21:00:16 2015 +0100
+++ b/Make.proto	Thu May 21 21:14:57 2015 +0100
@@ -194,6 +194,7 @@
 $(OUTDIR)ImageEditView.$(O) ImageEditView.$(H): ImageEditView.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libwidg2/ImageView.$(H) $(STCHDR)
 $(OUTDIR)ModelListEntry.$(O) ModelListEntry.$(H): ModelListEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/ListEntry.$(H) $(STCHDR)
 $(OUTDIR)MultiColListEntry.$(O) MultiColListEntry.$(H): MultiColListEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/ListEntry.$(H) $(STCHDR)
+$(OUTDIR)PluggableHierarchicalList.$(O) PluggableHierarchicalList.$(H): PluggableHierarchicalList.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic2/List.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalList.$(H) $(STCHDR)
 $(OUTDIR)SelectionInListModelView.$(O) SelectionInListModelView.$(H): SelectionInListModelView.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libwidg2/ListModelView.$(H) $(STCHDR)
 $(OUTDIR)TabView.$(O) TabView.$(H): TabView.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libwidg2/NoteBookView.$(H) $(STCHDR)
 $(OUTDIR)ThreeColumnTextView.$(O) ThreeColumnTextView.$(H): ThreeColumnTextView.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libwidg2/SyncedMultiColumnTextView.$(H) $(STCHDR)
@@ -209,7 +210,6 @@
 $(OUTDIR)HierarchicalItemWithLabelAndIcon.$(O) HierarchicalItemWithLabelAndIcon.$(H): HierarchicalItemWithLabelAndIcon.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItemWithLabel.$(H) $(STCHDR)
 $(OUTDIR)LabelAndTwoIcons.$(O) LabelAndTwoIcons.$(H): LabelAndTwoIcons.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/LabelAndIcon.$(H) $(INCLUDE_TOP)/stx/libwidg2/ListEntry.$(H) $(INCLUDE_TOP)/stx/libwidg2/ModelListEntry.$(H) $(STCHDR)
 $(OUTDIR)HierarchicalItemWithLabelAndIconAndValue.$(O) HierarchicalItemWithLabelAndIconAndValue.$(H): HierarchicalItemWithLabelAndIconAndValue.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItemWithLabel.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItemWithLabelAndIcon.$(H) $(STCHDR)
-$(OUTDIR)LicenceBox.$(O) LicenceBox.$(H): LicenceBox.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/ModalBox.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/StandardSystemView.$(H) $(INCLUDE_TOP)/stx/libview/TopView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libwidg/DialogBox.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/Make.spec	Thu May 21 21:00:16 2015 +0100
+++ b/Make.spec	Thu May 21 21:14:57 2015 +0100
@@ -120,6 +120,7 @@
 	ImageEditView \
 	ModelListEntry \
 	MultiColListEntry \
+	PluggableHierarchicalList \
 	SelectionInListModelView \
 	TabView \
 	ThreeColumnTextView \
@@ -209,6 +210,7 @@
     $(OUTDIR_SLASH)ImageEditView.$(O) \
     $(OUTDIR_SLASH)ModelListEntry.$(O) \
     $(OUTDIR_SLASH)MultiColListEntry.$(O) \
+    $(OUTDIR_SLASH)PluggableHierarchicalList.$(O) \
     $(OUTDIR_SLASH)SelectionInListModelView.$(O) \
     $(OUTDIR_SLASH)TabView.$(O) \
     $(OUTDIR_SLASH)ThreeColumnTextView.$(O) \
--- a/MenuButton.st	Thu May 21 21:00:16 2015 +0100
+++ b/MenuButton.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 Button subclass:#MenuButton
 	instanceVariableNames:'enterAction'
 	classVariableNames:''
--- a/MotionButton.st	Thu May 21 21:00:16 2015 +0100
+++ b/MotionButton.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 Button subclass:#MotionButton
 	instanceVariableNames:'oldBorderWidth'
 	classVariableNames:''
--- a/NoteBookFrameView.st	Thu May 21 21:00:16 2015 +0100
+++ b/NoteBookFrameView.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 SimpleView subclass:#NoteBookFrameView
 	instanceVariableNames:''
@@ -169,3 +170,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/NoteBookFrameView.st,v 1.3 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- a/ParagraphSpecification.st	Thu May 21 21:00:16 2015 +0100
+++ b/ParagraphSpecification.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 TabulatorSpecification subclass:#ParagraphSpecification
 	instanceVariableNames:'leftMargin rightMargin textAlignment'
@@ -48,25 +49,30 @@
 leftMargin
     "return leftMargin"
 
-    ^ leftMargin!
+    ^ leftMargin
+!
 
 leftMargin:something
     "set leftMargin"
 
-    leftMargin := something.!
+    leftMargin := something.
+!
 
 rightMargin
     "return rightMargin"
 
-    ^ rightMargin!
+    ^ rightMargin
+!
 
 rightMargin:something
     "set rightMargin"
 
-    rightMargin := something.! !
+    rightMargin := something.
+! !
 
 !ParagraphSpecification class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/ParagraphSpecification.st,v 1.6 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PluggableHierarchicalList.st	Thu May 21 21:14:57 2015 +0100
@@ -0,0 +1,137 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libwidg2' }"
+
+"{ NameSpace: Smalltalk }"
+
+HierarchicalList subclass:#PluggableHierarchicalList
+	instanceVariableNames:'childBlock labelBlock iconBlock'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Support'
+!
+
+!PluggableHierarchicalList class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    A customizable hierarchical tree list for ad-hoc trees
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+        protocol examples
+
+"
+! !
+
+!PluggableHierarchicalList class methodsFor:'examples'!
+
+example1
+    | window view list |
+    "
+    PluggableHierarchicalList example1
+    "
+
+    window := StandardSystemView new; extent:300@300.  
+    window label: self class name , '>> #example1'.
+    view := ScrollableView for:HierarchicalListView origin:0.0@0.0 corner:1.0@1.0 in: window.
+
+    list := PluggableHierarchicalList new.
+    list childBlock:[ :parent | 1 to: 5 collect: [:i | parent copyWith: i ] ].
+    list labelBlock:[ :child  | 'Section ' , child printString ].
+    list root: #(1).
+    view list: list.
+
+    window open.
+
+    "Created: / 21-05-2015 / 19:05:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PluggableHierarchicalList methodsFor:'accessing'!
+
+childBlock
+    ^ childBlock
+!
+
+childBlock:aBlock
+    childBlock := aBlock.
+!
+
+iconBlock
+    ^ iconBlock
+!
+
+iconBlock:aBlock
+    iconBlock := aBlock.
+!
+
+labelBlock
+    ^ labelBlock
+!
+
+labelBlock:aBlock
+    labelBlock := aBlock.
+! !
+
+!PluggableHierarchicalList methodsFor:'accessing-root'!
+
+root:anObject
+    | item |
+
+    item := HierarchicalItemWithLabelAndIconAndValue new.
+    item label: (labelBlock notNil ifTrue:[ labelBlock value: anObject ] ifFalse:[ anObject displayString ]).
+    item icon:  (iconBlock notNil ifTrue:[ iconBlock value: anObject ] ifFalse:[ nil ]).
+    item value: anObject. 
+    super root: item.
+
+    "Created: / 21-05-2015 / 19:17:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!PluggableHierarchicalList methodsFor:'protocol'!
+
+childrenFor: parentItem
+    | parent children |
+
+    parent := parentItem value.
+    children := childBlock value: parent.
+    ^ children collect:[ :child |
+        | childItem |
+        childItem := HierarchicalItemWithLabelAndIconAndValue new.
+        childItem label: (labelBlock notNil ifTrue:[ labelBlock value: child ] ifFalse:[ child displayString ]).
+        childItem icon:  (iconBlock notNil ifTrue:[ iconBlock value: child] ifFalse:[ nil ]).
+        childItem value: child.   
+        childItem parent: parentItem
+    ]
+
+    "Created: / 21-05-2015 / 19:19:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/RoundButton.st	Thu May 21 21:00:16 2015 +0100
+++ b/RoundButton.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 Button subclass:#RoundButton
 	instanceVariableNames:''
@@ -148,3 +149,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/RoundButton.st,v 1.5 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- a/Ruler.st	Thu May 21 21:00:16 2015 +0100
+++ b/Ruler.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 SimpleView subclass:#Ruler
 	instanceVariableNames:'fgColor metric paperWidth paperHeight scale showUnit orientation'
@@ -513,3 +514,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.28 2002-10-31 21:49:29 cg Exp $'
 ! !
+
--- a/Scale.st	Thu May 21 21:00:16 2015 +0100
+++ b/Scale.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 SimpleView subclass:#Scale
 	instanceVariableNames:'slider range action'
@@ -141,3 +142,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/Scale.st,v 1.6 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- a/SelectionInHierarchyView.st	Thu May 21 21:00:16 2015 +0100
+++ b/SelectionInHierarchyView.st	Thu May 21 21:14:57 2015 +0100
@@ -10,8 +10,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 SelectionInListView subclass:#SelectionInHierarchyView
 	instanceVariableNames:'itemList showConnectingLines itemClass indent itemPrintConverter'
@@ -137,7 +138,8 @@
 	super selection:  anIndex.
 	model selection:  anIndex.
 
-	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"
+!
 
 selectionIndex: anIndex
 	"Pass the selection along to the model."
@@ -190,7 +192,8 @@
 
     super keyPress:key x:x y:y
 
-	"Modified: 10.10.94 / 16:13:38 / W.Olberding"! !
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"
+! !
 
 !SelectionInHierarchyView methodsFor:'initialization'!
 
@@ -230,7 +233,8 @@
 
        ^Array new: 0.
 
-	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"
+!
 
 getListFromModel
     "Get list entries from model.
@@ -368,7 +372,8 @@
        self selection: (self getSelectionFromModel).
 
 	"Modified: 10.10.94 / 17:13:38 / W.Olberding"
-	"Modified: 08.11.94 / 15:28:03 / R.Sailer"! !
+	"Modified: 08.11.94 / 15:28:03 / R.Sailer"
+! !
 
 !SelectionInHierarchyView methodsFor:'updating'!
 
@@ -382,10 +387,12 @@
      aSymbol==#attributes
 	ifTrue: [].
 
-	"Modified: 10.10.94 / 16:13:38 / W.Olberding"! !
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"
+! !
 
 !SelectionInHierarchyView class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInHierarchyView.st,v 1.12 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- a/StrokeView.st	Thu May 21 21:00:16 2015 +0100
+++ b/StrokeView.st	Thu May 21 21:14:57 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 View subclass:#StrokeView
 	instanceVariableNames:'strokes currentStroke lastPoint clearButton clearLastButton
 		strokeAction'
@@ -190,3 +192,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/StrokeView.st,v 1.3 2004-03-02 08:44:45 cg Exp $'
 ! !
+
--- a/TabControl.st	Thu May 21 21:00:16 2015 +0100
+++ b/TabControl.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 NoteBookView subclass:#TabControl
 	instanceVariableNames:''
@@ -230,3 +231,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/TabControl.st,v 1.2 2006-03-13 19:27:30 cg Exp $'
 ! !
+
--- a/TabView.st	Thu May 21 21:00:16 2015 +0100
+++ b/TabView.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 NoteBookView subclass:#TabView
 	instanceVariableNames:''
 	classVariableNames:''
@@ -152,4 +154,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.48 2010-05-11 11:43:14 ca Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
+
--- a/TextRuler.st	Thu May 21 21:00:16 2015 +0100
+++ b/TextRuler.st	Thu May 21 21:14:57 2015 +0100
@@ -9,16 +9,17 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 Ruler subclass:#TextRuler
-	 instanceVariableNames:'leftMargin rightMargin spec moving settingTab'
-	 classVariableNames:'LeftAlignForm RightAlignForm AlignForm CenterForm LeftMarginForm
+	instanceVariableNames:'leftMargin rightMargin spec moving settingTab'
+	classVariableNames:'LeftAlignForm RightAlignForm AlignForm CenterForm LeftMarginForm
 		RightMarginForm LeftTabForm RightTabForm CenterTabForm
 		DecimalTabForm'
-	 poolDictionaries:''
-	 category:'Views-Interactors'
+	poolDictionaries:''
+	category:'Views-Interactors'
 !
 
 !TextRuler class methodsFor:'documentation'!
@@ -48,48 +49,17 @@
 
     TextRuler new open
 "
-!
-
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TextRuler.st,v 1.15 2006-11-13 16:11:31 cg Exp $'
 ! !
 
 !TextRuler class methodsFor:'defaults'!
 
-rightMarginForm
-    "return the form displayed for the right margin marker"
+alignForm
+    "return the form displayed in the align-button"
 
-    RightMarginForm isNil ifTrue:[
-	RightMarginForm := Image fromFile:'bitmaps/rightMarg.xbm' resolution:100
-    ].
-    ^ RightMarginForm
-!
-
-leftMarginForm
-    "return the form displayed for the left margin marker"
-
-    LeftMarginForm isNil ifTrue:[
-	LeftMarginForm := Image fromFile:'bitmaps/leftMargin.xbm' resolution:100
+    AlignForm isNil ifTrue:[
+	AlignForm := Image fromFile:'bitmaps/align.xbm' resolution:100
     ].
-    ^ LeftMarginForm
-!
-
-rightAlignForm
-    "return the form displayed in the rightAlign-button"
-
-    RightAlignForm isNil ifTrue:[
-	RightAlignForm :=  Image fromFile:'bitmaps/rightAlign.xbm' resolution:100
-    ].
-    ^ RightAlignForm
-!
-
-leftTabForm
-    "return the form displayed in the leftTab-button"
-
-    LeftTabForm isNil ifTrue:[
-	LeftTabForm := Image fromFile:'bitmaps/leftTab.xbm' resolution:100
-    ].
-    ^ LeftTabForm
+    ^ AlignForm
 !
 
 centerForm
@@ -101,31 +71,13 @@
     ^ CenterForm
 !
 
-alignForm
-    "return the form displayed in the align-button"
-
-    AlignForm isNil ifTrue:[
-	AlignForm := Image fromFile:'bitmaps/align.xbm' resolution:100
-    ].
-    ^ AlignForm
-!
-
-rightTabForm
-    "return the form displayed in the rightTab-button"
+centerTabForm
+    "return the form displayed in the centerTab-button"
 
-    RightTabForm isNil ifTrue:[
-	RightTabForm := Image fromFile:'bitmaps/rightTab.xbm' resolution:100
+    CenterTabForm isNil ifTrue:[
+	CenterTabForm := Image fromFile:'bitmaps/centerTab.xbm' resolution:100
     ].
-    ^ RightTabForm
-!
-
-leftAlignForm
-    "return the form displayed in the leftAlign-button"
-
-    LeftAlignForm isNil ifTrue:[
-	LeftAlignForm := Image fromFile:'bitmaps/leftAlign.xbm' resolution:100
-    ].
-    ^ LeftAlignForm
+    ^ CenterTabForm
 !
 
 decimalTabForm
@@ -137,13 +89,58 @@
     ^ DecimalTabForm
 !
 
-centerTabForm
-    "return the form displayed in the centerTab-button"
+leftAlignForm
+    "return the form displayed in the leftAlign-button"
+
+    LeftAlignForm isNil ifTrue:[
+	LeftAlignForm := Image fromFile:'bitmaps/leftAlign.xbm' resolution:100
+    ].
+    ^ LeftAlignForm
+!
+
+leftMarginForm
+    "return the form displayed for the left margin marker"
+
+    LeftMarginForm isNil ifTrue:[
+	LeftMarginForm := Image fromFile:'bitmaps/leftMargin.xbm' resolution:100
+    ].
+    ^ LeftMarginForm
+!
+
+leftTabForm
+    "return the form displayed in the leftTab-button"
 
-    CenterTabForm isNil ifTrue:[
-	CenterTabForm := Image fromFile:'bitmaps/centerTab.xbm' resolution:100
+    LeftTabForm isNil ifTrue:[
+	LeftTabForm := Image fromFile:'bitmaps/leftTab.xbm' resolution:100
+    ].
+    ^ LeftTabForm
+!
+
+rightAlignForm
+    "return the form displayed in the rightAlign-button"
+
+    RightAlignForm isNil ifTrue:[
+	RightAlignForm :=  Image fromFile:'bitmaps/rightAlign.xbm' resolution:100
     ].
-    ^ CenterTabForm
+    ^ RightAlignForm
+!
+
+rightMarginForm
+    "return the form displayed for the right margin marker"
+
+    RightMarginForm isNil ifTrue:[
+	RightMarginForm := Image fromFile:'bitmaps/rightMarg.xbm' resolution:100
+    ].
+    ^ RightMarginForm
+!
+
+rightTabForm
+    "return the form displayed in the rightTab-button"
+
+    RightTabForm isNil ifTrue:[
+	RightTabForm := Image fromFile:'bitmaps/rightTab.xbm' resolution:100
+    ].
+    ^ RightTabForm
 ! !
 
 !TextRuler methodsFor:'accessing'!
@@ -152,232 +149,6 @@
     spec := aSpec
 ! !
 
-!TextRuler methodsFor:'redrawing'!
-
-redraw
-    "redraw margin & tab marks"
-
-    |x top form tab type tabStops tabAlign viewOrigin orgX orgY|
-
-    self clear.
-
-    super redraw.
-
-    viewOrigin := self viewOrigin.
-    orgX := viewOrigin x.
-    orgY := viewOrigin y.
-
-    self paint:fgColor.
-
-    top := height - (font height) - (font ascent).
-
-    x := (self inchToPixel:leftMargin) rounded.
-    form := self class leftMarginForm.
-    self displayForm:form
-		   x:(x - (form width // 2) - orgX)
-		   y:(top - form height - orgY).
-
-    x := (self inchToPixel:rightMargin) rounded.
-    form := self class rightMarginForm.
-    self displayForm:form
-		   x:(x - (form width // 2) - orgX)
-		   y:(top - form height - orgY).
-
-    spec notNil ifTrue:[
-	tabStops := spec positions.
-	tabAlign := spec align.
-	tabStops notNil ifTrue:[
-	    1 to:tabStops size do:[:tabNr |
-		tab := tabStops at:tabNr.
-		type := tabAlign at:tabNr.
-		x := (spec positionOfTab:tabNr on:self) rounded.
-		(type == #left) ifTrue:[
-		    form := self class leftTabForm
-		] ifFalse:[
-		    (type == #right) ifTrue:[
-			form := self class rightTabForm
-		    ] ifFalse:[
-			(type == #center) ifTrue:[
-			    form := self class centerTabForm
-			] ifFalse:[
-			    (type == #decimal) ifTrue:[
-				form := self class decimalTabForm
-			    ]
-			]
-		    ]
-		].
-		self displayForm:form
-			       x:(x - (form width // 2) - orgX)
-			       y:(top - form height - orgY)
-	    ]
-	]
-    ]
-!
-
-clearMargin:which
-    "clear margin"
-
-    |this other otherX otherX2 x x2 top form symOther viewOrigin|
-
-    self paint:viewBackground.
-
-    top := height - (font height) - (font ascent).
-
-    (which == #left) ifTrue:[
-	this := leftMargin.
-	other := rightMargin. symOther := #right.
-	form := self class leftMarginForm
-    ].
-    (which == #right) ifTrue:[
-	this := rightMargin.
-	other := leftMargin. symOther := #left.
-	form := self class rightMarginForm
-    ].
-
-    x := (self inchToPixel:this) rounded - (form width // 2).
-    viewOrigin := self viewOrigin.
-    self displayForm:form
-		   x:x + viewOrigin x
-		   y:(top - form height - viewOrigin y).
-
-    "
-     if it covers any other, redraw them
-    "
-    x2 := x + form width.
-    otherX := (self inchToPixel:other) rounded - (form width // 2).
-    otherX2 := otherX + form width.
-
-    otherX  > x2 ifFalse:[
-	otherX2 < x ifFalse:[
-	    self drawMargin:symOther
-	]
-    ].
-!
-
-drawMargin:which
-    "clear margin"
-
-    |x top form viewOrigin|
-
-    self paint:fgColor.
-
-    top := height - (font height) - (font ascent).
-
-    (which == #left) ifTrue:[
-	x := (self inchToPixel:leftMargin) rounded.
-	form := self class leftMarginForm
-    ].
-    (which == #right) ifTrue:[
-	x := (self inchToPixel:rightMargin) rounded.
-	form := self class rightMarginForm
-    ].
-
-    viewOrigin := self viewOrigin.
-    self displayForm:form
-		   x:(x - (form width // 2) - viewOrigin x)
-		   y:(top - form height - viewOrigin y).
-
-! !
-
-!TextRuler methodsFor:'user interaction'!
-
-buttonRelease:button x:x y:y
-    "position a tab or start moving a ruler"
-
-    moving := nil
-!
-
-buttonPress:button x:pX y:y
-    "position a tab or start moving a ruler"
-
-    |mpos x|
-
-    ((button == #select) or:[button == 1]) ifFalse:[
-	^ super buttonPress:button x:pX y:y
-    ].
-
-    x := pX + self viewOrigin x.
-    settingTab notNil ifTrue:[
-	self setTabX:x.
-	settingTab := nil.
-	^ self
-    ].
-
-    mpos := self inchToPixel:leftMargin.
-    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
-	"start moving left margin"
-	moving := #left.
-	^ self
-    ].
-    mpos := self inchToPixel:rightMargin.
-    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
-	"start moving right margin"
-	moving := #right.
-	^ self
-    ].
-
-    ^ self
-!
-
-buttonMotion:state x:x y:y
-    "position a tab or start moving a ruler"
-
-    |mpos|
-
-    moving notNil ifTrue:[
-	self clearMargin:moving.
-	mpos := self pixelToInch:x + self viewOrigin x.
-	(mpos < 0) ifTrue:[
-	    mpos := 0
-	].
-	(mpos > paperWidth) ifTrue:[
-	    mpos := paperWidth
-	].
-	(moving == #left) ifTrue:[
-	    leftMargin := mpos
-	].
-	(moving == #right) ifTrue:[
-	    rightMargin := mpos
-	].
-	self drawMargin:moving
-    ]
-!
-
-leftAlign
-    ^ self
-!
-
-rightAlign
-    ^ self
-!
-
-leftTab
-    settingTab := #left.
-
-!
-
-align
-    ^ self
-!
-
-center
-    ^ self
-!
-
-centerTab
-    settingTab := #center.
-!
-
-rightTab
-    settingTab := #right.
-
-!
-
-decimalTab
-    settingTab := #decimal.
-
-! !
-
 !TextRuler methodsFor:'initializing'!
 
 initialize
@@ -447,3 +218,236 @@
 
     "TextRuler new open"
 ! !
+
+!TextRuler methodsFor:'redrawing'!
+
+clearMargin:which
+    "clear margin"
+
+    |this other otherX otherX2 x x2 top form symOther viewOrigin|
+
+    self paint:viewBackground.
+
+    top := height - (font height) - (font ascent).
+
+    (which == #left) ifTrue:[
+	this := leftMargin.
+	other := rightMargin. symOther := #right.
+	form := self class leftMarginForm
+    ].
+    (which == #right) ifTrue:[
+	this := rightMargin.
+	other := leftMargin. symOther := #left.
+	form := self class rightMarginForm
+    ].
+
+    x := (self inchToPixel:this) rounded - (form width // 2).
+    viewOrigin := self viewOrigin.
+    self displayForm:form
+		   x:x + viewOrigin x
+		   y:(top - form height - viewOrigin y).
+
+    "
+     if it covers any other, redraw them
+    "
+    x2 := x + form width.
+    otherX := (self inchToPixel:other) rounded - (form width // 2).
+    otherX2 := otherX + form width.
+
+    otherX  > x2 ifFalse:[
+	otherX2 < x ifFalse:[
+	    self drawMargin:symOther
+	]
+    ].
+!
+
+drawMargin:which
+    "clear margin"
+
+    |x top form viewOrigin|
+
+    self paint:fgColor.
+
+    top := height - (font height) - (font ascent).
+
+    (which == #left) ifTrue:[
+	x := (self inchToPixel:leftMargin) rounded.
+	form := self class leftMarginForm
+    ].
+    (which == #right) ifTrue:[
+	x := (self inchToPixel:rightMargin) rounded.
+	form := self class rightMarginForm
+    ].
+
+    viewOrigin := self viewOrigin.
+    self displayForm:form
+		   x:(x - (form width // 2) - viewOrigin x)
+		   y:(top - form height - viewOrigin y).
+
+!
+
+redraw
+    "redraw margin & tab marks"
+
+    |x top form tab type tabStops tabAlign viewOrigin orgX orgY|
+
+    self clear.
+
+    super redraw.
+
+    viewOrigin := self viewOrigin.
+    orgX := viewOrigin x.
+    orgY := viewOrigin y.
+
+    self paint:fgColor.
+
+    top := height - (font height) - (font ascent).
+
+    x := (self inchToPixel:leftMargin) rounded.
+    form := self class leftMarginForm.
+    self displayForm:form
+		   x:(x - (form width // 2) - orgX)
+		   y:(top - form height - orgY).
+
+    x := (self inchToPixel:rightMargin) rounded.
+    form := self class rightMarginForm.
+    self displayForm:form
+		   x:(x - (form width // 2) - orgX)
+		   y:(top - form height - orgY).
+
+    spec notNil ifTrue:[
+	tabStops := spec positions.
+	tabAlign := spec align.
+	tabStops notNil ifTrue:[
+	    1 to:tabStops size do:[:tabNr |
+		tab := tabStops at:tabNr.
+		type := tabAlign at:tabNr.
+		x := (spec positionOfTab:tabNr on:self) rounded.
+		(type == #left) ifTrue:[
+		    form := self class leftTabForm
+		] ifFalse:[
+		    (type == #right) ifTrue:[
+			form := self class rightTabForm
+		    ] ifFalse:[
+			(type == #center) ifTrue:[
+			    form := self class centerTabForm
+			] ifFalse:[
+			    (type == #decimal) ifTrue:[
+				form := self class decimalTabForm
+			    ]
+			]
+		    ]
+		].
+		self displayForm:form
+			       x:(x - (form width // 2) - orgX)
+			       y:(top - form height - orgY)
+	    ]
+	]
+    ]
+! !
+
+!TextRuler methodsFor:'user interaction'!
+
+align
+    ^ self
+!
+
+buttonMotion:state x:x y:y
+    "position a tab or start moving a ruler"
+
+    |mpos|
+
+    moving notNil ifTrue:[
+	self clearMargin:moving.
+	mpos := self pixelToInch:x + self viewOrigin x.
+	(mpos < 0) ifTrue:[
+	    mpos := 0
+	].
+	(mpos > paperWidth) ifTrue:[
+	    mpos := paperWidth
+	].
+	(moving == #left) ifTrue:[
+	    leftMargin := mpos
+	].
+	(moving == #right) ifTrue:[
+	    rightMargin := mpos
+	].
+	self drawMargin:moving
+    ]
+!
+
+buttonPress:button x:pX y:y
+    "position a tab or start moving a ruler"
+
+    |mpos x|
+
+    ((button == #select) or:[button == 1]) ifFalse:[
+	^ super buttonPress:button x:pX y:y
+    ].
+
+    x := pX + self viewOrigin x.
+    settingTab notNil ifTrue:[
+	self setTabX:x.
+	settingTab := nil.
+	^ self
+    ].
+
+    mpos := self inchToPixel:leftMargin.
+    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
+	"start moving left margin"
+	moving := #left.
+	^ self
+    ].
+    mpos := self inchToPixel:rightMargin.
+    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
+	"start moving right margin"
+	moving := #right.
+	^ self
+    ].
+
+    ^ self
+!
+
+buttonRelease:button x:x y:y
+    "position a tab or start moving a ruler"
+
+    moving := nil
+!
+
+center
+    ^ self
+!
+
+centerTab
+    settingTab := #center.
+!
+
+decimalTab
+    settingTab := #decimal.
+
+!
+
+leftAlign
+    ^ self
+!
+
+leftTab
+    settingTab := #left.
+
+!
+
+rightAlign
+    ^ self
+!
+
+rightTab
+    settingTab := #right.
+
+! !
+
+!TextRuler class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/TextRuler.st,v 1.15 2006-11-13 16:11:31 cg Exp $'
+! !
+
--- a/VT52TerminalView.st	Thu May 21 21:00:16 2015 +0100
+++ b/VT52TerminalView.st	Thu May 21 21:14:57 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libwidg2' }"
 
+"{ NameSpace: Smalltalk }"
+
 TerminalView subclass:#VT52TerminalView
 	instanceVariableNames:'param1 param2'
 	classVariableNames:''
--- a/VerticalRuler.st	Thu May 21 21:00:16 2015 +0100
+++ b/VerticalRuler.st	Thu May 21 21:14:57 2015 +0100
@@ -9,8 +9,9 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libwidg2' }"
 
-"{ Package: 'stx:libwidg2' }"
+"{ NameSpace: Smalltalk }"
 
 Ruler subclass:#VerticalRuler
 	instanceVariableNames:''
@@ -60,3 +61,4 @@
 version
     ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.11 2006-11-13 16:11:31 cg Exp $'
 ! !
+
--- a/abbrev.stc	Thu May 21 21:00:16 2015 +0100
+++ b/abbrev.stc	Thu May 21 21:14:57 2015 +0100
@@ -70,6 +70,7 @@
 ImageEditView ImageEditView stx:libwidg2 'Views-Misc' 2
 ModelListEntry ModelListEntry stx:libwidg2 'Views-Support' 0
 MultiColListEntry MultiColListEntry stx:libwidg2 'Views-Support' 0
+PluggableHierarchicalList PluggableHierarchicalList stx:libwidg2 'Views-Support' 0
 SelectionInListModelView SelectionInListModelView stx:libwidg2 'Views-Lists' 2
 TabView TabView stx:libwidg2 'Views-Interactors' 2
 ThreeColumnTextView ThreeColumnTextView stx:libwidg2 'Views-Text' 2
@@ -112,4 +113,3 @@
 TextRuler TextRuler stx:libwidg2 'Views-Interactors' 2
 VT52TerminalView VT52TerminalView stx:libwidg2 'Views-TerminalViews' 2
 VerticalRuler VerticalRuler stx:libwidg2 'Views-Misc' 2
-LicenceBox LicenceBox stx:libwidg2 'Views-DialogBoxes' 2
--- a/bc.mak	Thu May 21 21:00:16 2015 +0100
+++ b/bc.mak	Thu May 21 21:14:57 2015 +0100
@@ -144,6 +144,7 @@
 $(OUTDIR)ImageEditView.$(O) ImageEditView.$(H): ImageEditView.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libwidg2\ImageView.$(H) $(STCHDR)
 $(OUTDIR)ModelListEntry.$(O) ModelListEntry.$(H): ModelListEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\ListEntry.$(H) $(STCHDR)
 $(OUTDIR)MultiColListEntry.$(O) MultiColListEntry.$(H): MultiColListEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\ListEntry.$(H) $(STCHDR)
+$(OUTDIR)PluggableHierarchicalList.$(O) PluggableHierarchicalList.$(H): PluggableHierarchicalList.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic2\List.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalList.$(H) $(STCHDR)
 $(OUTDIR)SelectionInListModelView.$(O) SelectionInListModelView.$(H): SelectionInListModelView.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libwidg2\ListModelView.$(H) $(STCHDR)
 $(OUTDIR)TabView.$(O) TabView.$(H): TabView.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libwidg2\NoteBookView.$(H) $(STCHDR)
 $(OUTDIR)ThreeColumnTextView.$(O) ThreeColumnTextView.$(H): ThreeColumnTextView.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libwidg2\SyncedMultiColumnTextView.$(H) $(STCHDR)
@@ -159,7 +160,6 @@
 $(OUTDIR)HierarchicalItemWithLabelAndIcon.$(O) HierarchicalItemWithLabelAndIcon.$(H): HierarchicalItemWithLabelAndIcon.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItemWithLabel.$(H) $(STCHDR)
 $(OUTDIR)LabelAndTwoIcons.$(O) LabelAndTwoIcons.$(H): LabelAndTwoIcons.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\LabelAndIcon.$(H) $(INCLUDE_TOP)\stx\libwidg2\ListEntry.$(H) $(INCLUDE_TOP)\stx\libwidg2\ModelListEntry.$(H) $(STCHDR)
 $(OUTDIR)HierarchicalItemWithLabelAndIconAndValue.$(O) HierarchicalItemWithLabelAndIconAndValue.$(H): HierarchicalItemWithLabelAndIconAndValue.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItemWithLabel.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItemWithLabelAndIcon.$(H) $(STCHDR)
-$(OUTDIR)LicenceBox.$(O) LicenceBox.$(H): LicenceBox.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\ModalBox.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\StandardSystemView.$(H) $(INCLUDE_TOP)\stx\libview\TopView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libwidg\DialogBox.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/libInit.cc	Thu May 21 21:00:16 2015 +0100
+++ b/libInit.cc	Thu May 21 21:14:57 2015 +0100
@@ -96,6 +96,7 @@
 _ImageEditView_Init(pass,__pRT__,snd);
 _ModelListEntry_Init(pass,__pRT__,snd);
 _MultiColListEntry_Init(pass,__pRT__,snd);
+_PluggableHierarchicalList_Init(pass,__pRT__,snd);
 _SelectionInListModelView_Init(pass,__pRT__,snd);
 _TabView_Init(pass,__pRT__,snd);
 _ThreeColumnTextView_Init(pass,__pRT__,snd);
@@ -111,7 +112,6 @@
 _HierarchicalItemWithLabelAndIcon_Init(pass,__pRT__,snd);
 _LabelAndTwoIcons_Init(pass,__pRT__,snd);
 _HierarchicalItemWithLabelAndIconAndValue_Init(pass,__pRT__,snd);
-_LicenceBox_Init(pass,__pRT__,snd);
 
 
 __END_PACKAGE__();
--- a/stx_libwidg2.st	Thu May 21 21:00:16 2015 +0100
+++ b/stx_libwidg2.st	Thu May 21 21:14:57 2015 +0100
@@ -75,34 +75,48 @@
 !
 
 mandatoryPreRequisites
-    "list all required mandatory packages.
-     Packages are mandatory, if they contain superclasses of the package's classes
-     or classes which are extended by this package.
-     This list can be maintained manually or (better) generated and
-     updated by scanning the superclass hierarchies
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+    "list packages which are mandatory as a prerequisite.
+     This are packages containing superclasses of my classes and classes which
+     are extended by myself.
+     They are mandatory, because we need these packages as a prerequisite for loading and compiling.
+     This method is generated automatically,
+     by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "Notification - superclass of ProgressNotification "
-        #'stx:libbasic2'    "List - superclass of HierarchicalList "
-        #'stx:libview'    "TopView - superclass of ExtendedComboBox::MenuWrapper "
-        #'stx:libview2'    "ApplicationModel - superclass of PrintingDialog "
-        #'stx:libwidg'    "ListView - superclass of FilenameEditField "
+        #'stx:libbasic'    "ActivityNotification - superclass of ProgressNotification"
+        #'stx:libbasic2'    "List - superclass of HierarchicalFileList"
+        #'stx:libview'    "Controller - superclass of LinkButtonController"
+        #'stx:libview2'    "ApplicationModel - superclass of AssistantApplication"
+        #'stx:libwidg'    "Button - superclass of ComboBoxButton"
     )
 !
 
 referencedPreRequisites
-    "list all packages containing classes referenced by the packages's members.
-     This list can be maintained manually or (better) generated and
-     updated by looking for global variable accesses
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+    "list packages which are a prerequisite, because they contain
+     classes which are referenced by my classes.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
+     This method is generated automatically,
+     by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:libui'    "DividerSpec - referenced by Separator>>specClass "
+        #'stx:goodies/refactoryBrowser/browser'    "RefactoryTyper - referenced by DoWhatIMeanSupport>>codeCompletionForMessage:inClass:instance:context:codeView:"
+        #'stx:libboss'    "ObsoleteObject - referenced by DoWhatIMeanSupport>>codeCompletionForMessage:inClass:instance:context:codeView:"
+        #'stx:libjava'    "JavaLanguage - referenced by DoWhatIMeanSupport>>codeCompletionFor:language:method:orClass:context:codeView:into:"
+        #'stx:libjavascript'    "JavaScriptCompletionEngine - referenced by DoWhatIMeanSupport>>codeCompletionForJavascriptMethod:orClass:context:codeView:into:"
+        #'stx:libui'    "ComboBoxSpec - referenced by ComboBoxView>>specClass"
+    )
+!
+
+subProjects
+    "list packages which are known as subprojects.
+     The generated makefile will enter those and make there as well.
+     However: they are not forced to be loaded when a package is loaded;
+     for those, redefine requiredPrerequisites."
+
+    ^ #(
     )
 ! !
 
@@ -157,6 +171,7 @@
         HierarchyNode
         ImageView
         LabelledEnterField
+        LicenceBox
         LinkButton
         LinkButtonController
         ListEntry
@@ -200,6 +215,7 @@
         ImageEditView
         ModelListEntry
         MultiColListEntry
+        PluggableHierarchicalList
         SelectionInListModelView
         TabView
         ThreeColumnTextView
@@ -215,10 +231,6 @@
         HierarchicalItemWithLabelAndIcon
         LabelAndTwoIcons
         HierarchicalItemWithLabelAndIconAndValue
-        (KeyboardView autoload)
-        (MenuButton autoload)
-        (StrokeView autoload)
-        (TabControl autoload)
         (ColoredListEntry autoload)
         (ComboBrowseView autoload)
         (ComboUpDownView autoload)
@@ -231,7 +243,9 @@
         (GraphColumnViewSpec autoload)
         (HorizontalScale autoload)
         (ImageSelectionBox autoload)
+        (KeyboardView autoload)
         (ListEditor autoload)
+        (MenuButton autoload)
         (MotionButton autoload)
         (NoteBookFrameView autoload)
         (ParagraphSpecification autoload)
@@ -239,6 +253,8 @@
         (Ruler autoload)
         (Scale autoload)
         (SelectionInHierarchyView autoload)
+        (StrokeView autoload)
+        (TabControl autoload)
         (TextRuler autoload)
         (VT52TerminalView autoload)
         (VerticalRuler autoload)
@@ -246,8 +262,8 @@
 !
 
 extensionMethodNames
-    "lists the extension methods which are to be included in the project.
-     Entries are 2-element array literals, consisting of class-name and selector."
+    "list class/selector pairs of extensions.
+     A correponding method with real names must be present in my concrete subclasses"
 
     ^ #(
     )
@@ -296,5 +312,9 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libwidg2/stx_libwidg2.st,v 1.53 2015-05-01 14:41:51 cg Exp $'
+!
+
+version_HG
+    ^ '$Changeset: <not expanded> $'
 ! !