Move `CodeGenerator` and `CodeGeneratorTests` to namespace `Tools` jv
authorJan Vrany <jan.vrany@labware.com>
Wed, 15 Sep 2021 16:10:12 +0100
branchjv
changeset 19607 f9108fde4972
parent 19606 77274bbcd92b
child 19608 98f7cba0ce8c
Move `CodeGenerator` and `CodeGeneratorTests` to namespace `Tools` ...to avoid name clashes.
ApplicationBuilder.st
CodeGenerator.st
CodeGeneratorTests.st
CodeGeneratorTool.st
ColorInspectorView.st
Make.proto
Make.spec
SmalltalkCodeGeneratorTool.st
SmalltalkInspectorView.st
Tools__BrowserList.st
Tools__CodeGenerator.st
Tools__CodeView2DemoApp.st
Tools__NavigationHistoryTests.st
abbrev.stc
bc.mak
libInit.cc
stx_libtool.st
tests/Make.proto
tests/Make.spec
tests/Tools__CodeGeneratorTests.st
tests/Tools__NavigationHistoryTests.st
tests/WorkspaceApplicationTests.st
tests/abbrev.stc
tests/bc.mak
tests/libInit.cc
tests/stx_libtool_tests.st
--- a/ApplicationBuilder.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/ApplicationBuilder.st	Wed Sep 15 16:10:12 2021 +0100
@@ -26,7 +26,7 @@
  The following class instance variables are inherited by this class:
 
 	ToolApplicationModel - history fileHistory clipboard settings showingHelp instances
-	ApplicationModel - ClassResources
+	ApplicationModel - ClassResources defaultKeyboardMap defaultStyleSheet
 	Model - 
 	Object - 
 "
--- a/CodeGenerator.st	Wed Sep 15 13:57:00 2021 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,255 +0,0 @@
-"
- Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
- Copyright (c) 2009-2010 eXept Software AG
-
- Permission is hereby granted, free of charge, to any person
- obtaining a copy of this software and associated documentation
- files (the 'Software'), to deal in the Software without
- restriction, including without limitation the rights to use,
- copy, modify, merge, publish, distribute, sublicense, and/or sell
- copies of the Software, and to permit persons to whom the
- Software is furnished to do so, subject to the following
- conditions:
-
- The above copyright notice and this permission notice shall be
- included in all copies or substantial portions of the Software.
-
- THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
- OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
- NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
- HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
- WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
- OTHER DEALINGS IN THE SOFTWARE.
-"
-"{ Package: 'stx:libtool' }"
-
-RBProgramNodeVisitor subclass:#CodeGenerator
-	instanceVariableNames:'class protocol source change replacements
-		recordedReplacementsInSource'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Browsers'
-!
-
-!CodeGenerator class methodsFor:'documentation'!
-
-copyright
-"
- Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
- Copyright (c) 2009-2010 eXept Software AG
-
- Permission is hereby granted, free of charge, to any person
- obtaining a copy of this software and associated documentation
- files (the 'Software'), to deal in the Software without
- restriction, including without limitation the rights to use,
- copy, modify, merge, publish, distribute, sublicense, and/or sell
- copies of the Software, and to permit persons to whom the
- Software is furnished to do so, subject to the following
- conditions:
-
- The above copyright notice and this permission notice shall be
- included in all copies or substantial portions of the Software.
-
- THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
- OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
- NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
- HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
- WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
- OTHER DEALINGS IN THE SOFTWARE.
-"
-! !
-
-!CodeGenerator methodsFor:'accessing'!
-
-category:aString
-
-    self protocol: aString
-
-    "Created: / 30-12-2008 / 17:41:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 18:46:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-change
-
-   change ifNil:[self createChange].
-   ^change
-
-    "Created: / 30-12-2008 / 17:14:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 18:45:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-class:aClass
-
-    class := aClass
-
-    "Created: / 30-12-2008 / 15:38:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 18:46:34 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-protocol
-    ^ protocol
-!
-
-protocol:aString
-    protocol := aString.
-!
-
-replace: placeholder with: code
-
-    replacements 
-        at: placeholder
-        put: (code isSymbol 
-                ifTrue:[code]
-                ifFalse:[RBParser parseRewriteExpression: code])
-
-    "Created: / 07-07-2009 / 18:48:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 19:58:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-replacementFor: placeholder
-
-    ^replacements 
-        at: placeholder
-        ifAbsent:[self error:'No replacement for ', placeholder]
-
-    "Created: / 07-07-2009 / 19:13:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-source:aString
-    source := aString.
-
-    "Created: / 30-12-2008 / 17:04:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!CodeGenerator methodsFor:'compiling'!
-
-compile
-
-    ^self change apply
-
-    "Created: / 07-07-2009 / 18:47:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!CodeGenerator methodsFor:'initialization'!
-
-initialize
-    "Invoked when a new instance is created."
-
-    super initialize.
-    replacements := Dictionary new.
-
-    "Created: / 30-12-2008 / 15:29:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 18:45:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!CodeGenerator methodsFor:'private'!
-
-createChange
-
-    | parser method |
-    parser := RBParser new.
-    recordedReplacementsInSource := OrderedCollection new.
-    parser errorBlock:[ :str :pos | self error: ('Error: %1: %2' bindWith: pos with: str). ^ self ].
-    parser initializeParserWith: source type: #rewriteSavingCommentsOn:errorBlock:.
-    method := parser parseMethod: source.    
-
-    method source: nil.
-    method acceptVisitor: self.
-    self replaceInSourceCode.
-    (change := InteractiveAddMethodChange new)
-        class: class
-        protocol: protocol
-        source: (source notNil ifTrue:[source] ifFalse:[method formattedCode]).
-
-    "Created: / 07-07-2009 / 18:44:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 26-08-2014 / 23:51:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-recordReplaceInSourceFrom:start to:stop by:code
-    recordedReplacementsInSource add: { start. stop . code }.
-
-    "Modified: / 26-08-2014 / 23:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-replaceInSourceCode
-    "Perform recorded replacements in source"
-
-    recordedReplacementsInSource sort: [ :a :b | a second < b first ].
-    recordedReplacementsInSource reverseDo:[ :replacement |
-        source := 
-            (source copyTo: replacement first - 1) , replacement third , (source copyFrom: replacement second + 1)  
-    ].
-
-    "Created: / 26-08-2014 / 23:51:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-replacePlaceholdersInSelectorPartsOf:aMessageNode 
-    aMessageNode selectorParts do:[:part | 
-        part isPatternVariable ifTrue:[
-            |replacement|
-
-            replacement := self replacementFor:part value.
-            (replacement isSymbol or:[ replacement isVariable ]) ifFalse:[
-                self error:'Replacement for selector parts must be a single selector'
-            ].
-            source notNil ifTrue:[
-                self 
-                      recordReplaceInSourceFrom:part start
-                      to:part stop
-                      by:replacement formattedCode.
-            ].
-            part value:replacement formattedCode.                 
-        ]
-    ]
-
-    "Modified: / 26-08-2014 / 23:37:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!CodeGenerator methodsFor:'visitor-double dispatching'!
-
-acceptMessageNode:aMessageNode 
-    self replacePlaceholdersInSelectorPartsOf:aMessageNode.
-    super acceptMessageNode:aMessageNode.
-
-    "Created: / 07-07-2009 / 19:23:08 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-acceptMethodNode: aMethodNode
-
-    self replacePlaceholdersInSelectorPartsOf: aMethodNode.
-    super acceptMethodNode: aMethodNode.
-
-    "Created: / 07-07-2009 / 19:09:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-acceptVariableNode: aVariableNode
-
-    aVariableNode isPatternNode ifTrue:[            
-        source notNil ifTrue:[ 
-            self 
-                  recordReplaceInSourceFrom:aVariableNode start
-                  to:aVariableNode stop
-                  by:(self replacementFor:aVariableNode name) formattedCode
-        ].
-        aVariableNode replaceWith: (self replacementFor:aVariableNode name).
-    ]
-
-    "Created: / 30-12-2008 / 17:13:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 07-07-2009 / 19:13:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 26-08-2014 / 23:37:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!CodeGenerator class methodsFor:'documentation'!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/CodeGenerator.st,v 1.4 2014-08-26 22:58:13 vrany Exp $'
-!
-
-version_SVN
-    ^ '$Id: CodeGenerator.st,v 1.4 2014-08-26 22:58:13 vrany Exp $'
-! !
-
--- a/CodeGeneratorTests.st	Wed Sep 15 13:57:00 2021 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,235 +0,0 @@
-"
- Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
- Copyright (c) 2009-2010 eXept Software AG
-
- Permission is hereby granted, free of charge, to any person
- obtaining a copy of this software and associated documentation
- files (the 'Software'), to deal in the Software without
- restriction, including without limitation the rights to use,
- copy, modify, merge, publish, distribute, sublicense, and/or sell
- copies of the Software, and to permit persons to whom the
- Software is furnished to do so, subject to the following
- conditions:
-
- The above copyright notice and this permission notice shall be
- included in all copies or substantial portions of the Software.
-
- THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
- OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
- NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
- HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
- WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
- OTHER DEALINGS IN THE SOFTWARE.
-"
-"{ Package: 'stx:libtool' }"
-
-"{ NameSpace: Smalltalk }"
-
-TestCase subclass:#CodeGeneratorTests
-	instanceVariableNames:'cg'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Browsers'
-!
-
-!CodeGeneratorTests class methodsFor:'documentation'!
-
-copyright
-"
- Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
- Copyright (c) 2009-2010 eXept Software AG
-
- Permission is hereby granted, free of charge, to any person
- obtaining a copy of this software and associated documentation
- files (the 'Software'), to deal in the Software without
- restriction, including without limitation the rights to use,
- copy, modify, merge, publish, distribute, sublicense, and/or sell
- copies of the Software, and to permit persons to whom the
- Software is furnished to do so, subject to the following
- conditions:
-
- The above copyright notice and this permission notice shall be
- included in all copies or substantial portions of the Software.
-
- THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
- EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
- OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
- NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
- HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
- WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
- OTHER DEALINGS IN THE SOFTWARE.
-"
-! !
-
-!CodeGeneratorTests methodsFor:'initialization & release'!
-
-setUp
-
-    cg := CodeGenerator new
-
-    "Created: / 07-07-2009 / 09:26:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-tearDown
-
-    | mocks |
-    mocks := Set new.
-    self class selectorsDo:
-        [:selector| 
-        (selector startsWith: 'mock')
-            ifTrue:[mocks add: selector]].
-    mocks do:
-        [:selector|
-        self class removeSelector: selector].
-
-    "Modified: / 07-07-2009 / 09:34:22 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!CodeGeneratorTests methodsFor:'mocks - do not remove'!
-
-mmock_03
-
-    ^3
-
-    "Created: / 07-07-2009 / 19:21:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-mmock_03: x
-
-    ^x
-
-    "Created: / 07-07-2009 / 19:55:10 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!CodeGeneratorTests methodsFor:'tests'!
-
-test_01
-
-    cg
-        class: self class;
-        replace: '`@e' with: '1';
-        source: 'mock_01 ^ `@e';
-        compile.
-
-    self assert: (self respondsTo: #mock_01).
-    self assert: (self mock_01 = 1).
-
-    "Created: / 07-07-2009 / 09:29:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_02
-
-    cg
-        class: self class;
-        replace: '`@selector' with: #mock_02;
-        source: '`@selector ^ 2';
-        compile.
-
-    self assert: (self respondsTo: #mock_02).
-    self assert: (self mock_02 = 2).
-
-    "Created: / 07-07-2009 / 19:07:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_02b
-
-    cg
-        class: self class;
-        replace: '`@selector:' with: #mock_02:;
-        source: '`@selector: arg ^ arg';
-        compile.
-
-    self assert: (self respondsTo: #mock_02:).
-    self assert: (self mock_02: 20) = 20.
-
-    "Created: / 07-07-2009 / 19:54:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_03
-
-    cg
-        class: self class;
-        replace: '`@selector' with: 'mmock_03';
-        source: 'mock_03 ^ self `@selector';
-        compile.
-
-    self assert: (self respondsTo: #mock_03).
-    self assert: (self mock_03 = 3).
-
-    "Created: / 07-07-2009 / 19:22:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_03b
-
-    cg
-        class: self class;
-        replace: '`@selector:' with: #mmock_03:;
-        source: 'mock_03b ^ self `@selector: 30';
-        compile.
-
-    self assert: (self respondsTo: #mock_03b).
-    self assert: (self mock_03b = 30).
-
-    "Created: / 07-07-2009 / 19:54:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_04a
-
-    cg
-        class: self class;
-        source: '`@selector ^ 4';
-        replace: '`@selector' with: #mock_04a;
-        compile.
-
-    self assert: (self respondsTo: #mock_04a).
-    self assert: (self mock_04a = 4).
-
-    "Created: / 24-04-2014 / 11:13:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-test_04b
-
-    cg
-        class: self class;
-        source: '`@selpart1 anArg `@selpart2 anArg2 ^ anArg + anArg2';
-        replace: '`@selpart1' with: #mock_04:;
-        replace: '`@selpart2' with: #b:;
-        compile.
-
-    self assert: (self respondsTo: #mock_04:b:).
-    self assert: ((self mock_04:123 b: 123) = (123+123)).
-
-    "Created: / 24-04-2014 / 11:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-test_05
-
-    cg
-        class: self class;
-        source: 'mock_05
-                "comment"
-
-                ^ 10';
-        compile.
-
-    self assert: (self respondsTo: #mock_05).
-    self assert: (self perform: #mock_05) == 10.
-    self assert: ((self class >> #mock_05) source includesString: 'comment')
-
-    "Created: / 24-04-2014 / 11:28:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 24-05-2014 / 01:02:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!CodeGeneratorTests class methodsFor:'documentation'!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/CodeGeneratorTests.st,v 1.5 2014-05-24 00:10:50 vrany Exp $'
-!
-
-version_SVN
-    ^ '$Id: CodeGeneratorTests.st,v 1.5 2014-05-24 00:10:50 vrany Exp $'
-! !
-
--- a/CodeGeneratorTool.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/CodeGeneratorTool.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1219,7 +1219,7 @@
 
     (visitedClass includesSelector:#acceptVisitor:forEffect:) ifFalse:
         [self addChange:
-            (CodeGenerator new
+            (Tools::CodeGenerator new
                 class: visitedClass;
                 protocol: 'visiting';
                 source: ('acceptVisitor: visitor forEffect: effect
@@ -1238,7 +1238,7 @@
 
     (visitorClass includesSelector:(sel, 'forEffect:') asSymbol) ifFalse:[
         self addChange:
-            (CodeGenerator new
+            (Tools::CodeGenerator new
                 class: visitorClass;
                 protocol: 'visiting';
                 source: ('`@sel: anObject forEffect: effect
@@ -1290,7 +1290,7 @@
 
     (visitorClass includesSelector:sel) ifFalse:[
         self addChange:
-            (CodeGenerator new
+            (Tools::CodeGenerator new
                 class: visitorClass;
                 protocol: 'visiting';
                 source: ('`@sel: anObject 
--- a/ColorInspectorView.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/ColorInspectorView.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
 	      All Rights Reserved
@@ -130,7 +128,7 @@
 !ColorInspectorView class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/ColorInspectorView.st,v 1.14 2011/07/05 12:04:32 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/ColorInspectorView.st,v 1.14 2011/07/05 12:04:32 cg Exp §'
 !
 
 version_HG
--- a/Make.proto	Wed Sep 15 13:57:00 2021 +0100
+++ b/Make.proto	Wed Sep 15 16:10:12 2021 +0100
@@ -168,7 +168,6 @@
 $(OUTDIR)ChangesBrowser.$(O) ChangesBrowser.$(C) ChangesBrowser.$(H): ChangesBrowser.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/StandardSystemView.$(H) $(INCLUDE_TOP)/stx/libview/TopView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(STCHDR)
 $(OUTDIR)CodeCompletionHelpMenuView.$(O) CodeCompletionHelpMenuView.$(C) CodeCompletionHelpMenuView.$(H): CodeCompletionHelpMenuView.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/PopUpView.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/TopView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libwidg/ListView.$(H) $(INCLUDE_TOP)/stx/libwidg/MenuView.$(H) $(INCLUDE_TOP)/stx/libwidg/SelectionInListView.$(H) $(STCHDR)
 $(OUTDIR)CodeCompletionHelpView.$(O) CodeCompletionHelpView.$(C) CodeCompletionHelpView.$(H): CodeCompletionHelpView.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) $(STCHDR)
-$(OUTDIR)CodeGenerator.$(O) CodeGenerator.$(C) CodeGenerator.$(H): CodeGenerator.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser/RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CodeGeneratorTool.$(O) CodeGeneratorTool.$(C) CodeGeneratorTool.$(H): CodeGeneratorTool.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)DebugView.$(O) DebugView.$(C) DebugView.$(H): DebugView.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/StandardSystemView.$(H) $(INCLUDE_TOP)/stx/libview/TopView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(STCHDR)
 $(OUTDIR)Diff.$(O) Diff.$(C) Diff.$(H): Diff.st $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -218,6 +217,7 @@
 $(OUTDIR)Tools__ClassSorter.$(O) Tools__ClassSorter.$(C) Tools__ClassSorter.$(H): Tools__ClassSorter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeCompletionMenu.$(O) Tools__CodeCompletionMenu.$(C) Tools__CodeCompletionMenu.$(H): Tools__CodeCompletionMenu.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) $(INCLUDE_TOP)/stx/libwidg2/SelectionInListModelView.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeCritics.$(O) Tools__CodeCritics.$(C) Tools__CodeCritics.$(H): Tools__CodeCritics.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)Tools__CodeGenerator.$(O) Tools__CodeGenerator.$(C) Tools__CodeGenerator.$(H): Tools__CodeGenerator.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser/RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeView2.$(O) Tools__CodeView2.$(C) Tools__CodeView2.$(H): Tools__CodeView2.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview/AbstractBackground.$(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/libwidg/CodeView.$(H) $(INCLUDE_TOP)/stx/libwidg/EditTextView.$(H) $(INCLUDE_TOP)/stx/libwidg/ListView.$(H) $(INCLUDE_TOP)/stx/libwidg/TextCollector.$(H) $(INCLUDE_TOP)/stx/libwidg/TextView.$(H) $(INCLUDE_TOP)/stx/libwidg/Workspace.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeViewService.$(O) Tools__CodeViewService.$(C) Tools__CodeViewService.$(H): Tools__CodeViewService.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__DiffCodeView2.$(O) Tools__DiffCodeView2.$(C) Tools__DiffCodeView2.$(H): Tools__DiffCodeView2.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) $(INCLUDE_TOP)/stx/libwidg2/TwoColumnTextView.$(H) $(STCHDR)
--- a/Make.spec	Wed Sep 15 13:57:00 2021 +0100
+++ b/Make.spec	Wed Sep 15 16:10:12 2021 +0100
@@ -67,7 +67,6 @@
 	ChangesBrowser \
 	CodeCompletionHelpMenuView \
 	CodeCompletionHelpView \
-	CodeGenerator \
 	CodeGeneratorTool \
 	DebugView \
 	Diff \
@@ -117,6 +116,7 @@
 	Tools::ClassSorter \
 	Tools::CodeCompletionMenu \
 	Tools::CodeCritics \
+	Tools::CodeGenerator \
 	Tools::CodeView2 \
 	Tools::CodeViewService \
 	Tools::DiffCodeView2 \
@@ -264,7 +264,6 @@
     $(OUTDIR)ChangesBrowser.$(O) \
     $(OUTDIR)CodeCompletionHelpMenuView.$(O) \
     $(OUTDIR)CodeCompletionHelpView.$(O) \
-    $(OUTDIR)CodeGenerator.$(O) \
     $(OUTDIR)CodeGeneratorTool.$(O) \
     $(OUTDIR)DebugView.$(O) \
     $(OUTDIR)Diff.$(O) \
@@ -314,6 +313,7 @@
     $(OUTDIR)Tools__ClassSorter.$(O) \
     $(OUTDIR)Tools__CodeCompletionMenu.$(O) \
     $(OUTDIR)Tools__CodeCritics.$(O) \
+    $(OUTDIR)Tools__CodeGenerator.$(O) \
     $(OUTDIR)Tools__CodeView2.$(O) \
     $(OUTDIR)Tools__CodeViewService.$(O) \
     $(OUTDIR)Tools__DiffCodeView2.$(O) \
--- a/SmalltalkCodeGeneratorTool.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/SmalltalkCodeGeneratorTool.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1304,7 +1304,7 @@
                     ifFalse:['self subclassResponsibility']).
     self createAcceptVisitorMethod:sel in:visitedClass withParameter: withParameter.
     (visitorClass includesSelector:sel) ifFalse:[
-        self addChange:((CodeGenerator new)
+        self addChange:((Tools::CodeGenerator new)
                     class:visitorClass;
                     protocol:'visiting';
                     source:template;
--- a/SmalltalkInspectorView.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/SmalltalkInspectorView.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -78,7 +76,7 @@
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/SmalltalkInspectorView.st,v 1.4 2010/03/03 11:16:38 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/SmalltalkInspectorView.st,v 1.4 2010/03/03 11:16:38 cg Exp §'
 !
 
 version_HG
--- a/Tools__BrowserList.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/Tools__BrowserList.st	Wed Sep 15 16:10:12 2021 +0100
@@ -2149,5 +2149,10 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Tools__CodeGenerator.st	Wed Sep 15 16:10:12 2021 +0100
@@ -0,0 +1,259 @@
+"
+ Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
+ Copyright (c) 2009-2010 eXept Software AG
+ Copyright (c) 2021 LabWare
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+"{ Package: 'stx:libtool' }"
+
+"{ NameSpace: Tools }"
+
+RBProgramNodeVisitor subclass:#CodeGenerator
+	instanceVariableNames:'class protocol source change replacements
+		recordedReplacementsInSource'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Browsers'
+!
+
+!CodeGenerator class methodsFor:'documentation'!
+
+copyright
+"
+ Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
+ Copyright (c) 2009-2010 eXept Software AG
+ Copyright (c) 2021 LabWare
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+! !
+
+!CodeGenerator methodsFor:'accessing'!
+
+category:aString
+
+    self protocol: aString
+
+    "Created: / 30-12-2008 / 17:41:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 18:46:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+change
+
+   change ifNil:[self createChange].
+   ^change
+
+    "Created: / 30-12-2008 / 17:14:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 18:45:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+class:aClass
+
+    class := aClass
+
+    "Created: / 30-12-2008 / 15:38:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 18:46:34 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+protocol
+    ^ protocol
+!
+
+protocol:aString
+    protocol := aString.
+!
+
+replace: placeholder with: code
+
+    replacements 
+        at: placeholder
+        put: (code isSymbol 
+                ifTrue:[code]
+                ifFalse:[RBParser parseRewriteExpression: code])
+
+    "Created: / 07-07-2009 / 18:48:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 19:58:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+replacementFor: placeholder
+
+    ^replacements 
+        at: placeholder
+        ifAbsent:[self error:'No replacement for ', placeholder]
+
+    "Created: / 07-07-2009 / 19:13:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+source:aString
+    source := aString.
+
+    "Created: / 30-12-2008 / 17:04:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!CodeGenerator methodsFor:'compiling'!
+
+compile
+
+    ^self change apply
+
+    "Created: / 07-07-2009 / 18:47:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!CodeGenerator methodsFor:'initialization'!
+
+initialize
+    "Invoked when a new instance is created."
+
+    super initialize.
+    replacements := Dictionary new.
+
+    "Created: / 30-12-2008 / 15:29:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 18:45:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!CodeGenerator methodsFor:'private'!
+
+createChange
+
+    | parser method |
+    parser := RBParser new.
+    recordedReplacementsInSource := OrderedCollection new.
+    parser errorBlock:[ :str :pos | self error: ('Error: %1: %2' bindWith: pos with: str). ^ self ].
+    parser initializeParserWith: source type: #rewriteSavingCommentsOn:errorBlock:.
+    method := parser parseMethod: source.    
+
+    method source: nil.
+    method acceptVisitor: self.
+    self replaceInSourceCode.
+    (change := InteractiveAddMethodChange new)
+        class: class
+        protocol: protocol
+        source: (source notNil ifTrue:[source] ifFalse:[method formattedCode]).
+
+    "Created: / 07-07-2009 / 18:44:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 26-08-2014 / 23:51:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+recordReplaceInSourceFrom:start to:stop by:code
+    recordedReplacementsInSource add: { start. stop . code }.
+
+    "Modified: / 26-08-2014 / 23:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+replaceInSourceCode
+    "Perform recorded replacements in source"
+
+    recordedReplacementsInSource sort: [ :a :b | a second < b first ].
+    recordedReplacementsInSource reverseDo:[ :replacement |
+        source := 
+            (source copyTo: replacement first - 1) , replacement third , (source copyFrom: replacement second + 1)  
+    ].
+
+    "Created: / 26-08-2014 / 23:51:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+replacePlaceholdersInSelectorPartsOf:aMessageNode 
+    aMessageNode selectorParts do:[:part | 
+        part isPatternVariable ifTrue:[
+            |replacement|
+
+            replacement := self replacementFor:part value.
+            (replacement isSymbol or:[ replacement isVariable ]) ifFalse:[
+                self error:'Replacement for selector parts must be a single selector'
+            ].
+            source notNil ifTrue:[
+                self 
+                      recordReplaceInSourceFrom:part start
+                      to:part stop
+                      by:replacement formattedCode.
+            ].
+            part value:replacement formattedCode.                 
+        ]
+    ]
+
+    "Modified: / 26-08-2014 / 23:37:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CodeGenerator methodsFor:'visitor-double dispatching'!
+
+acceptMessageNode:aMessageNode 
+    self replacePlaceholdersInSelectorPartsOf:aMessageNode.
+    super acceptMessageNode:aMessageNode.
+
+    "Created: / 07-07-2009 / 19:23:08 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+acceptMethodNode: aMethodNode
+
+    self replacePlaceholdersInSelectorPartsOf: aMethodNode.
+    super acceptMethodNode: aMethodNode.
+
+    "Created: / 07-07-2009 / 19:09:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+acceptVariableNode: aVariableNode
+
+    aVariableNode isPatternNode ifTrue:[            
+        source notNil ifTrue:[ 
+            self 
+                  recordReplaceInSourceFrom:aVariableNode start
+                  to:aVariableNode stop
+                  by:(self replacementFor:aVariableNode name) formattedCode
+        ].
+        aVariableNode replaceWith: (self replacementFor:aVariableNode name).
+    ]
+
+    "Created: / 30-12-2008 / 17:13:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 07-07-2009 / 19:13:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 26-08-2014 / 23:37:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CodeGenerator class methodsFor:'documentation'!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/CodeGenerator.st,v 1.4 2014-08-26 22:58:13 vrany Exp $'
+!
+
+version_SVN
+    ^ '$Id: CodeGenerator.st,v 1.4 2014-08-26 22:58:13 vrany Exp $'
+! !
+
--- a/Tools__CodeView2DemoApp.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/Tools__CodeView2DemoApp.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
               All Rights Reserved
@@ -149,7 +147,7 @@
 !CodeView2DemoApp class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeView2DemoApp.st,v 1.2 2011/07/03 17:50:09 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeView2DemoApp.st,v 1.2 2011/07/03 17:50:09 cg Exp §'
 !
 
 version_HG
--- a/Tools__NavigationHistoryTests.st	Wed Sep 15 13:57:00 2021 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,211 +0,0 @@
-"{ Encoding: utf8 }"
-
-"
- COPYRIGHT (c) 2006 by eXept Software AG
- COPYRIGHT (c) 2015 Jan Vrany
-              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:libtool' }"
-
-"{ NameSpace: Tools }"
-
-TestCase subclass:#NavigationHistoryTests
-	instanceVariableNames:'history'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Browsers-New-History'
-!
-
-!NavigationHistoryTests class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 2006 by eXept Software AG
- COPYRIGHT (c) 2015 Jan Vrany
-              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.
-"
-! !
-
-!NavigationHistoryTests methodsFor:'initialization'!
-
-setUp
-
-    history := NavigationHistory new
-
-    "Created: / 21-02-2008 / 16:52:19 / janfrog"
-! !
-
-!NavigationHistoryTests methodsFor:'tests'!
-
-test_01
-
-    self
-        assert: history canGoBack not;
-        assert: history canGoForward not
-
-    "Created: / 21-02-2008 / 16:54:55 / janfrog"
-!
-
-test_02
-
-    history goTo: 1.
-        
-    self
-        assert: history canGoBack not;
-        assert: history canGoForward not
-
-    "Created: / 21-02-2008 / 16:55:34 / janfrog"
-!
-
-test_03
-    history
-        goTo:1;
-        goTo:2;
-        goTo:3;
-        goBack.
-    self
-        assert:history currentItem = 2;
-        assert:history canGoBack;
-        assert:history goBackItems asArray = #( 1 );
-        assert:history canGoForward;
-        assert:history goForwardItems asArray = #( 3 ).
-
-    "Created: / 21-02-2008 / 16:57:29 / janfrog"
-    "Modified: / 27-02-2008 / 11:52:26 / janfrog"
-    "Modified: / 06-06-2008 / 09:31:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_04
-    history
-        goTo:1;
-        goTo:2;
-        goTo:3;
-        goTo:2.
-    self
-        assert:history currentItem = 2;
-        assert:history canGoBack;
-        assert:history goBackItems asArray = #( 3 2 1);
-        assert:history canGoForward not;
-        assert:history goForwardItems asArray = #( ).
-
-    "Created: / 21-02-2008 / 16:57:58 / janfrog"
-    "Modified: / 27-02-2008 / 11:52:26 / janfrog"
-    "Modified: / 06-06-2008 / 09:31:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 04-09-2015 / 06:56:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-test_05
-    history
-        goTo:1;
-        goTo:2;
-        goTo:3;
-        goBack;
-        goBack;
-        goTo:5.
-    self
-        assert:history currentItem = 5;
-        assert:history canGoBack;
-        assert:history goBackItems asArray = #( 1 );
-        assert:history canGoForward not.
-
-    "Created: / 21-02-2008 / 16:59:11 / janfrog"
-    "Modified: / 27-02-2008 / 11:52:12 / janfrog"
-    "Modified: / 06-06-2008 / 09:31:40 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-test_06
-    history goTo:1.
-    self assert: history currentItem = 1.
-    self assert: history canGoBack not.
-    self assert: history goBackItems asArray = #( ).
-    self assert: history canGoForward not.
-    self assert: history goForwardItems asArray = #( ).
-
-    history goTo:2.
-    self assert: history currentItem = 2.
-    self assert: history canGoBack .
-    self assert: history goBackItems asArray = #( 1 ).
-    self assert: history canGoForward not.
-    self assert: history goForwardItems asArray = #( ).
-
-    history goTo:3.
-    self assert: history currentItem = 3.
-    self assert: history canGoBack .
-    self assert: history goBackItems asArray = #( 2 1 ).
-    self assert: history canGoForward not.
-    self assert: history goForwardItems asArray = #( ).
-
-    history goTo:2.
-    self assert: history currentItem = 2.
-    self assert: history canGoBack .
-    self assert: history goBackItems asArray = #( 3 2 1 ).
-    self assert: history canGoForward not.
-    self assert: history goForwardItems asArray = #( ).
-
-    history goBack.
-    self assert: history currentItem = 3.
-    self assert: history canGoBack .
-    self assert: history goBackItems asArray = #( 2 1 ).
-    self assert: history canGoForward.
-    self assert: history goForwardItems asArray = #( 2 ).
-
-    history goBack.
-    self assert: history currentItem = 2.
-    self assert: history canGoBack .
-    self assert: history goBackItems asArray = #( 1 ).
-    self assert: history canGoForward.
-    self assert: history goForwardItems asArray = #( 3 2 ).   
-
-    history goBack.
-    self assert: history currentItem = 1.
-    self assert: history canGoBack not.
-    self assert: history goBackItems asArray = #( ).
-    self assert: history canGoForward.
-    self assert: history goForwardItems asArray = #( 2 3 2 ).   
-
-    history goForward.
-    self assert: history currentItem = 2.
-    self assert: history canGoBack.
-    self assert: history goBackItems asArray = #( 1 ).
-    self assert: history canGoForward.
-    self assert: history goForwardItems asArray = #( 3 2 ).   
-
-    history goForward.
-    self assert: history currentItem = 3.
-    self assert: history canGoBack.
-    self assert: history goBackItems asArray = #( 2 1 ).
-    self assert: history canGoForward.
-    self assert: history goForwardItems asArray = #( 2 ).
-
-    "Created: / 04-09-2015 / 06:59:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!NavigationHistoryTests class methodsFor:'documentation'!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__NavigationHistoryTests.st,v 1.2 2012-09-02 11:21:14 cg Exp $'
-!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-!
-
-version_SVN
-    ^ '§Id: Tools__NavigationHistoryTests.st 7486 2009-10-26 22:06:24Z vranyj1 §'
-! !
-
--- a/abbrev.stc	Wed Sep 15 13:57:00 2021 +0100
+++ b/abbrev.stc	Wed Sep 15 16:10:12 2021 +0100
@@ -2,22 +2,22 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 AboutBox AboutBox stx:libtool 'Views-DialogBoxes' 2
-AbstractFileApplicationNoteBookComponent AbstractFileApplicationNoteBookComponent stx:libtool 'Interface-Tools-File' 2
-AbstractFileBrowser AbstractFileBrowser stx:libtool 'Interface-Tools-File' 4
-AbstractLauncherApplication AbstractLauncherApplication stx:libtool 'Interface-Smalltalk' 8
-AbstractSettingsApplication AbstractSettingsApplication stx:libtool 'Interface-Smalltalk' 2
+AbstractFileApplicationNoteBookComponent AbstractFileApplicationNoteBookComponent stx:libtool 'Interface-Tools-File' 3
+AbstractFileBrowser AbstractFileBrowser stx:libtool 'Interface-Tools-File' 5
+AbstractLauncherApplication AbstractLauncherApplication stx:libtool 'Interface-Smalltalk' 9
+AbstractSettingsApplication AbstractSettingsApplication stx:libtool 'Interface-Smalltalk' 3
 Bookmark Bookmark stx:libtool 'Interface-Bookmarks' 0
-BookmarkBar BookmarkBar stx:libtool 'Interface-Bookmarks' 2
-BookmarkEditor BookmarkEditor stx:libtool 'Interface-Bookmarks' 2
+BookmarkBar BookmarkBar stx:libtool 'Interface-Bookmarks' 3
+BookmarkEditor BookmarkEditor stx:libtool 'Interface-Bookmarks' 3
 BookmarkList BookmarkList stx:libtool 'Interface-Bookmarks' 0
-BookmarkListEditor BookmarkListEditor stx:libtool 'Interface-Bookmarks' 2
+BookmarkListEditor BookmarkListEditor stx:libtool 'Interface-Bookmarks' 3
 BookmarkVisitor BookmarkVisitor stx:libtool 'Interface-Bookmarks' 0
-BookmarksEditDialog BookmarksEditDialog stx:libtool 'Interface-Tools-File' 2
+BookmarksEditDialog BookmarksEditDialog stx:libtool 'Interface-Tools-File' 3
 BrowserView BrowserView stx:libtool 'Interface-Browsers' 2
 ChangesBrowser ChangesBrowser stx:libtool 'Interface-Browsers' 2
 CodeCompletionHelpMenuView CodeCompletionHelpMenuView stx:libtool 'Interface-Help' 2
 CodeCompletionHelpView CodeCompletionHelpView stx:libtool 'Interface-Help' 2
-CodeGenerator CodeGenerator stx:libtool 'Interface-Browsers' 0
+Tools::CodeGenerator Tools__CodeGenerator stx:libtool 'Interface-Browsers' 0
 CodeGeneratorTool CodeGeneratorTool stx:libtool 'Interface-Browsers' 0
 DebugView DebugView stx:libtool 'Interface-Debugger' 3
 Diff Diff stx:libtool 'Collections-Support' 0
@@ -31,38 +31,38 @@
 DisplayObjectView DisplayObjectView stx:libtool 'Views-Misc' 2
 EditFieldWithCompletion EditFieldWithCompletion stx:libtool 'Views-Text' 2
 EditFieldWithCompletionSpec EditFieldWithCompletionSpec stx:libtool 'Interface-Support-UI-Specs' 0
-EventMonitor EventMonitor stx:libtool 'Monitors-ST/X' 2
+EventMonitor EventMonitor stx:libtool 'Monitors-ST/X' 3
 FileBrowser FileBrowser stx:libtool 'Interface-Tools-File' 2
 FileBrowserV2PanelView FileBrowserV2PanelView stx:libtool 'Interface-Tools-File' 2
-FileBrowserV2SettingsDialog FileBrowserV2SettingsDialog stx:libtool 'Interface-Tools-File' 2
+FileBrowserV2SettingsDialog FileBrowserV2SettingsDialog stx:libtool 'Interface-Tools-File' 3
 FileBrowserV2UISpecifications FileBrowserV2UISpecifications stx:libtool 'Interface-Tools-File' 0
-FileDialog FileDialog stx:libtool 'Interface-Tools-File' 2
+FileDialog FileDialog stx:libtool 'Interface-Tools-File' 3
 FileOperation FileOperation stx:libtool 'Interface-Support' 0
 FilenameEditFieldV2 FilenameEditFieldV2 stx:libtool 'Interface-Tools-File' 2
 InspectorView InspectorView stx:libtool 'Interface-Inspector' 2
-MemoryMonitor MemoryMonitor stx:libtool 'Monitors-ST/X' 2
+MemoryMonitor MemoryMonitor stx:libtool 'Monitors-ST/X' 3
 MemoryMonitorView MemoryMonitorView stx:libtool 'Monitors-ST/X' 2
 MemoryUsageView MemoryUsageView stx:libtool 'Monitors-ST/X' 2
-MultiViewToolApplication MultiViewToolApplication stx:libtool 'Interface-Smalltalk' 8
+MultiViewToolApplication MultiViewToolApplication stx:libtool 'Interface-Smalltalk' 9
 PerforceSourceCodeManagerUtilities PerforceSourceCodeManagerUtilities stx:libtool 'System-SourceCodeManagement' 0
-ProcessMonitorV2 ProcessMonitorV2 stx:libtool 'Monitors-ST/X' 2
+ProcessMonitorV2 ProcessMonitorV2 stx:libtool 'Monitors-ST/X' 3
 RCSConflictEditTextView RCSConflictEditTextView stx:libtool 'Views-Text' 2
 Solarized Solarized stx:libtool 'Views-Text-Theme' 0
 SyntaxElement SyntaxElement stx:libtool 'Interface-CodeView-Syntax' 0
 SyntaxHighlighter2 SyntaxHighlighter2 stx:libtool 'Interface-CodeView-Syntax' 3
-SystemBrowser SystemBrowser stx:libtool 'Interface-Browsers' 2
+SystemBrowser SystemBrowser stx:libtool 'Interface-Browsers' 3
 SystemStatusMonitor SystemStatusMonitor stx:libtool 'Monitors-ST/X' 2
-Tools::AbstractTestRunner Tools__AbstractTestRunner stx:libtool 'SUnit-UI' 2
-Tools::BreakpointBrowser Tools__BreakpointBrowser stx:libtool 'Interface-Debugger' 2
-Tools::Browslet Tools__Browslet stx:libtool 'Interface-Browsers-Browslets' 2
-Tools::BrowsletCanvas Tools__BrowsletCanvas stx:libtool 'Interface-Browsers-Browslets' 2
+Tools::AbstractTestRunner Tools__AbstractTestRunner stx:libtool 'SUnit-UI' 3
+Tools::BreakpointBrowser Tools__BreakpointBrowser stx:libtool 'Interface-Debugger' 3
+Tools::Browslet Tools__Browslet stx:libtool 'Interface-Browsers-Browslets' 3
+Tools::BrowsletCanvas Tools__BrowsletCanvas stx:libtool 'Interface-Browsers-Browslets' 3
 Tools::CachedTags Tools__CachedTags stx:libtool 'Interface-Tools-File-Tags' 0
-Tools::ChangeSetBrowser2 Tools__ChangeSetBrowser2 stx:libtool 'Interface-Browsers-ChangeSet' 8
+Tools::ChangeSetBrowser2 Tools__ChangeSetBrowser2 stx:libtool 'Interface-Browsers-ChangeSet' 9
 Tools::ChangeSetDiffInfo Tools__ChangeSetDiffInfo stx:libtool 'Interface-Diff' 0
-Tools::ChangeSetDiffTool Tools__ChangeSetDiffTool stx:libtool 'Interface-Diff' 2
-Tools::ChangeSetSelectionDialog Tools__ChangeSetSelectionDialog stx:libtool 'Interface-Dialogs' 2
+Tools::ChangeSetDiffTool Tools__ChangeSetDiffTool stx:libtool 'Interface-Diff' 3
+Tools::ChangeSetSelectionDialog Tools__ChangeSetSelectionDialog stx:libtool 'Interface-Dialogs' 3
 Tools::ChangeSetSpec Tools__ChangeSetSpec stx:libtool 'Interface-Dialogs' 0
-Tools::CheckinInfoDialog Tools__CheckinInfoDialog stx:libtool 'System-SourceCodeManagement' 2
+Tools::CheckinInfoDialog Tools__CheckinInfoDialog stx:libtool 'System-SourceCodeManagement' 3
 Tools::ClassChecker Tools__ClassChecker stx:libtool 'Interface-Browsers-New' 0
 Tools::ClassSorter Tools__ClassSorter stx:libtool 'Interface-Browsers-New' 0
 Tools::CodeCompletionMenu Tools__CodeCompletionMenu stx:libtool 'Interface-CodeView' 2
@@ -70,45 +70,45 @@
 Tools::CodeView2 Tools__CodeView2 stx:libtool 'Interface-CodeView' 2
 Tools::CodeViewService Tools__CodeViewService stx:libtool 'Interface-CodeView' 0
 Tools::DiffCodeView2 Tools__DiffCodeView2 stx:libtool 'Interface-CodeView' 2
-Tools::HierarchicalChangesetDialog Tools__HierarchicalChangesetDialog stx:libtool 'Interface-Dialogs' 2
-Tools::InlineMessageDialog Tools__InlineMessageDialog stx:libtool 'Interface-Tools' 2
-Tools::Inspector2 Tools__Inspector2 stx:libtool 'Interface-Inspector2' 2
+Tools::HierarchicalChangesetDialog Tools__HierarchicalChangesetDialog stx:libtool 'Interface-Dialogs' 3
+Tools::InlineMessageDialog Tools__InlineMessageDialog stx:libtool 'Interface-Tools' 3
+Tools::Inspector2 Tools__Inspector2 stx:libtool 'Interface-Inspector2' 3
 Tools::Inspector2Tab Tools__Inspector2Tab stx:libtool 'Interface-Inspector2' 0
 Tools::LintAnnotation Tools__LintAnnotation stx:libtool 'Interface-Lint' 0
 Tools::LintHighlighter Tools__LintHighlighter stx:libtool 'Interface-Lint' 0
-Tools::LintRuleDetail Tools__LintRuleDetail stx:libtool 'Interface-Lint' 2
-Tools::LintRuleEditDialog Tools__LintRuleEditDialog stx:libtool 'Interface-Lint' 2
-Tools::LintRuleSelectionDialog Tools__LintRuleSelectionDialog stx:libtool 'Interface-Lint' 2
+Tools::LintRuleDetail Tools__LintRuleDetail stx:libtool 'Interface-Lint' 3
+Tools::LintRuleEditDialog Tools__LintRuleEditDialog stx:libtool 'Interface-Lint' 3
+Tools::LintRuleSelectionDialog Tools__LintRuleSelectionDialog stx:libtool 'Interface-Lint' 3
 Tools::MethodCategoryCache Tools__MethodCategoryCache stx:libtool 'Interface-Browsers-New' 0
-Tools::MethodRewriter Tools__MethodRewriter stx:libtool 'Interface-Tools' 2
+Tools::MethodRewriter Tools__MethodRewriter stx:libtool 'Interface-Tools' 3
 Tools::NavigationHistory Tools__NavigationHistory stx:libtool 'Interface-Browsers-New-History' 0
 Tools::NavigationState Tools__NavigationState stx:libtool 'Interface-Browsers-New' 0
-Tools::NavigatorModel Tools__NavigatorModel stx:libtool 'Interface-Browsers-New' 2
-Tools::NewClassWizardDialog Tools__NewClassWizardDialog stx:libtool 'Interface-Browsers-New' 2
+Tools::NavigatorModel Tools__NavigatorModel stx:libtool 'Interface-Browsers-New' 3
+Tools::NewClassWizardDialog Tools__NewClassWizardDialog stx:libtool 'Interface-Browsers-New' 3
 Tools::NewSystemBrowserCodeView Tools__NewSystemBrowserCodeView stx:libtool 'Interface-Browsers-New' 2
 Tools::Profiler Tools__Profiler stx:libtool 'Interface-Browsers-New-Profiler' 0
 Tools::ProfilerInfoBuilder Tools__ProfilerInfoBuilder stx:libtool 'Interface-Browsers-New-Profiler' 0
 Tools::ProfilerInfoItem Tools__ProfilerInfoItem stx:libtool 'Interface-Browsers-New-Profiler' 0
-Tools::ProjectCheckerBrowser Tools__ProjectCheckerBrowser stx:libtool 'System-Support-Projects' 2
-Tools::ProjectLoader Tools__ProjectLoader stx:libtool 'Interface-Tools' 2
+Tools::ProjectCheckerBrowser Tools__ProjectCheckerBrowser stx:libtool 'System-Support-Projects' 3
+Tools::ProjectLoader Tools__ProjectLoader stx:libtool 'Interface-Tools' 3
 Tools::SearchDialog Tools__SearchDialog stx:libtool 'Interface-Browsers-New' 2
-Tools::SmalltalkDiffTool Tools__SmalltalkDiffTool stx:libtool 'Interface-Diff & Merge tool' 2
-Tools::SourceCodeManagerConfigurationTestTool Tools__SourceCodeManagerConfigurationTestTool stx:libtool 'System-SourceCodeManagement' 2
-Tools::SpecialCodeView Tools__SpecialCodeView stx:libtool 'Interface-Browsers-New' 2
-Tools::StringSearchTool Tools__StringSearchTool stx:libtool 'Interface-Tools' 2
+Tools::SmalltalkDiffTool Tools__SmalltalkDiffTool stx:libtool 'Interface-Diff & Merge tool' 3
+Tools::SourceCodeManagerConfigurationTestTool Tools__SourceCodeManagerConfigurationTestTool stx:libtool 'System-SourceCodeManagement' 3
+Tools::SpecialCodeView Tools__SpecialCodeView stx:libtool 'Interface-Browsers-New' 3
+Tools::StringSearchTool Tools__StringSearchTool stx:libtool 'Interface-Tools' 3
 Tools::Tag Tools__Tag stx:libtool 'Interface-Tools-File-Tags' 0
 Tools::TagList Tools__TagList stx:libtool 'Interface-Tools-File-Tags' 0
-Tools::TagsBrowser Tools__TagsBrowser stx:libtool 'Interface-Tools-File-Tags' 2
-Tools::TextDiffTool Tools__TextDiffTool stx:libtool 'Interface-Diff' 2
+Tools::TagsBrowser Tools__TagsBrowser stx:libtool 'Interface-Tools-File-Tags' 3
+Tools::TextDiffTool Tools__TextDiffTool stx:libtool 'Interface-Diff' 3
 Tools::TextMergeInfo Tools__TextMergeInfo stx:libtool 'Interface-Diff' 0
 Tools::Toolbox Tools__Toolbox stx:libtool 'Interface-Tools' 0
-Tools::WebBrowserPage Tools__WebBrowserPage stx:libtool 'Interface-Browsers-Web' 2
-VersionDiffBrowser VersionDiffBrowser stx:libtool 'Interface-Browsers' 2
+Tools::WebBrowserPage Tools__WebBrowserPage stx:libtool 'Interface-Browsers-Web' 3
+VersionDiffBrowser VersionDiffBrowser stx:libtool 'Interface-Browsers' 3
 ViewWithAcceptAndCancelBar ViewWithAcceptAndCancelBar stx:libtool 'Views-Basic' 2
 stx_libtool stx_libtool stx:libtool '* Projects & Packages *' 3
-AbstractDirectoryBrowser AbstractDirectoryBrowser stx:libtool 'Interface-Tools-File' 4
-AbstractFileFinderApplicationComponent AbstractFileFinderApplicationComponent stx:libtool 'Interface-Tools-File' 2
-AbstractSourceCodeManagementSettingsAppl AbstractSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
+AbstractDirectoryBrowser AbstractDirectoryBrowser stx:libtool 'Interface-Tools-File' 5
+AbstractFileFinderApplicationComponent AbstractFileFinderApplicationComponent stx:libtool 'Interface-Tools-File' 3
+AbstractSourceCodeManagementSettingsAppl AbstractSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
 BookmarkMenuBuilder BookmarkMenuBuilder stx:libtool 'Interface-Bookmarks' 0
 ChangeSetBrowser ChangeSetBrowser stx:libtool 'Interface-Browsers' 2
 ClassInspectorView ClassInspectorView stx:libtool 'Interface-Inspector' 2
@@ -117,102 +117,101 @@
 Diff3ExclusiveVisitor Diff3ExclusiveVisitor stx:libtool 'Collections-Sequenceable-Diff' 0
 DiffCodeView DiffCodeView stx:libtool 'Views-Text' 2
 ExternalStreamMonitor ExternalStreamMonitor stx:libtool 'Monitors-ST/X' 2
-FileApplicationNoteBook FileApplicationNoteBook stx:libtool 'Interface-Tools-File' 4
-FileBrowserV2 FileBrowserV2 stx:libtool 'Interface-Tools-File' 4
-FileBrowserV2SettingsAppl FileBrowserV2SettingsAppl stx:libtool 'Interface-Tools-File' 2
-FileDialogWithPreview FileDialogWithPreview stx:libtool 'Interface-Tools-File' 2
+FileApplicationNoteBook FileApplicationNoteBook stx:libtool 'Interface-Tools-File' 5
+FileBrowserV2 FileBrowserV2 stx:libtool 'Interface-Tools-File' 5
+FileBrowserV2SettingsAppl FileBrowserV2SettingsAppl stx:libtool 'Interface-Tools-File' 3
+FileDialogWithPreview FileDialogWithPreview stx:libtool 'Interface-Tools-File' 3
 ImageInspectorView ImageInspectorView stx:libtool 'Interface-Inspector' 2
-NewLauncher NewLauncher stx:libtool 'Interface-Smalltalk' 8
+NewLauncher NewLauncher stx:libtool 'Interface-Smalltalk' 9
 OrderedCollectionInspectorView OrderedCollectionInspectorView stx:libtool 'Interface-Inspector' 2
 ParseTreeIndex ParseTreeIndex stx:libtool 'Interface-CodeView-Syntax' 0
 SetInspectorView SetInspectorView stx:libtool 'Interface-Inspector' 2
-SettingsDialog SettingsDialog stx:libtool 'Interface-Smalltalk' 2
+SettingsDialog SettingsDialog stx:libtool 'Interface-Smalltalk' 3
 SmalltalkCodeGeneratorTool SmalltalkCodeGeneratorTool stx:libtool 'Interface-Browsers' 0
 SolarizedDark SolarizedDark stx:libtool 'Views-Text-Theme' 0
 SyntaxElementVariable SyntaxElementVariable stx:libtool 'Interface-CodeView-Syntax' 0
-TerminalApplication TerminalApplication stx:libtool 'Interface-Smalltalk' 8
+TerminalApplication TerminalApplication stx:libtool 'Interface-Smalltalk' 9
 Tools::BackgroundSourceProcessingService Tools__BackgroundSourceProcessingService stx:libtool 'Interface-CodeView' 0
 Tools::BreakpointService Tools__BreakpointService stx:libtool 'Interface-CodeView' 0
-Tools::BrowserList Tools__BrowserList stx:libtool 'Interface-Browsers-New' 2
+Tools::BrowserList Tools__BrowserList stx:libtool 'Interface-Browsers-New' 3
 Tools::CodeCompletionService Tools__CodeCompletionService stx:libtool 'Interface-CodeView' 0
 Tools::CodeNavigationService Tools__CodeNavigationService stx:libtool 'Interface-CodeView' 0
-Tools::CodeView2SettingsAppl Tools__CodeView2SettingsAppl stx:libtool 'Interface-CodeView' 2
+Tools::CodeView2SettingsAppl Tools__CodeView2SettingsAppl stx:libtool 'Interface-CodeView' 3
 Tools::Diff2CodeView2 Tools__Diff2CodeView2 stx:libtool 'Interface-CodeView' 2
 Tools::Diff3CodeView2 Tools__Diff3CodeView2 stx:libtool 'Interface-CodeView' 2
-Tools::FontSettingsApplication Tools__FontSettingsApplication stx:libtool 'Interface-Smalltalk' 2
+Tools::FontSettingsApplication Tools__FontSettingsApplication stx:libtool 'Interface-Smalltalk' 3
 Tools::GenericToolbox Tools__GenericToolbox stx:libtool 'Interface-Tools' 0
-Tools::LintRuleSettingsApplication Tools__LintRuleSettingsApplication stx:libtool 'Interface-Lint' 2
+Tools::LintRuleSettingsApplication Tools__LintRuleSettingsApplication stx:libtool 'Interface-Lint' 3
 Tools::LintService Tools__LintService stx:libtool 'Interface-Lint' 0
-Tools::NavigatorCanvas Tools__NavigatorCanvas stx:libtool 'Interface-Browsers-New' 2
-Tools::NewSystemBrowser Tools__NewSystemBrowser stx:libtool 'Interface-Browsers-New' 2
-Tools::OrganizerCanvas Tools__OrganizerCanvas stx:libtool 'Interface-Browsers-New' 2
-Tools::SendersBrowslet Tools__SendersBrowslet stx:libtool 'Interface-Browsers-Browslets' 2
-Tools::StringSearchToolForTextView Tools__StringSearchToolForTextView stx:libtool 'Interface-Tools' 2
-Tools::TestRunnerMini Tools__TestRunnerMini stx:libtool 'SUnit-UI' 2
-Tools::TextDiff2Tool Tools__TextDiff2Tool stx:libtool 'Interface-Diff' 2
-Tools::TextDiff3Tool Tools__TextDiff3Tool stx:libtool 'Interface-Diff' 2
-Tools::VisualProfilerCanvas Tools__VisualProfilerCanvas stx:libtool 'Interface-Browsers-New-Profiler' 2
-WorkspaceApplication WorkspaceApplication stx:libtool 'Interface-Smalltalk' 8
+Tools::NavigatorCanvas Tools__NavigatorCanvas stx:libtool 'Interface-Browsers-New' 3
+Tools::NewSystemBrowser Tools__NewSystemBrowser stx:libtool 'Interface-Browsers-New' 3
+Tools::OrganizerCanvas Tools__OrganizerCanvas stx:libtool 'Interface-Browsers-New' 3
+Tools::SendersBrowslet Tools__SendersBrowslet stx:libtool 'Interface-Browsers-Browslets' 3
+Tools::StringSearchToolForTextView Tools__StringSearchToolForTextView stx:libtool 'Interface-Tools' 3
+Tools::TestRunnerMini Tools__TestRunnerMini stx:libtool 'SUnit-UI' 3
+Tools::TextDiff2Tool Tools__TextDiff2Tool stx:libtool 'Interface-Diff' 3
+Tools::TextDiff3Tool Tools__TextDiff3Tool stx:libtool 'Interface-Diff' 3
+Tools::VisualProfilerCanvas Tools__VisualProfilerCanvas stx:libtool 'Interface-Browsers-New-Profiler' 3
+WorkspaceApplication WorkspaceApplication stx:libtool 'Interface-Smalltalk' 9
 BookmarkAddMenuBuilder BookmarkAddMenuBuilder stx:libtool 'Interface-Bookmarks' 0
 BookmarkToolbarMenuBuilder BookmarkToolbarMenuBuilder stx:libtool 'Interface-Bookmarks' 0
-CVSSourceCodeManagementSettingsAppl CVSSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-DataBaseSourceCodeManagementSettingsAppl DataBaseSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-DirectoryContentsBrowser DirectoryContentsBrowser stx:libtool 'Interface-Tools-File' 4
-DirectoryDifferenceViewApplication DirectoryDifferenceViewApplication stx:libtool 'Interface-Tools-File' 2
-DirectoryTreeBrowser DirectoryTreeBrowser stx:libtool 'Interface-Tools-File' 4
-FileBasedSourceCodeManagementSettingsAppl FileBasedSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-FindFileApplication FindFileApplication stx:libtool 'Interface-Tools-File' 2
-GitSourceCodeManagementSettingsAppl GitSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-MercurialSourceCodeManagementSettingsAppl MercurialSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-PerforceSourceCodeManagementSettingsAppl PerforceSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-StoreSourceCodeManagementSettingsAppl StoreSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 2
-Tools::BrowserListWithFilter Tools__BrowserListWithFilter stx:libtool 'Interface-Browsers-New' 2
-Tools::ClassCategoryList Tools__ClassCategoryList stx:libtool 'Interface-Browsers-New' 2
-Tools::ClassGeneratorList Tools__ClassGeneratorList stx:libtool 'Interface-Browsers-New' 2
-Tools::ClassList Tools__ClassList stx:libtool 'Interface-Browsers-New' 2
+CVSSourceCodeManagementSettingsAppl CVSSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+DataBaseSourceCodeManagementSettingsAppl DataBaseSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+DirectoryContentsBrowser DirectoryContentsBrowser stx:libtool 'Interface-Tools-File' 5
+DirectoryDifferenceViewApplication DirectoryDifferenceViewApplication stx:libtool 'Interface-Tools-File' 3
+DirectoryTreeBrowser DirectoryTreeBrowser stx:libtool 'Interface-Tools-File' 5
+FileBasedSourceCodeManagementSettingsAppl FileBasedSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+FindFileApplication FindFileApplication stx:libtool 'Interface-Tools-File' 3
+GitSourceCodeManagementSettingsAppl GitSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+MercurialSourceCodeManagementSettingsAppl MercurialSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+PerforceSourceCodeManagementSettingsAppl PerforceSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+StoreSourceCodeManagementSettingsAppl StoreSourceCodeManagementSettingsAppl stx:libtool 'System-SourceCodeManagement' 3
+Tools::BrowserListWithFilter Tools__BrowserListWithFilter stx:libtool 'Interface-Browsers-New' 3
+Tools::ClassCategoryList Tools__ClassCategoryList stx:libtool 'Interface-Browsers-New' 3
+Tools::ClassGeneratorList Tools__ClassGeneratorList stx:libtool 'Interface-Browsers-New' 3
+Tools::ClassList Tools__ClassList stx:libtool 'Interface-Browsers-New' 3
 Tools::CodeHighlightingService Tools__CodeHighlightingService stx:libtool 'Interface-CodeView' 0
-Tools::LintRuleList Tools__LintRuleList stx:libtool 'Interface-Lint' 2
-Tools::MethodCategoryList Tools__MethodCategoryList stx:libtool 'Interface-Browsers-New' 2
-Tools::MethodList Tools__MethodList stx:libtool 'Interface-Browsers-New' 2
-Tools::NamespaceList Tools__NamespaceList stx:libtool 'Interface-Browsers-New' 2
-Tools::ProjectList Tools__ProjectList stx:libtool 'Interface-Browsers-New' 2
+Tools::LintRuleList Tools__LintRuleList stx:libtool 'Interface-Lint' 3
+Tools::MethodCategoryList Tools__MethodCategoryList stx:libtool 'Interface-Browsers-New' 3
+Tools::MethodList Tools__MethodList stx:libtool 'Interface-Browsers-New' 3
+Tools::NamespaceList Tools__NamespaceList stx:libtool 'Interface-Browsers-New' 3
+Tools::ProjectList Tools__ProjectList stx:libtool 'Interface-Browsers-New' 3
 Tools::SmalltalkToolbox Tools__SmalltalkToolbox stx:libtool 'Interface-Tools' 0
-Tools::TestRunnerEmbedded Tools__TestRunnerEmbedded stx:libtool 'SUnit-UI' 2
-Tools::VariableList Tools__VariableList stx:libtool 'Interface-Browsers-New' 2
-Tools::ChangeList Tools__ChangeList stx:libtool 'Interface-Browsers-ChangeSet' 2
-Tools::ChangeSetDiffList Tools__ChangeSetDiffList stx:libtool 'Interface-Diff' 2
-Tools::FullMethodCategoryList Tools__FullMethodCategoryList stx:libtool 'Interface-Browsers-New' 2
-Tools::HierarchicalClassCategoryList Tools__HierarchicalClassCategoryList stx:libtool 'Interface-Browsers-New' 2
-Tools::HierarchicalClassList Tools__HierarchicalClassList stx:libtool 'Interface-Browsers-New' 2
-Tools::HierarchicalLintRuleList Tools__HierarchicalLintRuleList stx:libtool 'Interface-Lint' 2
-Tools::HierarchicalProjectList Tools__HierarchicalProjectList stx:libtool 'Interface-Browsers-New' 2
-Tools::ImplementingClassList Tools__ImplementingClassList stx:libtool 'Interface-Browsers-New' 2
-Tools::ImplementingMethodList Tools__ImplementingMethodList stx:libtool 'Interface-Browsers-New' 2
-Tools::NamespaceFilter Tools__NamespaceFilter stx:libtool 'Interface-Browsers-New' 2
-Tools::TestRunner2 Tools__TestRunner2 stx:libtool 'SUnit-UI' 2
-Tools::HierarchicalChangeList Tools__HierarchicalChangeList stx:libtool 'Interface-Browsers-ChangeSet' 2
-Tools::HierarchicalPackageFilterList Tools__HierarchicalPackageFilterList stx:libtool 'Interface-Browsers-New-Profiler' 2
-Tools::InheritanceClassList Tools__InheritanceClassList stx:libtool 'Interface-Browsers-New' 2
-NewChangesBrowser NewChangesBrowser stx:libtool 'Interface-Browsers' 0
+Tools::TestRunnerEmbedded Tools__TestRunnerEmbedded stx:libtool 'SUnit-UI' 3
+Tools::VariableList Tools__VariableList stx:libtool 'Interface-Browsers-New' 3
+Tools::ChangeList Tools__ChangeList stx:libtool 'Interface-Browsers-ChangeSet' 3
+Tools::ChangeSetDiffList Tools__ChangeSetDiffList stx:libtool 'Interface-Diff' 3
+Tools::FullMethodCategoryList Tools__FullMethodCategoryList stx:libtool 'Interface-Browsers-New' 3
+Tools::HierarchicalClassCategoryList Tools__HierarchicalClassCategoryList stx:libtool 'Interface-Browsers-New' 3
+Tools::HierarchicalClassList Tools__HierarchicalClassList stx:libtool 'Interface-Browsers-New' 3
+Tools::HierarchicalLintRuleList Tools__HierarchicalLintRuleList stx:libtool 'Interface-Lint' 3
+Tools::HierarchicalProjectList Tools__HierarchicalProjectList stx:libtool 'Interface-Browsers-New' 3
+Tools::ImplementingClassList Tools__ImplementingClassList stx:libtool 'Interface-Browsers-New' 3
+Tools::ImplementingMethodList Tools__ImplementingMethodList stx:libtool 'Interface-Browsers-New' 3
+Tools::NamespaceFilter Tools__NamespaceFilter stx:libtool 'Interface-Browsers-New' 3
+Tools::TestRunner2 Tools__TestRunner2 stx:libtool 'SUnit-UI' 3
+Tools::HierarchicalChangeList Tools__HierarchicalChangeList stx:libtool 'Interface-Browsers-ChangeSet' 3
+Tools::HierarchicalPackageFilterList Tools__HierarchicalPackageFilterList stx:libtool 'Interface-Browsers-New-Profiler' 3
+Tools::InheritanceClassList Tools__InheritanceClassList stx:libtool 'Interface-Browsers-New' 3
+NewChangesBrowser NewChangesBrowser stx:libtool 'Interface-Browsers' 9
+AbstractVersionDiffBrowserItem AbstractVersionDiffBrowserItem stx:libtool 'Interface-Browsers-Support' 0
 AbstractRevisionItem AbstractRevisionItem stx:libtool 'Interface-Browsers-Support' 0
-AbstractVersionDiffBrowserItem AbstractVersionDiffBrowserItem stx:libtool 'Interface-Browsers-Support' 0
-ApplicationBuilder ApplicationBuilder stx:libtool 'Interface-Tools' 9
+ApplicationBuilder ApplicationBuilder stx:libtool 'Interface-Tools' 10
 ClassItem ClassItem stx:libtool 'Interface-Browsers-Support' 0
 ClassItemRoot ClassItemRoot stx:libtool 'Interface-Browsers-Support' 0
 ClassItemRootForRevision ClassItemRootForRevision stx:libtool 'Interface-Browsers-Support' 0
 ClassNameItem ClassNameItem stx:libtool 'Interface-Browsers-Support' 0
-ClassRevisionTree ClassRevisionTree stx:libtool 'Interface-Browsers-Support' 2
-CodeGeneratorTests CodeGeneratorTests stx:libtool 'Interface-Browsers' 0
+ClassRevisionTree ClassRevisionTree stx:libtool 'Interface-Browsers-Support' 3
 ColorInspectorView ColorInspectorView stx:libtool 'Interface-Inspector' 2
 EWorldIconLibrary EWorldIconLibrary stx:libtool 'Interface-Smalltalk' 0
 ExpandableRevisionItem ExpandableRevisionItem stx:libtool 'Interface-Browsers-Support' 0
 FileBrowserV2Tests FileBrowserV2Tests stx:libtool 'Interface-Tools-File' 1
-FileDialogV2 FileDialogV2 stx:libtool 'Interface-Tools-File' 2
+FileDialogV2 FileDialogV2 stx:libtool 'Interface-Tools-File' 3
 HierarchicalClassRevisionList HierarchicalClassRevisionList stx:libtool 'Interface-Browsers-Support' 0
-HierarchicalVersionDiffBrowser HierarchicalVersionDiffBrowser stx:libtool 'Interface-Browsers' 2
-Launcher Launcher stx:libtool 'Interface-Smalltalk' 8
-LibraryBuilder LibraryBuilder stx:libtool 'Interface-Tools' 9
-OldLauncher OldLauncher stx:libtool 'Interface-Smalltalk' 0
+HierarchicalVersionDiffBrowser HierarchicalVersionDiffBrowser stx:libtool 'Interface-Browsers' 3
+Launcher Launcher stx:libtool 'Interface-Smalltalk' 9
+LibraryBuilder LibraryBuilder stx:libtool 'Interface-Tools' 10
+OldLauncher OldLauncher stx:libtool 'Interface-Smalltalk' 2
 ProcessMonitor ProcessMonitor stx:libtool 'Monitors-ST/X' 2
 ProjectView ProjectView stx:libtool 'Interface-Tools' 2
 SemaphoreMonitor SemaphoreMonitor stx:libtool 'Monitors-ST/X' 2
@@ -220,14 +219,13 @@
 ClassVariablesInspectorView ClassVariablesInspectorView stx:libtool 'Interface-Inspector' 2
 SourceRevisionItem SourceRevisionItem stx:libtool 'Interface-Browsers-Support' 0
 TextDiffTests TextDiffTests stx:libtool 'Collections-Sequenceable-Diff' 1
-Tools::CodeView2DemoApp Tools__CodeView2DemoApp stx:libtool 'Interface-CodeView' 2
+Tools::CodeView2DemoApp Tools__CodeView2DemoApp stx:libtool 'Interface-CodeView' 3
+Tools::DiffCodeView2DemoApp Tools__DiffCodeView2DemoApp stx:libtool 'Interface-CodeView' 3
+Tools::SmalltalkMergeTool Tools__SmalltalkMergeTool stx:libtool 'Interface-Diff & Merge tool' 3
+Tools::ToDoList Tools__ToDoList stx:libtool 'Interface-Smalltalk-ToDo' 0
+Tools::ToDoListBrowser Tools__ToDoListBrowser stx:libtool 'Interface-Smalltalk-ToDo' 3
+Tools::ToDoListEntry Tools__ToDoListEntry stx:libtool 'Interface-Smalltalk-ToDo' 0
 Tools::CompilerWarningToDoListEntry Tools__CompilerWarningToDoListEntry stx:libtool 'Interface-Smalltalk-ToDo' 0
-Tools::DiffCodeView2DemoApp Tools__DiffCodeView2DemoApp stx:libtool 'Interface-CodeView' 2
-Tools::NavigationHistoryTests Tools__NavigationHistoryTests stx:libtool 'Interface-Browsers-New-History' 1
-Tools::SmalltalkMergeTool Tools__SmalltalkMergeTool stx:libtool 'Interface-Diff & Merge tool' 2
-Tools::ToDoList Tools__ToDoList stx:libtool 'Interface-Smalltalk-ToDo' 0
-Tools::ToDoListBrowser Tools__ToDoListBrowser stx:libtool 'Interface-Smalltalk-ToDo' 2
-Tools::ToDoListEntry Tools__ToDoListEntry stx:libtool 'Interface-Smalltalk-ToDo' 0
 Tools::ToDoNotification Tools__ToDoNotification stx:libtool 'Interface-Smalltalk-ToDo' 1
 VersionRevisionItem VersionRevisionItem stx:libtool 'Interface-Browsers-Support' 0
 XTermView XTermView stx:libtool 'Interface-Tools-Terminal' 2
--- a/bc.mak	Wed Sep 15 13:57:00 2021 +0100
+++ b/bc.mak	Wed Sep 15 16:10:12 2021 +0100
@@ -96,7 +96,6 @@
 $(OUTDIR)ChangesBrowser.$(O) ChangesBrowser.$(C) ChangesBrowser.$(H): ChangesBrowser.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\StandardSystemView.$(H) $(INCLUDE_TOP)\stx\libview\TopView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(STCHDR)
 $(OUTDIR)CodeCompletionHelpMenuView.$(O) CodeCompletionHelpMenuView.$(C) CodeCompletionHelpMenuView.$(H): CodeCompletionHelpMenuView.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\PopUpView.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\TopView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libwidg\ListView.$(H) $(INCLUDE_TOP)\stx\libwidg\MenuView.$(H) $(INCLUDE_TOP)\stx\libwidg\SelectionInListView.$(H) $(STCHDR)
 $(OUTDIR)CodeCompletionHelpView.$(O) CodeCompletionHelpView.$(C) CodeCompletionHelpView.$(H): CodeCompletionHelpView.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) $(STCHDR)
-$(OUTDIR)CodeGenerator.$(O) CodeGenerator.$(C) CodeGenerator.$(H): CodeGenerator.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser\RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CodeGeneratorTool.$(O) CodeGeneratorTool.$(C) CodeGeneratorTool.$(H): CodeGeneratorTool.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)DebugView.$(O) DebugView.$(C) DebugView.$(H): DebugView.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\StandardSystemView.$(H) $(INCLUDE_TOP)\stx\libview\TopView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(STCHDR)
 $(OUTDIR)Diff.$(O) Diff.$(C) Diff.$(H): Diff.st $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -146,6 +145,7 @@
 $(OUTDIR)Tools__ClassSorter.$(O) Tools__ClassSorter.$(C) Tools__ClassSorter.$(H): Tools__ClassSorter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeCompletionMenu.$(O) Tools__CodeCompletionMenu.$(C) Tools__CodeCompletionMenu.$(H): Tools__CodeCompletionMenu.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) $(INCLUDE_TOP)\stx\libwidg2\SelectionInListModelView.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeCritics.$(O) Tools__CodeCritics.$(C) Tools__CodeCritics.$(H): Tools__CodeCritics.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Tools__CodeGenerator.$(O) Tools__CodeGenerator.$(C) Tools__CodeGenerator.$(H): Tools__CodeGenerator.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser\RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeView2.$(O) Tools__CodeView2.$(C) Tools__CodeView2.$(H): Tools__CodeView2.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview\AbstractBackground.$(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\libwidg\CodeView.$(H) $(INCLUDE_TOP)\stx\libwidg\EditTextView.$(H) $(INCLUDE_TOP)\stx\libwidg\ListView.$(H) $(INCLUDE_TOP)\stx\libwidg\TextCollector.$(H) $(INCLUDE_TOP)\stx\libwidg\TextView.$(H) $(INCLUDE_TOP)\stx\libwidg\Workspace.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeViewService.$(O) Tools__CodeViewService.$(C) Tools__CodeViewService.$(H): Tools__CodeViewService.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__DiffCodeView2.$(O) Tools__DiffCodeView2.$(C) Tools__DiffCodeView2.$(H): Tools__DiffCodeView2.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) $(INCLUDE_TOP)\stx\libwidg2\TwoColumnTextView.$(H) $(STCHDR)
--- a/libInit.cc	Wed Sep 15 13:57:00 2021 +0100
+++ b/libInit.cc	Wed Sep 15 16:10:12 2021 +0100
@@ -32,7 +32,6 @@
 extern void _ChangesBrowser_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CodeCompletionHelpMenuView_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CodeCompletionHelpView_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _CodeGenerator_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CodeGeneratorTool_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DebugView_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Diff_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -82,6 +81,7 @@
 extern void _Tools__ClassSorter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__CodeCompletionMenu_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__CodeCritics_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _Tools__CodeGenerator_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__CodeView2_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__CodeViewService_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__DiffCodeView2_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -238,7 +238,6 @@
     _ChangesBrowser_Init(pass,__pRT__,snd);
     _CodeCompletionHelpMenuView_Init(pass,__pRT__,snd);
     _CodeCompletionHelpView_Init(pass,__pRT__,snd);
-    _CodeGenerator_Init(pass,__pRT__,snd);
     _CodeGeneratorTool_Init(pass,__pRT__,snd);
     _DebugView_Init(pass,__pRT__,snd);
     _Diff_Init(pass,__pRT__,snd);
@@ -288,6 +287,7 @@
     _Tools__ClassSorter_Init(pass,__pRT__,snd);
     _Tools__CodeCompletionMenu_Init(pass,__pRT__,snd);
     _Tools__CodeCritics_Init(pass,__pRT__,snd);
+    _Tools__CodeGenerator_Init(pass,__pRT__,snd);
     _Tools__CodeView2_Init(pass,__pRT__,snd);
     _Tools__CodeViewService_Init(pass,__pRT__,snd);
     _Tools__DiffCodeView2_Init(pass,__pRT__,snd);
--- a/stx_libtool.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/stx_libtool.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,6 +1,7 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger / eXept Software AG
  COPYRIGHT (c) 2015-2016 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -27,6 +28,7 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger / eXept Software AG
  COPYRIGHT (c) 2015-2016 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -214,7 +216,7 @@
         ChangesBrowser
         CodeCompletionHelpMenuView
         CodeCompletionHelpView
-        CodeGenerator
+        #'Tools::CodeGenerator'
         CodeGeneratorTool
         DebugView
         Diff
@@ -391,15 +393,14 @@
         #'Tools::HierarchicalPackageFilterList'
         #'Tools::InheritanceClassList'
         (NewChangesBrowser autoload)
+        (AbstractVersionDiffBrowserItem autoload)
         (AbstractRevisionItem autoload)
-        (AbstractVersionDiffBrowserItem autoload)
         (ApplicationBuilder autoload)
         (ClassItem autoload)
         (ClassItemRoot autoload)
         (ClassItemRootForRevision autoload)
         (ClassNameItem autoload)
         (ClassRevisionTree autoload)
-        (CodeGeneratorTests autoload)
         (ColorInspectorView autoload)
         (EWorldIconLibrary autoload)
         (ExpandableRevisionItem autoload)
@@ -418,17 +419,18 @@
         (SourceRevisionItem autoload)
         (TextDiffTests autoload)
         (#'Tools::CodeView2DemoApp' autoload)
-        (#'Tools::CompilerWarningToDoListEntry' autoload)
         (#'Tools::DiffCodeView2DemoApp' autoload)
-        (#'Tools::NavigationHistoryTests' autoload)
         (#'Tools::SmalltalkMergeTool' autoload)
         (#'Tools::ToDoList' autoload)
         (#'Tools::ToDoListBrowser' autoload)
         (#'Tools::ToDoListEntry' autoload)
+        (#'Tools::CompilerWarningToDoListEntry' autoload)
         (#'Tools::ToDoNotification' autoload)
         (VersionRevisionItem autoload)
         (XTermView autoload)
     )
+
+    "Modified: / 15-09-2021 / 16:15:50 / Jan Vrany <jan.vrany@labware.com>"
 !
 
 extensionMethodNames
--- a/tests/Make.proto	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/Make.proto	Wed Sep 15 16:10:12 2021 +0100
@@ -125,7 +125,9 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)Tools__CodeGeneratorTests.$(O) Tools__CodeGeneratorTests.$(C) Tools__CodeGeneratorTests.$(H): Tools__CodeGeneratorTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeView2Tests.$(O) Tools__CodeView2Tests.$(C) Tools__CodeView2Tests.$(H): Tools__CodeView2Tests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)Tools__NavigationHistoryTests.$(O) Tools__NavigationHistoryTests.$(C) Tools__NavigationHistoryTests.$(H): Tools__NavigationHistoryTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__NewSystemBrowserTests.$(O) Tools__NewSystemBrowserTests.$(C) Tools__NewSystemBrowserTests.$(H): Tools__NewSystemBrowserTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)WorkspaceApplicationTests.$(O) WorkspaceApplicationTests.$(C) WorkspaceApplicationTests.$(H): WorkspaceApplicationTests.st $(INCLUDE_TOP)/stx/goodies/sunit/TestAsserter.$(H) $(INCLUDE_TOP)/stx/goodies/sunit/TestCase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)stx_libtool_tests.$(O) stx_libtool_tests.$(C) stx_libtool_tests.$(H): stx_libtool_tests.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
--- a/tests/Make.spec	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/Make.spec	Wed Sep 15 16:10:12 2021 +0100
@@ -51,7 +51,9 @@
 STCWARNINGS=-warnNonStandard
 
 COMMON_CLASSES= \
+	Tools::CodeGeneratorTests \
 	Tools::CodeView2Tests \
+	Tools::NavigationHistoryTests \
 	Tools::NewSystemBrowserTests \
 	WorkspaceApplicationTests \
 	stx_libtool_tests \
@@ -60,7 +62,9 @@
 
 
 COMMON_OBJS= \
+    $(OUTDIR)Tools__CodeGeneratorTests.$(O) \
     $(OUTDIR)Tools__CodeView2Tests.$(O) \
+    $(OUTDIR)Tools__NavigationHistoryTests.$(O) \
     $(OUTDIR)Tools__NewSystemBrowserTests.$(O) \
     $(OUTDIR)WorkspaceApplicationTests.$(O) \
     $(OUTDIR)stx_libtool_tests.$(O) \
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/tests/Tools__CodeGeneratorTests.st	Wed Sep 15 16:10:12 2021 +0100
@@ -0,0 +1,237 @@
+"
+ Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
+ Copyright (c) 2009-2010 eXept Software AG
+ Copyright (c) 2021 LabWare
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+"{ Package: 'stx:libtool/tests' }"
+
+"{ NameSpace: Tools }"
+
+TestCase subclass:#CodeGeneratorTests
+	instanceVariableNames:'cg'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Browsers-Tests'
+!
+
+!CodeGeneratorTests class methodsFor:'documentation'!
+
+copyright
+"
+ Copyright (c) 2007-2010 Jan Vrany, SWING Research Group, Czech Technical University in Prague
+ Copyright (c) 2009-2010 eXept Software AG
+ Copyright (c) 2021 LabWare
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+! !
+
+!CodeGeneratorTests methodsFor:'initialization & release'!
+
+setUp
+
+    cg := CodeGenerator new
+
+    "Created: / 07-07-2009 / 09:26:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+tearDown
+
+    | mocks |
+    mocks := Set new.
+    self class selectorsDo:
+        [:selector| 
+        (selector startsWith: 'mock')
+            ifTrue:[mocks add: selector]].
+    mocks do:
+        [:selector|
+        self class removeSelector: selector].
+
+    "Modified: / 07-07-2009 / 09:34:22 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!CodeGeneratorTests methodsFor:'mocks - do not remove'!
+
+mmock_03
+
+    ^3
+
+    "Created: / 07-07-2009 / 19:21:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+mmock_03: x
+
+    ^x
+
+    "Created: / 07-07-2009 / 19:55:10 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!CodeGeneratorTests methodsFor:'tests'!
+
+test_01
+
+    cg
+        class: self class;
+        replace: '`@e' with: '1';
+        source: 'mock_01 ^ `@e';
+        compile.
+
+    self assert: (self respondsTo: #mock_01).
+    self assert: (self mock_01 = 1).
+
+    "Created: / 07-07-2009 / 09:29:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_02
+
+    cg
+        class: self class;
+        replace: '`@selector' with: #mock_02;
+        source: '`@selector ^ 2';
+        compile.
+
+    self assert: (self respondsTo: #mock_02).
+    self assert: (self mock_02 = 2).
+
+    "Created: / 07-07-2009 / 19:07:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_02b
+
+    cg
+        class: self class;
+        replace: '`@selector:' with: #mock_02:;
+        source: '`@selector: arg ^ arg';
+        compile.
+
+    self assert: (self respondsTo: #mock_02:).
+    self assert: (self mock_02: 20) = 20.
+
+    "Created: / 07-07-2009 / 19:54:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_03
+
+    cg
+        class: self class;
+        replace: '`@selector' with: 'mmock_03';
+        source: 'mock_03 ^ self `@selector';
+        compile.
+
+    self assert: (self respondsTo: #mock_03).
+    self assert: (self mock_03 = 3).
+
+    "Created: / 07-07-2009 / 19:22:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_03b
+
+    cg
+        class: self class;
+        replace: '`@selector:' with: #mmock_03:;
+        source: 'mock_03b ^ self `@selector: 30';
+        compile.
+
+    self assert: (self respondsTo: #mock_03b).
+    self assert: (self mock_03b = 30).
+
+    "Created: / 07-07-2009 / 19:54:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_04a
+
+    cg
+        class: self class;
+        source: '`@selector ^ 4';
+        replace: '`@selector' with: #mock_04a;
+        compile.
+
+    self assert: (self respondsTo: #mock_04a).
+    self assert: (self mock_04a = 4).
+
+    "Created: / 24-04-2014 / 11:13:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_04b
+
+    cg
+        class: self class;
+        source: '`@selpart1 anArg `@selpart2 anArg2 ^ anArg + anArg2';
+        replace: '`@selpart1' with: #mock_04:;
+        replace: '`@selpart2' with: #b:;
+        compile.
+
+    self assert: (self respondsTo: #mock_04:b:).
+    self assert: ((self mock_04:123 b: 123) = (123+123)).
+
+    "Created: / 24-04-2014 / 11:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_05
+
+    cg
+        class: self class;
+        source: 'mock_05
+                "comment"
+
+                ^ 10';
+        compile.
+
+    self assert: (self respondsTo: #mock_05).
+    self assert: (self perform: #mock_05) == 10.
+    self assert: ((self class >> #mock_05) source includesString: 'comment')
+
+    "Created: / 24-04-2014 / 11:28:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-05-2014 / 01:02:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!CodeGeneratorTests class methodsFor:'documentation'!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/CodeGeneratorTests.st,v 1.5 2014-05-24 00:10:50 vrany Exp $'
+!
+
+version_SVN
+    ^ '$Id: CodeGeneratorTests.st,v 1.5 2014-05-24 00:10:50 vrany Exp $'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/tests/Tools__NavigationHistoryTests.st	Wed Sep 15 16:10:12 2021 +0100
@@ -0,0 +1,209 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+ COPYRIGHT (c) 2015 Jan Vrany
+              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:libtool/tests' }"
+
+"{ NameSpace: Tools }"
+
+TestCase subclass:#NavigationHistoryTests
+	instanceVariableNames:'history'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-Browsers-New-History'
+!
+
+!NavigationHistoryTests class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+ COPYRIGHT (c) 2015 Jan Vrany
+              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.
+"
+! !
+
+!NavigationHistoryTests methodsFor:'initialization'!
+
+setUp
+
+    history := NavigationHistory new
+
+    "Created: / 21-02-2008 / 16:52:19 / janfrog"
+! !
+
+!NavigationHistoryTests methodsFor:'tests'!
+
+test_01
+
+    self
+        assert: history canGoBack not;
+        assert: history canGoForward not
+
+    "Created: / 21-02-2008 / 16:54:55 / janfrog"
+!
+
+test_02
+
+    history goTo: 1.
+        
+    self
+        assert: history canGoBack not;
+        assert: history canGoForward not
+
+    "Created: / 21-02-2008 / 16:55:34 / janfrog"
+!
+
+test_03
+    history
+        goTo:1;
+        goTo:2;
+        goTo:3;
+        goBack.
+    self
+        assert:history currentItem = 2;
+        assert:history canGoBack;
+        assert:history goBackItems asArray = #( 1 );
+        assert:history canGoForward;
+        assert:history goForwardItems asArray = #( 3 ).
+
+    "Created: / 21-02-2008 / 16:57:29 / janfrog"
+    "Modified: / 27-02-2008 / 11:52:26 / janfrog"
+    "Modified: / 06-06-2008 / 09:31:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_04
+    history
+        goTo:1;
+        goTo:2;
+        goTo:3;
+        goTo:2.
+    self
+        assert:history currentItem = 2;
+        assert:history canGoBack;
+        assert:history goBackItems asArray = #( 3 2 1);
+        assert:history canGoForward not;
+        assert:history goForwardItems asArray = #( ).
+
+    "Created: / 21-02-2008 / 16:57:58 / janfrog"
+    "Modified: / 27-02-2008 / 11:52:26 / janfrog"
+    "Modified: / 06-06-2008 / 09:31:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 04-09-2015 / 06:56:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_05
+    history
+        goTo:1;
+        goTo:2;
+        goTo:3;
+        goBack;
+        goBack;
+        goTo:5.
+    self
+        assert:history currentItem = 5;
+        assert:history canGoBack;
+        assert:history goBackItems asArray = #( 1 );
+        assert:history canGoForward not.
+
+    "Created: / 21-02-2008 / 16:59:11 / janfrog"
+    "Modified: / 27-02-2008 / 11:52:12 / janfrog"
+    "Modified: / 06-06-2008 / 09:31:40 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+test_06
+    history goTo:1.
+    self assert: history currentItem = 1.
+    self assert: history canGoBack not.
+    self assert: history goBackItems asArray = #( ).
+    self assert: history canGoForward not.
+    self assert: history goForwardItems asArray = #( ).
+
+    history goTo:2.
+    self assert: history currentItem = 2.
+    self assert: history canGoBack .
+    self assert: history goBackItems asArray = #( 1 ).
+    self assert: history canGoForward not.
+    self assert: history goForwardItems asArray = #( ).
+
+    history goTo:3.
+    self assert: history currentItem = 3.
+    self assert: history canGoBack .
+    self assert: history goBackItems asArray = #( 2 1 ).
+    self assert: history canGoForward not.
+    self assert: history goForwardItems asArray = #( ).
+
+    history goTo:2.
+    self assert: history currentItem = 2.
+    self assert: history canGoBack .
+    self assert: history goBackItems asArray = #( 3 2 1 ).
+    self assert: history canGoForward not.
+    self assert: history goForwardItems asArray = #( ).
+
+    history goBack.
+    self assert: history currentItem = 3.
+    self assert: history canGoBack .
+    self assert: history goBackItems asArray = #( 2 1 ).
+    self assert: history canGoForward.
+    self assert: history goForwardItems asArray = #( 2 ).
+
+    history goBack.
+    self assert: history currentItem = 2.
+    self assert: history canGoBack .
+    self assert: history goBackItems asArray = #( 1 ).
+    self assert: history canGoForward.
+    self assert: history goForwardItems asArray = #( 3 2 ).   
+
+    history goBack.
+    self assert: history currentItem = 1.
+    self assert: history canGoBack not.
+    self assert: history goBackItems asArray = #( ).
+    self assert: history canGoForward.
+    self assert: history goForwardItems asArray = #( 2 3 2 ).   
+
+    history goForward.
+    self assert: history currentItem = 2.
+    self assert: history canGoBack.
+    self assert: history goBackItems asArray = #( 1 ).
+    self assert: history canGoForward.
+    self assert: history goForwardItems asArray = #( 3 2 ).   
+
+    history goForward.
+    self assert: history currentItem = 3.
+    self assert: history canGoBack.
+    self assert: history goBackItems asArray = #( 2 1 ).
+    self assert: history canGoForward.
+    self assert: history goForwardItems asArray = #( 2 ).
+
+    "Created: / 04-09-2015 / 06:59:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!NavigationHistoryTests class methodsFor:'documentation'!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NavigationHistoryTests.st,v 1.2 2012-09-02 11:21:14 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ '§Id: Tools__NavigationHistoryTests.st 7486 2009-10-26 22:06:24Z vranyj1 §'
+! !
+
--- a/tests/WorkspaceApplicationTests.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/WorkspaceApplicationTests.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,5 +1,6 @@
 "
  COPYRIGHT (c) 2017 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -25,6 +26,7 @@
 copyright
 "
  COPYRIGHT (c) 2017 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -149,3 +151,10 @@
     "Modified: / 29-08-2018 / 21:43:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!WorkspaceApplicationTests class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/tests/abbrev.stc	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/abbrev.stc	Wed Sep 15 16:10:12 2021 +0100
@@ -1,4 +1,9 @@
-Tools::CodeView2Tests Tools__CodeView2Tests stx:libtool/tests 'Interface-CodeView-Tests' 0
-Tools::NewSystemBrowserTests Tools__NewSystemBrowserTests stx:libtool/tests 'Interface-Browsers-New-Tests' 0
-WorkspaceApplicationTests WorkspaceApplicationTests stx:libtool/tests 'Interface-CodeView-Tests' 0
-stx_libtool_tests stx_libtool_tests stx:libtool/tests '* Projects & Packages *' 0
+# automagically generated by the project definition
+# this file is needed for stc to be able to compile modules independently.
+# it provides information about a classes filename, category and especially namespace.
+Tools::CodeView2Tests Tools__CodeView2Tests stx:libtool/tests 'Interface-CodeView-Tests' 1
+Tools::NewSystemBrowserTests Tools__NewSystemBrowserTests stx:libtool/tests 'Interface-Browsers-New-Tests' 1
+WorkspaceApplicationTests WorkspaceApplicationTests stx:libtool/tests 'Interface-CodeView-Tests' 1
+Tools::CodeGeneratorTests Tools__CodeGeneratorTests stx:libtool/tests 'Interface-Browsers-Tests' 1
+Tools::NavigationHistoryTests Tools__NavigationHistoryTests stx:libtool/tests 'Interface-Browsers-New-History' 1
+stx_libtool_tests stx_libtool_tests stx:libtool/tests '* Projects & Packages *' 3
--- a/tests/bc.mak	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/bc.mak	Wed Sep 15 16:10:12 2021 +0100
@@ -63,7 +63,7 @@
 
 
 
-test: $(TOP)\goodies\builder\reports\NUL
+test: $(TOP)\goodies\builder\reports
 	pushd $(TOP)\goodies\builder\reports & $(MAKE_BAT)
 	$(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
         
@@ -72,7 +72,9 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)Tools__CodeGeneratorTests.$(O) Tools__CodeGeneratorTests.$(C) Tools__CodeGeneratorTests.$(H): Tools__CodeGeneratorTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__CodeView2Tests.$(O) Tools__CodeView2Tests.$(C) Tools__CodeView2Tests.$(H): Tools__CodeView2Tests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Tools__NavigationHistoryTests.$(O) Tools__NavigationHistoryTests.$(C) Tools__NavigationHistoryTests.$(H): Tools__NavigationHistoryTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Tools__NewSystemBrowserTests.$(O) Tools__NewSystemBrowserTests.$(C) Tools__NewSystemBrowserTests.$(H): Tools__NewSystemBrowserTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)WorkspaceApplicationTests.$(O) WorkspaceApplicationTests.$(C) WorkspaceApplicationTests.$(H): WorkspaceApplicationTests.st $(INCLUDE_TOP)\stx\goodies\sunit\TestAsserter.$(H) $(INCLUDE_TOP)\stx\goodies\sunit\TestCase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)stx_libtool_tests.$(O) stx_libtool_tests.$(C) stx_libtool_tests.$(H): stx_libtool_tests.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
--- a/tests/libInit.cc	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/libInit.cc	Wed Sep 15 16:10:12 2021 +0100
@@ -16,7 +16,9 @@
 DLL_EXPORT void _libstx_libtool_tests_InitDefinition() INIT_TEXT_SECTION;
 #endif
 
+extern void _Tools__CodeGeneratorTests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__CodeView2Tests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _Tools__NavigationHistoryTests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Tools__NewSystemBrowserTests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WorkspaceApplicationTests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _stx_137libtool_137tests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -34,7 +36,9 @@
 void _libstx_libtool_tests_Init(int pass, struct __vmData__ *__pRT__, OBJ snd)
 {
   __BEGIN_PACKAGE2__("libstx_libtool_tests", _libstx_libtool_tests_Init, "stx:libtool/tests");
+    _Tools__CodeGeneratorTests_Init(pass,__pRT__,snd);
     _Tools__CodeView2Tests_Init(pass,__pRT__,snd);
+    _Tools__NavigationHistoryTests_Init(pass,__pRT__,snd);
     _Tools__NewSystemBrowserTests_Init(pass,__pRT__,snd);
     _WorkspaceApplicationTests_Init(pass,__pRT__,snd);
     _stx_137libtool_137tests_Init(pass,__pRT__,snd);
--- a/tests/stx_libtool_tests.st	Wed Sep 15 13:57:00 2021 +0100
+++ b/tests/stx_libtool_tests.st	Wed Sep 15 16:10:12 2021 +0100
@@ -1,5 +1,6 @@
 "
  COPYRIGHT (c) 2017 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -25,6 +26,7 @@
 copyright
 "
  COPYRIGHT (c) 2017 Jan Vrany
+ COPYRIGHT (c) 2021 LabWare
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -107,8 +109,12 @@
         #'Tools::CodeView2Tests'
         #'Tools::NewSystemBrowserTests'
         WorkspaceApplicationTests
+        #'Tools::CodeGeneratorTests'
+        #'Tools::NavigationHistoryTests'
         #'stx_libtool_tests'
     )
+
+    "Modified: / 15-09-2021 / 16:20:30 / Jan Vrany <jan.vrany@labware.com>"
 !
 
 extensionMethodNames