Merge jv
authorMerge Script
Fri, 29 Jul 2016 06:57:08 +0200
branchjv
changeset 4067 ea65905990e9
parent 4065 a3da1e8be872 (diff)
parent 4066 9087a9dc0946 (current diff)
child 4074 533d1c715e83
Merge
SystemOrganizer.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/.hgignore	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,17 @@
+
+syntax: glob
+*Init.c   
+makefile
+*.so
+*.H
+*.o
+*.STH
+*.sc
+objbc
+objvc
+*.class
+java/libs/*.jar
+java/libs-src/*.jar
+*-Test.xml
+st.chg
+stx_libbasic3-config.h
--- a/AbstractSourceCodeManager.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/AbstractSourceCodeManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -18,7 +18,8 @@
 Object subclass:#AbstractSourceCodeManager
 	instanceVariableNames:''
 	classVariableNames:'CacheDirectoryName CachingSources DefaultManager ManagerPerModule
-		UseWorkTree Verbose WorkTreeDirectoryName'
+		UseWorkTree Verbose WorkTreeDirectoryName
+		ManagerForPackageCache'
 	poolDictionaries:''
 	category:'System-SourceCodeManagement'
 !
@@ -107,6 +108,7 @@
 
     CachingSources isNil ifTrue:[CachingSources := true].
     UseWorkTree    isNil ifTrue:[UseWorkTree := false].
+    ManagerForPackageCache := Dictionary new.
 
     CachingSources ifTrue:[
         self validateCacheDirPath.
@@ -114,6 +116,7 @@
     Smalltalk addDependent:self
 
     "Modified: / 02-03-2012 / 17:00:11 / cg"
+    "Modified: / 01-10-2015 / 06:07:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 update:something with:aParameter from:changedObject
@@ -129,6 +132,20 @@
     or:[CacheDirectoryName asFilename exists not]) ifTrue:[
         self initCacheDirPath   
     ].
+!
+
+validateWorkingCopy: path
+    "Return true, if given path is a valid working 
+     copy of this manager; false otherwise."
+
+    "/ JV@2015-10-02: Following is certainly a kludge, but defined
+    "/ here tp avoid forking stx:libsvn..."
+    self name == #SVNSourceCodeManager ifTrue:[
+        ^ (path asFilename / '.svn') isDirectory
+    ].
+    ^ false
+
+    "Created: / 02-10-2015 / 09:52:07 / jv"
 ! !
 
 !AbstractSourceCodeManager class methodsFor:'accessing'!
@@ -252,7 +269,8 @@
     ManagerPerModule add:
         (PackageAndManager 
             package: aPackageIDMatchString 
-            manager: aSourceCodeManagerClass)
+            manager: aSourceCodeManagerClass).
+    ManagerForPackageCache := Dictionary new. 
 
     "
      self managerForModule:'stx:libbasic2' put:SVNSourceCodeManager
@@ -262,20 +280,61 @@
     "
 
     "Created: / 18-04-2011 / 19:48:19 / cg"
-    "Modified: / 07-07-2013 / 10:40:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-10-2015 / 06:04:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-managerForPackage:aPackageID
+managerForPackage: aSymbol
     "return the sourceCodeManager for a aPackageID, nil if unspecified in the manager per package list"
 
+    | prjsym prjdef prjdir parentPrjId manager |
+
+    prjsym := aSymbol asSymbol.
     "JV@2012-01-23: If source code management is disabled, return nil. Following code
      is hack since  there is no global boolean flag, sigh"
     (Smalltalk at:#SourceCodeManager) isNil ifTrue:[ ^nil ].
 
-    "JV@2012-01-23: HACK: Q: Shouldn't it filter configured manager through
-     'enabled' managers?"         
+    "First, search the cache..."
+    ManagerForPackageCache at: prjsym ifPresent:[ :manager | ^ manager ].
+
+    "If not found in the cache, search configured managers"
     self managerPerMatchingModuleDefinitions do:[:each |
-        (each match:aPackageID) ifTrue:[^ each manager].
+        (each match:prjsym) ifTrue:[
+            ManagerForPackageCache at: prjsym put: each manager.
+            ^ each manager
+        ].
+    ].
+
+    "If there's no configuration for given package, try to use the same
+     that was used when package was compiled"
+    prjdef := ProjectDefinition definitionClassForPackage: prjsym.
+    (prjdef notNil and:[prjdef binaryRevisionString notNil]) ifTrue:[ 
+        manager := prjdef sourceCodeManagerFromBinaryRevision.
+        (manager notNil and:[manager enabled and:[manager isResponsibleForPackage: prjsym]]) ifTrue:[ 
+            ManagerForPackageCache at: prjsym put: manager.
+            ^manager
+        ].
+    ].
+
+    "Still no luck, try to auto-configure."
+    prjdef notNil ifTrue:[
+        prjdir := prjdef packageDirectory.
+        (prjdir notNil and:[prjdir isDirectory]) ifTrue:[
+            | managers |
+            managers := self availableManagers select:[:mgr |
+                mgr enabled
+                    and:[(mgr isResponsibleForPackage: prjsym)
+                    and:[mgr validateWorkingCopy: prjdir] ] .    
+            ].
+            managers size == 1 ifTrue:[
+                manager := managers anElement.
+                ManagerForPackageCache at: prjsym put: manager.
+                ^manager
+            ]
+        ].
+    ].
+    parentPrjId := prjsym asPackageId parentPackage.
+    parentPrjId notNil ifTrue:[ 
+        ^ self managerForPackage: parentPrjId asSymbol  
     ].
     ^ DefaultManager
 
@@ -288,7 +347,8 @@
     "Created: / 18-04-2011 / 19:39:19 / cg"
     "Created: / 10-10-2011 / 14:50:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 19-10-2011 / 16:45:38 / cg"
-    "Modified (comment): / 23-01-2012 / 19:46:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-10-2015 / 10:24:41 / jv"
+    "Modified: / 04-03-2016 / 15:33:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 managerPerMatchingModuleDefinitions
@@ -309,10 +369,11 @@
      (not a dictionary, because order is relevant in the matching process, where the first match counts)"
 
     ManagerPerModule := aCollection.
-    UserPreferences current managerPerMatchingModuleDefinitions:aCollection
+    UserPreferences current managerPerMatchingModuleDefinitions:aCollection.
+    ManagerForPackageCache := Dictionary new.
 
     "Created: / 18-04-2011 / 20:09:21 / cg"
-    "Modified: / 09-07-2011 / 13:36:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-10-2015 / 06:04:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 named: managerTypeName
@@ -374,9 +435,11 @@
 shownInBrowserMenus:aBoolean
     "can be redefined in subclasses which can be suppressed in the browser's menus"
 
+    ManagerForPackageCache := Dictionary new.
     ^ UserPreferences current at:(self nameWithoutPrefix,'.enabled') put:aBoolean.
 
     "Created: / 15-01-2012 / 14:09:21 / cg"
+    "Modified: / 01-10-2015 / 06:07:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 useWorkTree
@@ -2555,7 +2618,7 @@
 
     |versionString|
 
-    versionString := aString copyWithout: $ยง.
+    versionString := aString copyWithout: (Character codePoint: 167).
     ^ self ensureKeywordExpansionWith: $$ inVersionMethod:versionString.
 
     "
@@ -2567,6 +2630,8 @@
      self ensureDollarsInVersionMethod:'foo ^ ''$Head'' '    
      self ensureDollarsInVersionMethod:'foo ^ ''Header$'' '    
     "
+
+    "Modified: / 04-05-2016 / 10:51:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 ensureKeyword: keyword inVersionMethod: source
@@ -4043,6 +4108,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id$'
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BeeProjectDefinitionWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,121 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Smalltalk }"
+
+BeeProjectWriter subclass:#BeeProjectDefinitionWriter
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes-Support'
+!
+
+!BeeProjectDefinitionWriter class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    A writer to write Smalltalk/X package in Bee Smalltalk format (.prj). Usage:
+
+    BeeProjectDefinitionWriter fileOut: 'jv:calipel/s' to: '/tmp/jv-calipel-s.prj'
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!BeeProjectDefinitionWriter methodsFor:'source writing'!
+
+fileOutClasses: classes on: stream
+
+    classes do:[:class |  
+        stream nextPutAll: 'project addClass: '; nextPutAll: class name storeString; nextPutAll: '.'; cr.
+    ].
+    stream cr.
+
+    "Modified: / 03-11-2015 / 07:05:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutExtensions:methods on: stream
+
+    stream nextPutAll: '#('; cr.
+    methods do:[:method | 
+        stream nextPut:'''';
+               nextPutAll: method mclass name;
+               nextPutAll: '>>';
+               nextPutAll: method seelctore;
+               nextPut:'''';
+               cr.
+    ].
+    stream nextPutAll: ') do: [:string | project addMethod: string].'
+
+    "Modified: / 03-11-2015 / 07:07:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutFooterOn:aStream
+    aStream cr.
+    aStream cr.
+    aStream nextPutAll: '^ project'.
+
+    "Created: / 03-11-2015 / 23:05:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutHeaderOn:aStream
+
+    aStream nextPutAll:(
+'"
+        __________________________________________________
+        @VM Project 1.0
+        __________________________________________________
+"
+
+| project |
+project := SimpleSmalltalkProject new 
+        name: ''%(NAME)'';
+        version: ''%(VERSION)'';
+        description: ''%(DESCRIPTION)'';
+        author: ''%(AUTHOR)'';
+        yourself.
+
+' bindWithArguments: self mappings)
+
+    "Modified: / 02-11-2015 / 19:16:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeProjectDefinitionWriter class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BeeProjectSourceWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,129 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Smalltalk }"
+
+BeeProjectWriter subclass:#BeeProjectSourceWriter
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes-Support'
+!
+
+!BeeProjectSourceWriter class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    A writer to write Smalltalk/X package in Bee Smalltalk format (.stp). Usage:
+
+    BeeProjectSourceWriter fileOut: 'jv:calipel/s' to: '/tmp/jv-calipel-s.stp'
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!BeeProjectSourceWriter methodsFor:'source writing'!
+
+fileOutClasses: classes on: stream
+    | writer |
+
+    writer := BeeSourceWriter new.
+    classes do:[:class |
+        self activityNotification:'exporting ', class name,'...'.
+        writer fileOut:class on:stream withTimeStamp:false withInitialize:false withDefinition:true methodFilter:[:m | false]
+    ].
+    classes do:[:class |
+        self activityNotification:'exporting ', class name,'...'.
+        writer fileOut:class on:stream withTimeStamp:false withInitialize:false withDefinition:false methodFilter:[:m | true]
+    ].
+
+    "Created: / 14-04-2015 / 13:47:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutExtensions: methods on:stream
+    | writer |
+
+    writer := BeeSourceWriter new.
+    self activityNotification:'exporting extensions...'.
+    methods do:[:eachMethod |
+        writer fileOutMethods:methods on:stream.
+        stream cr.
+    ]
+
+    "Modified: / 14-04-2015 / 13:51:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutHeaderOn: aStream
+
+    aStream nextPutAll:(
+'"
+        __________________________________________________
+        Author: %(AUTHOR).
+        Project name: %(NAME)
+        Version: %(VERSION)
+        Timestamp: %(TIMESTAMP)
+        Description: %(DESCRIPTION)
+        __________________________________________________
+"
+
+' bindWithArguments: self mappings)
+
+    "Created: / 14-04-2015 / 13:42:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-11-2015 / 19:00:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeProjectSourceWriter methodsFor:'utilities'!
+
+ensureNoUnicodeInClass:aClass
+    "/ check if we need UTF8 encoding
+    aClass withAllPrivateClasses do:[:cls |
+         cls instAndClassMethods contains:[:m |
+            self ensureNoUnicodeInMethod:m
+         ]
+    ].
+!
+
+ensureNoUnicodeInMethod:aMethod
+    |src|
+
+    src := aMethod source.
+    src isNil ifTrue:[
+        self error:'missing source in ',aMethod whoString
+    ].
+    src asSingleByteStringIfPossible isWideString ifTrue:[
+        self error:(aMethod whoString , ' contains unicode strings or character contants. Cannot be exported to VSE')
+    ].
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BeeProjectWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,174 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#BeeProjectWriter
+	instanceVariableNames:'projectDefinitionClass classesToBeInitialized'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes-Support'
+!
+
+!BeeProjectWriter class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!BeeProjectWriter class methodsFor:'private'!
+
+basenameForPackage:pkg
+    |  pkgdef |
+
+    pkgdef := ProjectDefinition definitionClassForPackage: pkg.
+    ^ pkgdef name.
+
+    "Created: / 03-11-2015 / 07:15:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeProjectWriter class methodsFor:'queries'!
+
+isAbstract
+    "Return if this class is an abstract class.
+     True is returned here for myself only; false for subclasses.
+     Abstract subclasses must redefine again."
+
+    ^ self == BeeProjectWriter.
+! !
+
+!BeeProjectWriter class methodsFor:'simple API'!
+
+fileOut: pkg in: directory
+    "File out Bee package (definition - .prj and source - .stp) in
+     given directory."
+
+    | basename prjFilename stpFilename |
+
+    basename := self basenameForPackage: pkg.
+    prjFilename := directory asFilename / (basename , '.prj').
+    stpFilename := directory asFilename  / (basename , '.stp').
+
+    BeeProjectDefinitionWriter fileOut: pkg to: prjFilename.
+    BeeProjectSourceWriter fileOut: pkg to: stpFilename.
+
+    "Created: / 03-11-2015 / 07:14:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOut:packageId on:stream
+    self new fileOut:packageId on:stream
+
+    "Modified: / 14-04-2015 / 13:52:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOut:packageId to: stringOrFilename
+    stringOrFilename asFilename writingFileDo:[ :stream |
+        self fileOut: packageId on: stream
+    ].
+
+    "Created: / 24-10-2015 / 08:49:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeProjectWriter methodsFor:'private'!
+
+mappings
+    | revinfo mappings |
+
+    revinfo := projectDefinitionClass revisionInfo.
+    mappings := Dictionary new.
+    mappings at: 'NAME' put: projectDefinitionClass name.
+    mappings at: 'VERSION' put: revinfo revision.
+    mappings at: 'AUTHOR' put: revinfo author asString.
+    mappings at: 'TIMESTAMP' put: revinfo date asString, ' ', revinfo time asString.
+    mappings at: 'DESCRIPTION' put: projectDefinitionClass description.
+    ^ mappings
+
+    "Created: / 02-11-2015 / 16:59:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-11-2015 / 18:58:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeProjectWriter methodsFor:'source writing'!
+
+fileOut:packageID on:aStream
+    |classesToFileout methodsToFileOut |
+
+    projectDefinitionClass := packageID asPackageId projectDefinitionClass.
+    classesToBeInitialized := OrderedCollection new.
+
+    aStream lineEndCRLF.
+
+    "/ make sure that everything is loaded.
+    projectDefinitionClass notNil ifTrue:[
+        projectDefinitionClass autoload.
+        projectDefinitionClass ensureFullyLoaded.
+        classesToFileout := Smalltalk allClassesInPackage:packageID.
+    ] ifFalse:[
+        classesToFileout := Smalltalk allClassesInPackage:packageID.
+        classesToFileout := classesToFileout collect:[:each | each autoload].
+    ].
+
+    classesToFileout := classesToFileout reject:[:cls | cls isSubclassOf: ProjectDefinition ].
+    classesToFileout topologicalSort:[:a :b | b isSubclassOf:a].
+
+    classesToFileout do:[:cls | 
+        cls isPrivate ifTrue:[
+            self error:'Cannot file out private class: ',cls name.
+        ].
+    ].
+
+    methodsToFileOut := projectDefinitionClass extensions.
+
+    self activityNotification:'checking for unportable unicode...'.
+
+    self fileOutHeaderOn:aStream.
+    self fileOutClasses: classesToFileout on: aStream.
+    self fileOutExtensions: methodsToFileOut on: aStream.
+    self fileOutFooterOn: aStream.
+
+    "Created: / 14-04-2015 / 13:42:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 03-11-2015 / 23:05:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutClasses:arg1 on:arg2
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+fileOutExtensions:arg1 on:arg2
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+fileOutFooterOn:aStresm
+
+    "Created: / 03-11-2015 / 23:05:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutHeaderOn:arg
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BeeSourceWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,230 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Smalltalk }"
+
+SmalltalkChunkFileSourceWriter subclass:#BeeSourceWriter
+	instanceVariableNames:'timestamp'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes-Support'
+!
+
+!BeeSourceWriter class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!BeeSourceWriter class methodsFor:'simple API'!
+
+fileOut:aClass on:aStream
+    self fileOut:aClass on:aStream withTimeStamp:false
+        withInitialize:true withDefinition:true
+        methodFilter:nil encoder:nil
+
+    "Created: / 14-04-2015 / 13:12:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!BeeSourceWriter methodsFor:'source writing'!
+
+fileOut:aClass on:outStreamArg withTimeStamp:stampIt withInitialize:initIt withDefinition:withDefinition methodFilter:methodFilter encoder:encoderOrNil
+    timestamp := Timestamp now printStringFormat:'%d/%m/%y %H:%M:%S'.
+    super fileOut:aClass on:outStreamArg withTimeStamp:stampIt withInitialize:initIt withDefinition:withDefinition methodFilter:methodFilter encoder:encoderOrNil
+
+    "Created: / 14-04-2015 / 12:26:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutAllDefinitionsOf:aNonMetaClass on:aStream withNameSpace: withNameSpacePragma
+    "append expressions on aStream, which defines myself and all of my private classes."
+
+
+    self fileOutDefinitionOf:aNonMetaClass on:aStream withNameSpace: withNameSpacePragma.
+
+    "/ self fileOutDefinitionOf:aNonMetaClass on:aStream.
+    "/ aStream nextPutChunkSeparator. 
+    aStream cr.
+
+    "/
+    "/ optional classInstanceVariables
+    "/
+    aNonMetaClass class instanceVariableString isBlank ifFalse:[
+        self fileOutClassInstVarDefinitionOf:aNonMetaClass on:aStream
+    ].
+
+    "/ here, the full nameSpace prefixes are output,
+    "/ to avoid confusing stc 
+    "/ (which otherwise could not find the correct superclass)
+    "/
+    Class fileOutNameSpaceQuerySignal answer:false do:[
+        Class forceNoNameSpaceQuerySignal answer:true do:[
+            aNonMetaClass privateClassesSorted do:[:aClass |
+                 self fileOutAllDefinitionsOf:aClass on:aStream withNameSpace: false
+            ]
+        ]
+    ].
+
+    "Created: / 14-04-2015 / 13:02:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutCategory:aCategory of:aClass except:skippedMethods only:savedMethods methodFilter:methodFilter on:aStream
+    "file out all methods belonging to aCategory, aString onto aStream.
+     If skippedMethods is nonNil, those are not saved.
+     If savedMethods is nonNil, only those are saved.
+     If both are nil, all are saved. See version-method handling in
+     fileOut for what this is needed."
+
+    |sortedSelectors interestingMethods prjDef|
+
+    interestingMethods := OrderedCollection new.
+    aClass methodsDo:[:each |
+        | wanted method shadowed |
+
+        method := each.
+        (methodsAlreadySaved includes:method) ifFalse:[
+            (aCategory = method category) ifTrue:[
+                wanted := methodFilter isNil or:[methodFilter value:method].
+                wanted ifFalse:[ 
+                    "/ care for methods which have been shadowed by an extension from another package!!
+                    "/ The problem is that we cannot easily introspect the filter, so we cannot know
+                    "/ if the filter is for package or not. In most (all?) cases it is as this method
+                    "/ is mostly used by source code management, so if the filter filters method out,
+                    "/ try afain for possibly shadowed method.
+                    methodFilter notNil ifTrue:[ 
+                        shadowed := method shadowedMethod.
+                        shadowed notNil ifTrue:[ 
+                            wanted := methodFilter value: shadowed.
+                        ].
+                    ].
+                ].
+                wanted ifTrue:[
+                    skippedMethods notNil ifTrue:[
+                        wanted := (skippedMethods includesIdentical:method) not
+                    ] ifFalse:[
+                        wanted := savedMethods isNil or:[ savedMethods includesIdentical:method ].
+                    ].
+                    wanted ifTrue:[
+                        (method selector isSymbol) ifTrue:[
+                            interestingMethods add:method
+                        ] ifFalse:[
+                            Transcript showCR:'skipping non-symbol method ', method selector printString.
+                        ].
+                    ].
+                ]
+            ]
+        ]
+    ].
+
+    interestingMethods notEmpty ifTrue:[
+        "/
+        "/ sort by selector
+        "/
+        sortedSelectors := interestingMethods collect:[:m | aClass selectorAtMethod:m].
+        sortedSelectors sortWith:interestingMethods.
+
+        generatingSourceForOriginal == true ifTrue:[
+            "/ care for methods which have been shadowed by an extension from another package!!
+            (prjDef := aClass theNonMetaclass projectDefinitionClass) notNil ifTrue:[
+                prjDef hasSavedOverwrittenMethods ifTrue:[
+                    interestingMethods := interestingMethods collect:[:m |
+                                                |originalOrNil|
+                                                
+                                                (m package ~~ aClass package) ifTrue:[ 
+                                                    originalOrNil := prjDef savedOverwrittenMethodForClass:aClass selector:m selector.
+                                                    originalOrNil notNil ifTrue:[ 
+                                                        1.
+                                                        self breakPoint:#cg 
+                                                    ].
+                                                ].
+                                                originalOrNil ? m
+                                          ].
+                ]
+            ].
+        ].
+
+        interestingMethods do:[:eachMethod |
+            self fileOutMethod:eachMethod on:aStream.
+            methodsAlreadySaved add:eachMethod.
+        ].
+    ].
+
+    "Created: / 14-04-2015 / 13:05:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-04-2015 / 14:31:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutDefinitionOf:aNonMetaClass on:aStream withNameSpace: withNameSpacePragma
+    aStream nextPutAll: '!!ClassDefinition timeStamp:'; nextPutAll: timestamp storeString; nextPutAll: ' author: nil className: '; nextPutAll: aNonMetaClass name storeString; nextPutAll: '!!'.
+    aStream cr; cr.       
+    aNonMetaClass basicFileOutDefinitionOn:aStream withNameSpace: false withPackage: false.
+    aStream nextPut: $!!; cr.
+
+    "Created: / 14-04-2015 / 12:39:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutMethod:aMethod on:aStream
+    "file a single method onto aStream."
+
+    |source possiblyRewrittenSource rewriteQuery|
+
+    source := aMethod source asSingleByteStringIfPossible.
+    source isNil ifTrue:[
+        Class fileOutErrorSignal 
+            raiseRequestWith:aMethod mclass
+            errorString:' - no source for method: ', (aMethod displayString)
+    ] ifFalse:[
+        "/ hook to allow for just-in-time rewriting of a method's sourceCode while filing out
+        "/ used when saving version_XXX methods in a non-XXX sourceCodeManager
+        "/ (i.e. to rewrite all non-CVS version methods while saving into a CVS repository)
+        "/ this is required because we cannot save an SVN version method (dollar-ID-...-dollar) into a
+        "/ CVS repository without loosing the original string with the next checkout, because it also gets  
+        "/ expanded by CVS. The same is true vice-versa for CVS-Ids, which get clobbered by SVN.
+        "/ also used, when generating sourcecode for another Smalltalk system (VSE fileout)
+
+        rewriteQuery := AbstractSourceFileWriter methodSourceRewriteQuery new.
+        rewriteQuery method:aMethod source:source.
+        possiblyRewrittenSource := (rewriteQuery query) ? source.
+
+        aStream nextPutAll: '!!MethodDefinition timeStamp:'; nextPutAll: timestamp storeString; 
+                nextPutAll: ' author: ';    nextPutAll: 'Unknown' storeString;
+                nextPutAll: ' className: '; nextPutAll: aMethod mclass name storeString; 
+                nextPutAll: ' selector: ';  nextPutAll: aMethod selector storeString; 
+                nextPutAll: ' category: ';  nextPutAll: aMethod category storeString; 
+                nextPutAll: '!!'.
+        aStream cr.
+        aStream nextChunkPut:possiblyRewrittenSource.
+        aStream cr.
+    ].
+
+    "Created: / 14-04-2015 / 12:41:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-04-2015 / 14:48:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+fileOutMethods: methods on: stream
+
+    methods do:[:method| 
+        self fileOutMethod: method on: stream.
+    ]
+
+    "Created: / 14-04-2015 / 12:41:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/CVSSourceCodeManager.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/CVSSourceCodeManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -347,6 +347,15 @@
             ]
         ].
     ].
+!
+
+validateWorkingCopy: path
+    "Return true, if given path is a valid working 
+     copy of this manager; false otherwise."
+
+    ^ (path asFilename / 'CVS') isDirectory and:[ (path asFilename / 'CVS' / 'Root') exists ]
+
+    "Created: / 02-10-2015 / 09:59:04 / jv"
 ! !
 
 !CVSSourceCodeManager class methodsFor:'accessing'!
--- a/CallChain.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/CallChain.st	Fri Jul 29 06:57:08 2016 +0200
@@ -227,9 +227,19 @@
 !CallChain class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/CallChain.st,v 1.14 2010-07-04 08:06:27 cg Exp $'
+    ^ '$Header: CallChain.st 1909 2012-03-31 00:14:49Z vranyj1 $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/CallChain.st,v 1.14 2010-07-04 08:06:27 cg Exp $'
+    ^ 'งHeader: /cvs/stx/stx/libbasic3/CallChain.st,v 1.14 2010/07/04 08:06:27 cg Exp ง'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: CallChain.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/Change.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/Change.st	Fri Jul 29 06:57:08 2016 +0200
@@ -64,8 +64,8 @@
 
     source1 := source1 withoutTrailingSeparators asCollectionOfLines.
     source2 := source2 withoutTrailingSeparators asCollectionOfLines.
-    [source1 last isEmptyOrNil] whileTrue:[ source1 removeLast ].
-    [source2 last isEmptyOrNil] whileTrue:[ source2 removeLast ].
+    [source1 notEmptyOrNil and:[ source1 last isEmptyOrNil]] whileTrue:[ source1 removeLast ].
+    [source2 notEmptyOrNil and:[ source2 last isEmptyOrNil]] whileTrue:[ source2 removeLast ].
 
     source1 size ~~ source2 size ifTrue:[^ false].
     source1 = source2 ifTrue:[^ true].
@@ -82,6 +82,7 @@
     ^ false.
 
     "Created: / 25-07-2006 / 11:22:21 / cg"
+    "Modified: / 21-05-2015 / 13:30:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Change methodsFor:'accessing'!
@@ -130,6 +131,7 @@
 !
 
 delta
+    <resource: #obsolete>
     "Returns a delta to current state as symbol:
         #+ .....the subject is to be added to the image (new)
         #- .....the subject is to be removed from the image (old)
@@ -138,10 +140,10 @@
         #? .....delta is unknown or N/A for this kind of change
     "
 
-    "/ obsolete: please use deltaDetail
-    ^#? "We don't know how to compute delta for generic change"
+    ^ self deltaDetail shortDeltaSymbol
 
     "Modified (comment): / 31-08-2011 / 10:29:47 / cg"
+    "Modified: / 23-04-2015 / 10:38:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 deltaDetail
@@ -572,6 +574,11 @@
 version_CVS
     ^ '$Header$'
 !
+    
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
 
 version_SVN
     ^ '$Id$'
--- a/ChangeDeltaInformation.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ChangeDeltaInformation.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#ChangeDeltaInformation
 	instanceVariableNames:'shortDeltaSymbol'
 	classVariableNames:'Unknown Identical Different Added Removed IdenticalButWhiteSpace
@@ -205,6 +207,19 @@
     "Created: / 31-08-2011 / 10:39:05 / cg"
 ! !
 
+!ChangeDeltaInformation methodsFor:'printing & storing'!
+
+printOn:aStream
+    "append a printed representation if the receiver to the argument, aStream"
+
+    super printOn:aStream.
+    aStream nextPut:$(.
+    shortDeltaSymbol printOn:aStream.
+    aStream nextPut:$).
+
+    "Modified: / 23-04-2015 / 08:50:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !ChangeDeltaInformation class methodsFor:'documentation'!
 
 version
@@ -213,6 +228,11 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/ChangeDeltaInformation.st,v 1.4 2014-12-11 20:47:41 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/ChangeSet.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ChangeSet.st	Fri Jul 29 06:57:08 2016 +0200
@@ -837,13 +837,13 @@
      The lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
-    |encodedStream chunk s change currentNameSpace currentPackage
+    |encodedStream chunk s change currentNameSpace currentPackage defaultPackage
      lineNumber pos reader reportProgress size |
 
     aStream isNil ifTrue:[^ self].
 
     currentNameSpace := Smalltalk.
-    currentPackage := Class packageQuerySignal query.
+    currentPackage := defaultPackage := Class packageQuerySignal query.
 
     (reader := aReader) isNil ifTrue:[
         reader := ChangeFileReader new.
@@ -934,6 +934,12 @@
                             tree isLiteral ifTrue:[
                                 (s := tree evaluate) isString ifTrue:[
                                     (s startsWith:'---- ') ifTrue:[
+                                        (s startsWith:'---- timestamp') ifTrue:[ 
+                                            "/ Beginning of next record in changelog. Reset all
+                                            "/ previously set namespaces and packages
+                                            currentPackage := defaultPackage.
+                                            currentNameSpace := Smalltalk.
+                                        ]. 
                                         reader inputStream: s readStream.
                                         reader processInfo: s.
                                         reader inputStream: encodedStream.
@@ -973,7 +979,7 @@
 
     "Created: / 16-02-1998 / 12:19:34 / cg"
     "Modified: / 30-07-2013 / 21:34:16 / cg"
-    "Modified: / 14-03-2014 / 16:39:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 26-04-2016 / 22:52:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ChangeSet class methodsFor:'queries'!
@@ -3992,15 +3998,24 @@
 !ChangeSet::ClassSourceWriter methodsFor:'source writing'!
 
 fileOut:aChangeSet on:outStreamArg
+    |encoder any16Bit|
+
+    any16Bit := aChangeSet contains:[:chg | |src| src := chg source. src notNil and:[src isWideString and:[ src contains: [:c | c codePoint > 16rFF ] ] ] ].
+    any16Bit ifTrue:[
+        encoder := CharacterEncoder encoderForUTF8.
+    ].          
+
+
     ^ self
-	fileOut: aChangeSet
-	on:outStreamArg
-	withTimeStamp:false
-	withInitialize:true
-	withDefinition:true
-	methodFilter:nil encoder:nil.
+        fileOut: aChangeSet
+        on:outStreamArg
+        withTimeStamp:false
+        withInitialize:true
+        withDefinition:true
+        methodFilter:nil encoder:encoder.
 
     "Created: / 04-02-2014 / 18:36:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-04-2015 / 21:27:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileOut:aChangeSet on:outStreamArg withTimeStamp:stampIt withInitialize:initIt withDefinition:withDefinition methodFilter:methodFilter encoder:encoderOrNil
@@ -4019,7 +4034,7 @@
         outStream := outStreamArg.
     ] ifFalse:[
         outStream := EncodedStream stream:outStreamArg encoder:encoderOrNil.
-        outStream nextPutAll:'"{ Encoding: ' , encoderOrNil nameOfEncoding , ' }"'; cr; cr.
+        outStream nextPutAll:'"{ Encoding: '; nextPutAll: encoderOrNil nameOfEncoding; nextPutAll: ' }"'; cr; cr.
     ].
 
     "/ Just a bunch of extensions?
@@ -4147,7 +4162,6 @@
 "/            self fileOutCategory:m category of:nonMeta except:nil only:(Array with:m) methodFilter:methodFilter on:outStream.
 "/        ].
 "/    ].
-
     "/
     "/ methods from all categories
     "/
@@ -4200,7 +4214,7 @@
     "Modified: / 01-04-1997 / 16:01:05 / stefan"
     "Modified: / 29-09-2011 / 14:53:49 / cg"
     "Created: / 15-03-2012 / 17:39:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-05-2013 / 09:17:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-04-2015 / 21:25:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileOutAllDefinitionsOf:nonMetaInfo on:aStream
@@ -4276,7 +4290,7 @@
     "Created: / 15-10-1996 / 11:15:19 / cg"
     "Modified: / 22-03-1997 / 16:11:56 / cg"
     "Created: / 15-03-2012 / 19:18:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 11-06-2013 / 22:23:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-04-2015 / 18:32:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileOutAllMethodsOf:aClass on:aStream methodFilter:methodFilter
@@ -4523,10 +4537,11 @@
 methodDictionary
     methodDictionary isEmptyOrNil ifTrue:[
         methodDictionary := Dictionary new.
-        methods do:[:m| methodDictionary at: m selector put: m].
+        self methodsDo:[:e | methodDictionary at: e selector put: e]  
     ].
 
     ^ methodDictionary.
+    "Modified: / 13-04-2015 / 19:02:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 methods
--- a/ChangeSetDiffEntry.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ChangeSetDiffEntry.st	Fri Jul 29 06:57:08 2016 +0200
@@ -279,8 +279,12 @@
     | merged |
     merged := versionMerged.
     (merged isNil and:[mergeInfo notNil]) ifTrue:[
+        | source |
+
+        source := mergeInfo text.
+        source isEmpty ifTrue:[ ^ nil ].
         merged := (versionA ? versionB ? versionBase) copy.
-        merged source: mergeInfo text.
+        merged source: source.
         merged isClassDefinitionChange ifTrue:[
             merged setupFromSource.
         ]
@@ -288,7 +292,7 @@
     ].
     ^merged
 
-    "Modified: / 21-03-2012 / 00:59:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-11-2015 / 13:19:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 versionMerged:aChange
@@ -411,6 +415,11 @@
 
 !ChangeSetDiffEntry class methodsFor:'documentation'!
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_CVS
     ^ '$Header$'
 !
--- a/ClassClassVariableChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassClassVariableChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#ClassClassVariableChange
 	instanceVariableNames:'variableName otherParameters'
 	classVariableNames:''
@@ -76,5 +78,10 @@
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/ClassClassVariableChange.st,v 1.5 2014-02-05 17:52:03 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/ClassDefinitionChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassDefinitionChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -100,38 +100,16 @@
     classVariableString := aString.
 !
 
-delta
-    | changeClass changeSource imageSource  |
-
-
-    changeClass := self changeClass.
-    changeClass isNil ifTrue:[^#+].
-    changeSource := self definitionString.
-    imageSource := self isPrivateClassDefinitionChange 
-                    ifTrue:[changeClass definition]
-                    ifFalse:[changeClass definitionWithoutPackage].
-
-    ^ (self class isSource: changeSource 
-                 sameSourceAs: imageSource) ifTrue:[ #= ] ifFalse:[ #~ ].
-
-    "
-        Tools::TextDiff2Tool openOn: changeSource label: 'Change' and: imageSource label: 'Image'
-    "
-
-    "Modified: / 31-08-2011 / 09:26:48 / cg"
-    "Modified: / 04-02-2014 / 20:30:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 deltaDetail
     "Returns a delta to the current state as a ChangeDelta object"
 
-    | class mySource imageSource myTree imageTree same |
+    | class mySource imageSource myTree myClassDefTree imageTree imageClassDefTree same |
 
     class := self changeClass.
     class isNil ifTrue:[^ ChangeDeltaInformation added ].
     class isLoaded ifFalse:[^ ChangeDeltaInformation different ].
     mySource := self source.
-    imageSource := class definitionWithoutPackage "definition".
+    imageSource := self imageSource.
     same := (mySource = imageSource).
     same ifFalse:[
         same := (self class isSource: mySource sameSourceAs: imageSource ).
@@ -143,20 +121,34 @@
             same ifFalse:[
                 "/ some classDefinition strings may contain whitespace
                 "/ instVarName string like 'foo bar ' instead of 'foo bar' (i.e. added a space)...
-                ((myTree receiver = imageTree receiver)
-                    and:[ (myTree selector = imageTree selector)
-                    and:[ ('*ubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:' match: myTree selector)
-                    and:[ (myTree arguments at:1) = (imageTree arguments at:1)  
+
+                "/ Kludge for class instance variable definitions.
+                "/ In that case, myTree is not the subclass:.. message send node but 
+                "/ an sequence. In that case, make it a a subclass:... message send node
+                "/ so the following code works...
+
+                myClassDefTree := myTree isSequence 
+                                    ifTrue:[ myTree statements first] 
+                                    ifFalse:[ myTree ].
+                imageClassDefTree := imageTree isSequence 
+                                    ifTrue:[ imageTree statements first]
+                                    ifFalse:[ imageTree ].
+
+                ((myClassDefTree receiver = imageClassDefTree receiver)
+                    and:[ (myClassDefTree selector = imageClassDefTree selector)
+                    and:[ ('*ubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:' match: myClassDefTree selector)
+                    and:[ (myClassDefTree arguments at:1) = (imageClassDefTree arguments at:1)  
 
                     and:[ (2 to:5) conform:[:i |
-                            ((myTree arguments at:i) isLiteral
-                            and:[ (imageTree arguments at:i) isLiteral
-                            and:[ (myTree arguments at:i) value asString asCollectionOfWords
-                                  = (imageTree arguments at:i) value asString asCollectionOfWords ]]) ]   
+                            ((myClassDefTree arguments at:i) isLiteral
+                            and:[ (imageClassDefTree arguments at:i) isLiteral
+                            and:[ (myClassDefTree arguments at:i) value asString asCollectionOfWords
+                                  = (imageClassDefTree arguments at:i) value asString asCollectionOfWords ]]) ]   
 
                 ]]]])
                     ifTrue:[
-                        same := true
+                        same := myTree isSequence == imageTree isSequence 
+                                    and:[ myTree isSequence not or:[ myTree statements second = imageTree statements second]  ]
                     ]
             ].
         ]
@@ -167,7 +159,7 @@
         ifFalse:[ ChangeDeltaInformation different ]
 
     "Created: / 31-08-2011 / 10:26:42 / cg"
-    "Modified: / 24-01-2012 / 22:13:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-04-2015 / 11:09:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 imageSource
@@ -177,7 +169,19 @@
 
     cls := self changeClass.
     cls isNil ifTrue:[ ^ nil ].
-    ^ cls definitionWithoutPackage
+    ^ cls class instanceVariableNames isEmptyOrNil ifTrue:[ 
+        cls definitionWithoutPackage
+    ] ifFalse:[ 
+        String streamContents:[ :s|
+            s nextPutAll: cls definitionWithoutPackage trimSeparators.
+            s nextPut: $.; cr;cr.
+            s nextPutAll:cls nameWithoutNameSpacePrefix;
+              nextPutAll:' class instanceVariableNames: ';
+              nextPutAll:cls class instanceVariableString storeString.     
+        ]
+    ].
+
+    "Modified: / 15-04-2015 / 11:11:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 indexedType
@@ -459,20 +463,14 @@
 definitionString
     | ns  |
 
-
-    ns := self nameSpaceName.
-    ns isEmptyOrNil ifTrue:[
-        ^ self definitionStringInNamespace: ns.
-    ].
+    ns := (self nameSpaceName) ? 'Smalltalk'.
     ^String streamContents:[:s|
-"/        owningClassName isNil ifTrue:[
-            s nextPutAll: '"{ NameSpace: '; nextPutAll: ns; nextPutAll: ' }"'.
-            s cr; cr.
-"/        ].
+        s nextPutAll: '"{ NameSpace: '; nextPutAll: ns;  nextPutAll: ' }"'.
+        s cr; cr.
         s nextPutAll: (self definitionStringInNamespace: ns).
     ]
 
-    "Modified: / 13-11-2013 / 17:40:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 13-04-2015 / 18:23:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 definitionStringInNamespace: nsOrNil
@@ -554,17 +552,15 @@
         ].
 
         classInstanceVariableString notEmptyOrNil ifTrue:[
-            stream nextPut:$.; cr;
-                   nextPutAll:'"'; 
+            stream nextPut:$.; cr; cr;
                    nextPutAll:classNameUsed; 
                    nextPutAll:' class instanceVariableNames: ';
-                   nextPutAll:classInstanceVariableString storeString; 
-                   nextPutAll:'"' 
+                   nextPutAll:classInstanceVariableString storeString. 
         ].
       ]
 
     "Modified: / 13-06-2012 / 13:01:58 / cg"
-    "Modified: / 13-11-2013 / 17:13:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-04-2015 / 10:30:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 definitionStringWithoutNamespace
--- a/ClassInitializeChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassInitializeChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#ClassInitializeChange
 	instanceVariableNames:''
 	classVariableNames:''
@@ -9,6 +22,20 @@
 
 !ClassInitializeChange class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     Change for class initialization chunk. Unlike DoItChange, 
--- a/ClassInstVarDefinitionChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassInstVarDefinitionChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#ClassInstVarDefinitionChange
 	instanceVariableNames:'classInstVarNames'
 	classVariableNames:''
@@ -45,21 +47,17 @@
     classInstVarNames := something.
 !
 
-delta
-    | ns changeClass |
+deltaDetail
+    "Returns a delta to the current state as a ChangeDelta object"
+    | class |
 
-    "/ Must enforce current namespace because caller (such as Workspace!!!!!!) enforces
-    "/ the namespace wia NameSpaceQuerySignal. Therefore for classes not in Smalltalk.
-    "/ `self changeClass` will always return nil, sigh.
-    ns := nameSpaceName notNil ifTrue:[(NameSpace name: nameSpaceName)] ifFalse:[nil].
-    Class nameSpaceQuerySignal answer: nil do:[
-        changeClass := self changeClass.
-        changeClass isNil ifTrue:[^#+].
-    ].
+    class := self changeClass.
+    class isNil ifTrue:[^ ChangeDeltaInformation added ].
+    class isLoaded ifFalse:[^ ChangeDeltaInformation different ].
+    class instanceVariableNames = classInstVarNames ifTrue:[ ^ ChangeDeltaInformation identical ].
+    ^ ChangeDeltaInformation different
 
-    ^ self classInstVarNames = changeClass instanceVariableNames ifTrue:[#'='] ifFalse:[#'~']
-
-    "Created: / 13-11-2013 / 17:58:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 25-04-2015 / 22:22:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ClassInstVarDefinitionChange methodsFor:'comparing'!
@@ -112,5 +110,10 @@
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/ClassInstVarDefinitionChange.st,v 1.10 2014-12-29 20:35:51 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/ClassOrganizer.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassOrganizer.st	Fri Jul 29 06:57:08 2016 +0200
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic3' }"
 
 Object subclass:#ClassOrganizer
@@ -87,6 +86,7 @@
     ^ 'as yet unspecified'
 ! !
 
+
 !ClassOrganizer methodsFor:'accessing'!
 
 addCategory:aCategory
@@ -333,5 +333,15 @@
 !ClassOrganizer class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/ClassOrganizer.st,v 1.21 2006-08-21 10:14:53 cg Exp $'
+    ^ '$Header: ClassOrganizer.st 1909 2012-03-31 00:14:49Z vranyj1 $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: ClassOrganizer.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/ClassOtherChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassOtherChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -76,5 +76,15 @@
 !ClassOtherChange class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/ClassOtherChange.st,v 1.6 2009-09-24 08:41:51 cg Exp $'
+    ^ '$Header: ClassOtherChange.st 1909 2012-03-31 00:14:49Z vranyj1 $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: ClassOtherChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/ClassRemoveChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ClassRemoveChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#ClassRemoveChange
 	instanceVariableNames:''
 	classVariableNames:''
@@ -52,6 +54,20 @@
 "
 ! !
 
+!ClassRemoveChange methodsFor:'accessing'!
+
+deltaDetail
+    "Returns a delta to the current state as a ChangeDelta object"
+
+    ^ self changeClass isNil ifTrue:[ 
+        ChangeDeltaInformation identical.        
+    ] ifFalse:[ 
+        ChangeDeltaInformation removed.
+    ].
+
+    "Created: / 15-04-2015 / 11:16:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !ClassRemoveChange methodsFor:'printing'!
 
 printOn:aStream
@@ -62,16 +78,6 @@
     "Modified: / 13-11-2006 / 10:40:17 / cg"
 ! !
 
-!ClassRemoveChange methodsFor:'queries'!
-
-delta
-    | class |
-
-    class := self changeClass.
-    class notNil ifTrue:[^#-].
-    ^ #=
-! !
-
 !ClassRemoveChange methodsFor:'testing'!
 
 isClassRemoveChange
@@ -82,5 +88,10 @@
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/ClassRemoveChange.st,v 1.8 2014-02-19 13:05:21 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/DataBaseSourceCodeManagerUtilities.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/DataBaseSourceCodeManagerUtilities.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 SourceCodeManagerUtilities subclass:#DataBaseSourceCodeManagerUtilities
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,6 +20,21 @@
 	category:'System-SourceCodeManagement'
 !
 
+!DataBaseSourceCodeManagerUtilities class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !DataBaseSourceCodeManagerUtilities class methodsFor:'documentation'!
 
--- a/HTMLDocGenerator.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/HTMLDocGenerator.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1711,7 +1711,7 @@
                                  '>' , methodSpecLine , '</a>'.
         self generateJavaScriptCallInfo ifTrue:[
             |jsMethodSpecLine|
-            aStream nextPutLine:'<br>JS: ' , (HTMLDocGeneratorForJavaScript htmlForMethod:aMethod).
+            aStream nextPutLine:'<br>JS: ' , ((Smalltalk at: #HTMLDocGeneratorForJavaScript) htmlForMethod:aMethod).
         ].
     ].
     aStream nextPutLine:'<DD>'.
@@ -1830,6 +1830,7 @@
 
     "Created: / 22-04-1996 / 20:03:30 / cg"
     "Modified: / 08-08-2011 / 18:54:10 / cg"
+    "Modified: / 25-09-2015 / 07:42:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 printOutHTMLProtocolOf:aClass on:aStream 
--- a/InfoChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/InfoChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -52,6 +52,7 @@
 "
 ! !
 
+
 !InfoChange class methodsFor:'instance creation'!
 
 type: type data: data timestamp: timestamp
@@ -64,6 +65,7 @@
     "Created: / 18-05-2012 / 16:59:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !InfoChange methodsFor:'accessing'!
 
 data
@@ -74,6 +76,7 @@
     data := something.
 ! !
 
+
 !InfoChange methodsFor:'applying'!
 
 apply
@@ -82,6 +85,7 @@
     "Created: / 18-05-2012 / 17:00:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !InfoChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -107,6 +111,7 @@
     "Created: / 18-05-2012 / 17:02:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !InfoChange class methodsFor:'documentation'!
 
 version
@@ -117,6 +122,11 @@
     ^ '$Header: /cvs/stx/stx/libbasic3/InfoChange.st,v 1.2 2013-04-02 19:20:25 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ 'งId:: InfoChange.st 1942 2012-07-27 14:53:23Z vranyj1                                                                        ง'
 ! !
--- a/InvalidChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/InvalidChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -41,6 +41,7 @@
 "
 ! !
 
+
 !InvalidChange methodsFor:'applying'!
 
 apply
@@ -49,6 +50,7 @@
     "Modified: / 24-01-2012 / 16:50:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !InvalidChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -59,6 +61,7 @@
     "Modified: / 24-01-2012 / 16:51:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !InvalidChange class methodsFor:'documentation'!
 
 version
@@ -67,5 +70,14 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/InvalidChange.st,v 1.3 2013-03-06 17:09:34 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: InvalidChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
 
--- a/Make.proto	Thu Jul 28 15:03:23 2016 +0200
+++ b/Make.proto	Fri Jul 29 06:57:08 2016 +0200
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/libbasic3/Make.proto,v 1.146 2015-01-27 20:35:44 cg Exp $
+# $Header$
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_libbasic3.
@@ -63,7 +63,14 @@
 
 all:: preMake classLibRule postMake
 
-pre_objs::  
+pre_objs:: stx_libbasic3-config.h 
+
+
+stx_libbasic3-config.h: stx_libbasic3-config.sh
+	./stx_libbasic3-config.sh
+
+clean::
+	rm -f stx_libbasic3-config.h
 
 
 
@@ -85,13 +92,20 @@
 		sed -e "s/\"\$$SVN\-Revision:\".*\"\$$\"/\"\$$SVN-Revision:\"\'$$rev2\'\"\$$\"/g" $< > .stx_libbasic3.svn.st; \
 	fi
 	$(MAKE) CC="$(CLASSLIB_CC)" OPT="$(OPT)" SEPINITCODE="$(SEPINITCODE)" STC="$(STC)" STFILE=.stx_libbasic3.svn $(C_RULE);
-	sed -i -e "s/\".stx_libbasic3.svn.st\");/\"\stx_libbasic3.st\");/g" .stx_libbasic3.svn.c
+	sed -i -e "s/\".stx_libbasic3.svn.st\");/\"stx_libbasic3.st\");/g" .stx_libbasic3.svn.c
 	$(MAKE) .stx_libbasic3.svn.$(O)
 	@mv .stx_libbasic3.svn.$(O) stx_libbasic3.$(O)
 endif
 
 
 
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+ifneq (**NOHG**, $(shell hg root 2> /dev/null || echo -n '**NOHG**'))
+stx_libbasic3.$(O): $(shell hg root)/.hg/dirstate
+endif
+
 
 
 
@@ -116,7 +130,7 @@
 
 # build all mandatory prerequisite packages (containing superclasses) for this package
 prereq:
-	cd ../libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd ../libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 
 
 
@@ -136,79 +150,84 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
-$(OUTDIR)AbstractSourceCodeManager.$(O) AbstractSourceCodeManager.$(H): AbstractSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)CallChain.$(O) CallChain.$(H): CallChain.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)Change.$(O) Change.$(H): Change.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
-$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)HTMLDocGenerator.$(O) HTMLDocGenerator.$(H): HTMLDocGenerator.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)HistoryManager.$(O) HistoryManager.$(H): HistoryManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MessageTally.$(O) MessageTally.$(H): MessageTally.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MessageTracer.$(O) MessageTracer.$(H): MessageTracer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MethodFinder.$(O) MethodFinder.$(H): MethodFinder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ProfileTree.$(O) ProfileTree.$(H): ProfileTree.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ProjectChecker.$(O) ProjectChecker.$(H): ProjectChecker.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ProjectProblem.$(O) ProjectProblem.$(H): ProjectProblem.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeCache.$(O) SourceCodeCache.$(H): SourceCodeCache.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerError.$(O) SourceCodeManagerError.$(H): SourceCodeManagerError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilities.$(O) SourceCodeManagerUtilities.$(H): SourceCodeManagerUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SystemEnvironment.$(O) SystemEnvironment.$(H): SystemEnvironment.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SystemOrganizer.$(O) SystemOrganizer.$(H): SystemOrganizer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)TraceBuffer.$(O) TraceBuffer.$(H): TraceBuffer.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
-$(OUTDIR)VersionInfo.$(O) VersionInfo.$(H): VersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)WrappedMethod.$(O) WrappedMethod.$(H): WrappedMethod.st $(INCLUDE_TOP)/stx/libbasic/CompiledCode.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutableFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/Method.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)stx_libbasic3.$(O) stx_libbasic3.$(H): stx_libbasic3.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)CVSSourceCodeManager.$(O) CVSSourceCodeManager.$(H): CVSSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)CVSVersionInfo.$(O) CVSVersionInfo.$(H): CVSVersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffEntry.$(O) ChangeSetDiffEntry.$(H): ChangeSetDiffEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeSetDiffComponent.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffSet.$(O) ChangeSetDiffSet.$(H): ChangeSetDiffSet.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeSetDiffComponent.$(H) $(STCHDR)
-$(OUTDIR)ClassChange.$(O) ClassChange.$(H): ClassChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)CompositeChange.$(O) CompositeChange.$(H): CompositeChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)DataBaseSourceCodeManager.$(O) DataBaseSourceCodeManager.$(H): DataBaseSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)DataBaseSourceCodeManagerUtilities.$(O) DataBaseSourceCodeManagerUtilities.$(H): DataBaseSourceCodeManagerUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)DoItChange.$(O) DoItChange.$(H): DoItChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)FileBasedSourceCodeManager.$(O) FileBasedSourceCodeManager.$(H): FileBasedSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)FileInChange.$(O) FileInChange.$(H): FileInChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)GitSourceCodeManager.$(O) GitSourceCodeManager.$(H): GitSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)InvalidChange.$(O) InvalidChange.$(H): InvalidChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)MercurialSourceCodeManager.$(O) MercurialSourceCodeManager.$(H): MercurialSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)MethodChangeNotificationParameter.$(O) MethodChangeNotificationParameter.$(H): MethodChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)NameSpaceCreationChange.$(O) NameSpaceCreationChange.$(H): NameSpaceCreationChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)OtherChange.$(O) OtherChange.$(H): OtherChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
-$(OUTDIR)PerforceSourceCodeManager.$(O) PerforceSourceCodeManager.$(H): PerforceSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)SVNVersionInfo.$(O) SVNVersionInfo.$(H): SVNVersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilitiesForContainerBasedManagers.$(O) SourceCodeManagerUtilitiesForContainerBasedManagers.$(H): SourceCodeManagerUtilitiesForContainerBasedManagers.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(O) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(H): SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)StoreSourceCodeManager.$(O) StoreSourceCodeManager.$(H): StoreSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)ClassCategoryChange.$(O) ClassCategoryChange.$(H): ClassCategoryChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassClassVariableChange.$(O) ClassClassVariableChange.$(H): ClassClassVariableChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassCommentChange.$(O) ClassCommentChange.$(H): ClassCommentChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassDefinitionChange.$(O) ClassDefinitionChange.$(H): ClassDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassInitializeChange.$(O) ClassInitializeChange.$(H): ClassInitializeChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassInstVarDefinitionChange.$(O) ClassInstVarDefinitionChange.$(H): ClassInstVarDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassOtherChange.$(O) ClassOtherChange.$(H): ClassOtherChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveChange.$(O) ClassPrimitiveChange.$(H): ClassPrimitiveChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassRemoveChange.$(O) ClassRemoveChange.$(H): ClassRemoveChange.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Query.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassRenameChange.$(O) ClassRenameChange.$(H): ClassRenameChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)InfoChange.$(O) InfoChange.$(H): InfoChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/OtherChange.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryChangeNotificationParameter.$(O) MethodCategoryChangeNotificationParameter.$(H): MethodCategoryChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryRenameChange.$(O) MethodCategoryRenameChange.$(H): MethodCategoryRenameChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)MethodChange.$(O) MethodChange.$(H): MethodChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
-$(OUTDIR)MethodRemoveChangeNotificationParameter.$(O) MethodRemoveChangeNotificationParameter.$(H): MethodRemoveChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)MethodTrapChangeNotificationParameter.$(O) MethodTrapChangeNotificationParameter.$(H): MethodTrapChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)TimestampChange.$(O) TimestampChange.$(H): TimestampChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/OtherChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveDefinitionsChange.$(O) ClassPrimitiveDefinitionsChange.$(H): ClassPrimitiveDefinitionsChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveFunctionsChange.$(O) ClassPrimitiveFunctionsChange.$(H): ClassPrimitiveFunctionsChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveVariablesChange.$(O) ClassPrimitiveVariablesChange.$(H): ClassPrimitiveVariablesChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryChange.$(O) MethodCategoryChange.$(H): MethodCategoryChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodDefinitionChange.$(O) MethodDefinitionChange.$(H): MethodDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodPackageChange.$(O) MethodPackageChange.$(H): MethodPackageChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodPrivacyChange.$(O) MethodPrivacyChange.$(H): MethodPrivacyChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodRemoveChange.$(O) MethodRemoveChange.$(H): MethodRemoveChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
+$(OUTDIR)AbstractSourceCodeManager.$(O) AbstractSourceCodeManager.$(C) AbstractSourceCodeManager.$(H): AbstractSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectWriter.$(O) BeeProjectWriter.$(C) BeeProjectWriter.$(H): BeeProjectWriter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)BeeSourceWriter.$(O) BeeSourceWriter.$(C) BeeSourceWriter.$(H): BeeSourceWriter.st $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
+$(OUTDIR)CallChain.$(O) CallChain.$(C) CallChain.$(H): CallChain.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)Change.$(O) Change.$(C) Change.$(H): Change.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(C) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(C) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)ChangeSet.$(O) ChangeSet.$(C) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(C) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(C) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(C) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HTMLDocGenerator.$(O) HTMLDocGenerator.$(C) HTMLDocGenerator.$(H): HTMLDocGenerator.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HistoryManager.$(O) HistoryManager.$(C) HistoryManager.$(H): HistoryManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MessageTally.$(O) MessageTally.$(C) MessageTally.$(H): MessageTally.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MessageTracer.$(O) MessageTracer.$(C) MessageTracer.$(H): MessageTracer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MethodFinder.$(O) MethodFinder.$(C) MethodFinder.$(H): MethodFinder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ProfileTree.$(O) ProfileTree.$(C) ProfileTree.$(H): ProfileTree.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ProjectChecker.$(O) ProjectChecker.$(C) ProjectChecker.$(H): ProjectChecker.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)ProjectProblem.$(O) ProjectProblem.$(C) ProjectProblem.$(H): ProjectProblem.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeCache.$(O) SourceCodeCache.$(C) SourceCodeCache.$(H): SourceCodeCache.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerError.$(O) SourceCodeManagerError.$(C) SourceCodeManagerError.$(H): SourceCodeManagerError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilities.$(O) SourceCodeManagerUtilities.$(C) SourceCodeManagerUtilities.$(H): SourceCodeManagerUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SystemEnvironment.$(O) SystemEnvironment.$(C) SystemEnvironment.$(H): SystemEnvironment.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SystemOrganizer.$(O) SystemOrganizer.$(C) SystemOrganizer.$(H): SystemOrganizer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SystemProfiler.$(O) SystemProfiler.$(C) SystemProfiler.$(H): SystemProfiler.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)TraceBuffer.$(O) TraceBuffer.$(C) TraceBuffer.$(H): TraceBuffer.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)VersionInfo.$(O) VersionInfo.$(C) VersionInfo.$(H): VersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)WrappedMethod.$(O) WrappedMethod.$(C) WrappedMethod.$(H): WrappedMethod.st $(INCLUDE_TOP)/stx/libbasic/CompiledCode.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutableFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/Method.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)stx_libbasic3.$(O) stx_libbasic3.$(C) stx_libbasic3.$(H): stx_libbasic3.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectDefinitionWriter.$(O) BeeProjectDefinitionWriter.$(C) BeeProjectDefinitionWriter.$(H): BeeProjectDefinitionWriter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/BeeProjectWriter.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectSourceWriter.$(O) BeeProjectSourceWriter.$(C) BeeProjectSourceWriter.$(H): BeeProjectSourceWriter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/BeeProjectWriter.$(H) $(STCHDR)
+$(OUTDIR)CVSSourceCodeManager.$(O) CVSSourceCodeManager.$(C) CVSSourceCodeManager.$(H): CVSSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)CVSVersionInfo.$(O) CVSVersionInfo.$(C) CVSVersionInfo.$(H): CVSVersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffEntry.$(O) ChangeSetDiffEntry.$(C) ChangeSetDiffEntry.$(H): ChangeSetDiffEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeSetDiffComponent.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffSet.$(O) ChangeSetDiffSet.$(C) ChangeSetDiffSet.$(H): ChangeSetDiffSet.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeSetDiffComponent.$(H) $(STCHDR)
+$(OUTDIR)ClassChange.$(O) ClassChange.$(C) ClassChange.$(H): ClassChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)CompositeChange.$(O) CompositeChange.$(C) CompositeChange.$(H): CompositeChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)DataBaseSourceCodeManager.$(O) DataBaseSourceCodeManager.$(C) DataBaseSourceCodeManager.$(H): DataBaseSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)DataBaseSourceCodeManagerUtilities.$(O) DataBaseSourceCodeManagerUtilities.$(C) DataBaseSourceCodeManagerUtilities.$(H): DataBaseSourceCodeManagerUtilities.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)DoItChange.$(O) DoItChange.$(C) DoItChange.$(H): DoItChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)FileBasedSourceCodeManager.$(O) FileBasedSourceCodeManager.$(C) FileBasedSourceCodeManager.$(H): FileBasedSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)FileInChange.$(O) FileInChange.$(C) FileInChange.$(H): FileInChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)GitSourceCodeManager.$(O) GitSourceCodeManager.$(C) GitSourceCodeManager.$(H): GitSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)InvalidChange.$(O) InvalidChange.$(C) InvalidChange.$(H): InvalidChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)MercurialSourceCodeManager.$(O) MercurialSourceCodeManager.$(C) MercurialSourceCodeManager.$(H): MercurialSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)MethodChangeNotificationParameter.$(O) MethodChangeNotificationParameter.$(C) MethodChangeNotificationParameter.$(H): MethodChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)NameSpaceCreationChange.$(O) NameSpaceCreationChange.$(C) NameSpaceCreationChange.$(H): NameSpaceCreationChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)OtherChange.$(O) OtherChange.$(C) OtherChange.$(H): OtherChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(STCHDR)
+$(OUTDIR)PerforceSourceCodeManager.$(O) PerforceSourceCodeManager.$(C) PerforceSourceCodeManager.$(H): PerforceSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)SVNVersionInfo.$(O) SVNVersionInfo.$(C) SVNVersionInfo.$(H): SVNVersionInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilitiesForContainerBasedManagers.$(O) SourceCodeManagerUtilitiesForContainerBasedManagers.$(C) SourceCodeManagerUtilitiesForContainerBasedManagers.$(H): SourceCodeManagerUtilitiesForContainerBasedManagers.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(O) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(C) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(H): SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)StoreSourceCodeManager.$(O) StoreSourceCodeManager.$(C) StoreSourceCodeManager.$(H): StoreSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)ClassCategoryChange.$(O) ClassCategoryChange.$(C) ClassCategoryChange.$(H): ClassCategoryChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassClassVariableChange.$(O) ClassClassVariableChange.$(C) ClassClassVariableChange.$(H): ClassClassVariableChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassCommentChange.$(O) ClassCommentChange.$(C) ClassCommentChange.$(H): ClassCommentChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassDefinitionChange.$(O) ClassDefinitionChange.$(C) ClassDefinitionChange.$(H): ClassDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassInitializeChange.$(O) ClassInitializeChange.$(C) ClassInitializeChange.$(H): ClassInitializeChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassInstVarDefinitionChange.$(O) ClassInstVarDefinitionChange.$(C) ClassInstVarDefinitionChange.$(H): ClassInstVarDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassOtherChange.$(O) ClassOtherChange.$(C) ClassOtherChange.$(H): ClassOtherChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveChange.$(O) ClassPrimitiveChange.$(C) ClassPrimitiveChange.$(H): ClassPrimitiveChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassRemoveChange.$(O) ClassRemoveChange.$(C) ClassRemoveChange.$(H): ClassRemoveChange.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Query.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassRenameChange.$(O) ClassRenameChange.$(C) ClassRenameChange.$(H): ClassRenameChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)InfoChange.$(O) InfoChange.$(C) InfoChange.$(H): InfoChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/OtherChange.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryChangeNotificationParameter.$(O) MethodCategoryChangeNotificationParameter.$(C) MethodCategoryChangeNotificationParameter.$(H): MethodCategoryChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryRenameChange.$(O) MethodCategoryRenameChange.$(C) MethodCategoryRenameChange.$(H): MethodCategoryRenameChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)MethodChange.$(O) MethodChange.$(C) MethodChange.$(H): MethodChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(STCHDR)
+$(OUTDIR)MethodRemoveChangeNotificationParameter.$(O) MethodRemoveChangeNotificationParameter.$(C) MethodRemoveChangeNotificationParameter.$(H): MethodRemoveChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)MethodTrapChangeNotificationParameter.$(O) MethodTrapChangeNotificationParameter.$(C) MethodTrapChangeNotificationParameter.$(H): MethodTrapChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic3/ChangeNotificationParameter.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)TimestampChange.$(O) TimestampChange.$(C) TimestampChange.$(H): TimestampChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/OtherChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveDefinitionsChange.$(O) ClassPrimitiveDefinitionsChange.$(C) ClassPrimitiveDefinitionsChange.$(H): ClassPrimitiveDefinitionsChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveFunctionsChange.$(O) ClassPrimitiveFunctionsChange.$(C) ClassPrimitiveFunctionsChange.$(H): ClassPrimitiveFunctionsChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveVariablesChange.$(O) ClassPrimitiveVariablesChange.$(C) ClassPrimitiveVariablesChange.$(H): ClassPrimitiveVariablesChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryChange.$(O) MethodCategoryChange.$(C) MethodCategoryChange.$(H): MethodCategoryChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodDefinitionChange.$(O) MethodDefinitionChange.$(C) MethodDefinitionChange.$(H): MethodDefinitionChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodPackageChange.$(O) MethodPackageChange.$(C) MethodPackageChange.$(H): MethodPackageChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodPrivacyChange.$(O) MethodPrivacyChange.$(C) MethodPrivacyChange.$(H): MethodPrivacyChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodRemoveChange.$(O) MethodRemoveChange.$(C) MethodRemoveChange.$(H): MethodRemoveChange.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/ClassChange.$(H) $(INCLUDE_TOP)/stx/libbasic3/MethodChange.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/CompiledCode.$(H) $(INCLUDE_TOP)/stx/libbasic/ConfigurableFeatures.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutableFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/UserPreferences.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/Make.spec	Thu Jul 28 15:03:23 2016 +0200
+++ b/Make.spec	Fri Jul 29 06:57:08 2016 +0200
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/libbasic3/Make.spec,v 1.97 2015-01-27 20:35:39 cg Exp $
+# $Header$
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_libbasic3.
@@ -52,6 +52,8 @@
 
 COMMON_CLASSES= \
 	AbstractSourceCodeManager \
+	BeeProjectWriter \
+	BeeSourceWriter \
 	CallChain \
 	Change \
 	ChangeDeltaInformation \
@@ -73,10 +75,13 @@
 	SourceCodeManagerUtilities \
 	SystemEnvironment \
 	SystemOrganizer \
+	SystemProfiler \
 	TraceBuffer \
 	VersionInfo \
 	WrappedMethod \
 	stx_libbasic3 \
+	BeeProjectDefinitionWriter \
+	BeeProjectSourceWriter \
 	CVSSourceCodeManager \
 	CVSVersionInfo \
 	ChangeSetDiffEntry \
@@ -130,6 +135,8 @@
 
 COMMON_OBJS= \
     $(OUTDIR_SLASH)AbstractSourceCodeManager.$(O) \
+    $(OUTDIR_SLASH)BeeProjectWriter.$(O) \
+    $(OUTDIR_SLASH)BeeSourceWriter.$(O) \
     $(OUTDIR_SLASH)CallChain.$(O) \
     $(OUTDIR_SLASH)Change.$(O) \
     $(OUTDIR_SLASH)ChangeDeltaInformation.$(O) \
@@ -151,10 +158,13 @@
     $(OUTDIR_SLASH)SourceCodeManagerUtilities.$(O) \
     $(OUTDIR_SLASH)SystemEnvironment.$(O) \
     $(OUTDIR_SLASH)SystemOrganizer.$(O) \
+    $(OUTDIR_SLASH)SystemProfiler.$(O) \
     $(OUTDIR_SLASH)TraceBuffer.$(O) \
     $(OUTDIR_SLASH)VersionInfo.$(O) \
     $(OUTDIR_SLASH)WrappedMethod.$(O) \
     $(OUTDIR_SLASH)stx_libbasic3.$(O) \
+    $(OUTDIR_SLASH)BeeProjectDefinitionWriter.$(O) \
+    $(OUTDIR_SLASH)BeeProjectSourceWriter.$(O) \
     $(OUTDIR_SLASH)CVSSourceCodeManager.$(O) \
     $(OUTDIR_SLASH)CVSVersionInfo.$(O) \
     $(OUTDIR_SLASH)ChangeSetDiffEntry.$(O) \
--- a/MessageTally.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MessageTally.st	Fri Jul 29 06:57:08 2016 +0200
@@ -164,6 +164,7 @@
 "
 ! !
 
+
 !MessageTally class methodsFor:'constants'!
 
 detailedSamplingIntervalMS
@@ -174,6 +175,7 @@
     ^ 10
 ! !
 
+
 !MessageTally class methodsFor:'spying-private'!
 
 spyLeafOn:aBlock interval:ms to:outStream
@@ -220,6 +222,7 @@
     "Modified: 22.3.1997 / 16:54:36 / cg"
 ! !
 
+
 !MessageTally class methodsFor:'spying-public interface'!
 
 spyDetailedOn:aBlock
@@ -262,6 +265,7 @@
     "Modified: 22.3.1997 / 16:26:51 / cg"
 ! !
 
+
 !MessageTally methodsFor:'accessing'!
 
 endTime
@@ -307,6 +311,7 @@
     "Modified: 18.5.1996 / 18:47:57 / cg"
 ! !
 
+
 !MessageTally methodsFor:'printing & storing'!
 
 printFlatMethodLeafsOn:aStream
@@ -430,6 +435,7 @@
     "Created: 22.3.1997 / 16:53:23 / cg"
 ! !
 
+
 !MessageTally methodsFor:'private'!
 
 execute
@@ -441,6 +447,7 @@
     "Modified: 20.3.1997 / 21:36:27 / cg"
 ! !
 
+
 !MessageTally methodsFor:'probing'!
 
 count:aContext
@@ -525,6 +532,7 @@
     "Modified: / 04-07-2010 / 09:47:06 / cg"
 ! !
 
+
 !MessageTally methodsFor:'spy setup'!
 
 spyLeafOn:aBlock interval:ms
@@ -637,6 +645,7 @@
     "Modified: 22.3.1997 / 16:45:42 / cg"
 ! !
 
+
 !MessageTally class methodsFor:'documentation'!
 
 version
@@ -645,5 +654,14 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'Id: MessageTally.st 1981 2012-11-30 17:20:01Z vranyj1 '
 ! !
 
--- a/MethodCategoryChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodCategoryChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -90,6 +90,21 @@
     "Created: / 16.2.1998 / 14:14:16 / cg"
 !
 
+deltaDetail
+    "Returns a delta to the current state as a ChangeDelta object"
+
+    | mth|
+
+    mth := self changeMethod.
+    (mth notNil and:[mth category = methodCategory]) ifTrue:[
+        ^ ChangeDeltaInformation identical 
+    ].
+    ^ ChangeDeltaInformation different
+
+    "Created: / 09-10-2015 / 17:45:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-10-2015 / 16:34:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 origin
     ^ origin
 !
@@ -165,6 +180,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id$'
 ! !
--- a/MethodChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -78,11 +78,13 @@
 changeMethod
     |cls|
 
+    selector isNil ifTrue:[ ^ nil ].
     cls := self changeClass.
     (cls isNil or:[selector isNil]) ifTrue:[^ nil].
-    ^ cls compiledMethodAt:selector asSymbol 
+    ^ cls compiledMethodAt:selector asSymbol
 
-    "Created: / 7.2.1998 / 19:47:53 / cg"
+    "Created: / 07-02-1998 / 19:47:53 / cg"
+    "Modified: / 14-07-2014 / 09:43:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 changeSelector
@@ -139,21 +141,6 @@
     "Modified: / 16.2.1998 / 14:28:12 / cg"
 !
 
-delta
-    "/ obsolete: please use deltaDetail
-
-    | mth |
-
-    self isMethodCodeChange ifFalse:[^super delta].
-    mth := self changeMethod.
-    mth isNil ifTrue:[^#+].
-    ^(self class isSource: self source sameSourceAs: mth source)
-        ifTrue:[#=]
-        ifFalse:[#~]
-
-    "Modified: / 18-11-2011 / 14:48:50 / cg"
-!
-
 deltaDetail
     "Returns a delta to the current state as a ChangeDelta object"
 
@@ -459,6 +446,7 @@
     "Created: / 09-10-2006 / 13:58:09 / cg"
 ! !
 
+
 !MethodChange methodsFor:'testing'!
 
 isMethodChange
@@ -535,6 +523,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id$'
 ! !
--- a/MethodDefinitionChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodDefinitionChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -64,5 +64,14 @@
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/MethodDefinitionChange.st,v 1.5 2013-01-18 12:55:22 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: MethodDefinitionChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
 
--- a/MethodPackageChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodPackageChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -113,9 +113,19 @@
 !MethodPackageChange class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/MethodPackageChange.st,v 1.4 2010-04-14 13:40:49 cg Exp $'
+    ^ '$Header: MethodPackageChange.st 1909 2012-03-31 00:14:49Z vranyj1 $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/MethodPackageChange.st,v 1.4 2010-04-14 13:40:49 cg Exp $'
+    ^ 'งHeader: /cvs/stx/stx/libbasic3/MethodPackageChange.st,v 1.4 2010/04/14 13:40:49 cg Exp ง'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: MethodPackageChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/MethodPrivacyChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodPrivacyChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -93,9 +93,19 @@
 !MethodPrivacyChange class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/MethodPrivacyChange.st,v 1.11 2010-04-14 13:40:33 cg Exp $'
+    ^ '$Header: MethodPrivacyChange.st 1909 2012-03-31 00:14:49Z vranyj1 $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/MethodPrivacyChange.st,v 1.11 2010-04-14 13:40:33 cg Exp $'
+    ^ 'งHeader: /cvs/stx/stx/libbasic3/MethodPrivacyChange.st,v 1.11 2010/04/14 13:40:33 cg Exp ง'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: MethodPrivacyChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/MethodRemoveChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodRemoveChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 MethodChange subclass:#MethodRemoveChange
 	instanceVariableNames:''
 	classVariableNames:''
@@ -77,16 +79,6 @@
     "Created: / 16.2.1998 / 12:51:57 / cg"
 !
 
-delta
-    "/ obsolete: please use deltaDetail
-
-    ^self changeMethod 
-        ifNil:[#=]
-        ifNotNil:[#-]
-
-    "Modified (comment): / 31-08-2011 / 10:29:57 / cg"
-!
-
 deltaDetail
     "Returns a delta to the current state as a ChangeDelta object"
 
--- a/MethodRemoveChangeNotificationParameter.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/MethodRemoveChangeNotificationParameter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -61,5 +59,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/MethodRemoveChangeNotificationParameter.st,v 1.3 2015-03-20 13:17:02 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/OtherChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/OtherChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -34,6 +34,7 @@
 "
 ! !
 
+
 !OtherChange methodsFor:'accessing'!
 
 file
@@ -79,6 +80,7 @@
     type := something.
 ! !
 
+
 !OtherChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -88,18 +90,30 @@
     ].
 ! !
 
+
 !OtherChange methodsFor:'testing'!
 
 isOtherChange
     ^ true
 ! !
 
+
 !OtherChange class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/OtherChange.st,v 1.5 2012-07-31 12:23:08 vrany Exp $'
 !
 
+version_CVS
+    ^ 'งHeader: /cvs/stx/stx/libbasic3/OtherChange.st,v 1.5 2012-07-31 13:23:08 +0100 vrany Exp ง'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ 'งId: OtherChange.st 1942 2012-07-27 14:53:23Z vranyj1 ง'
 ! !
+
--- a/ProfileTree.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ProfileTree.st	Fri Jul 29 06:57:08 2016 +0200
@@ -504,5 +504,14 @@
 
 version
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'Id: ProfileTree.st 1909 2012-03-31 00:14:49Z vranyj1 '
 ! !
 
--- a/ProjectChecker.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/ProjectChecker.st	Fri Jul 29 06:57:08 2016 +0200
@@ -770,6 +770,11 @@
     ^ '$Header: /cvs/stx/stx/libbasic3/ProjectChecker.st,v 1.33 2015-02-24 23:50:29 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: ProjectChecker.st,v 1.33 2015-02-24 23:50:29 cg Exp $'
 ! !
--- a/SourceCodeManagerError.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/SourceCodeManagerError.st	Fri Jul 29 06:57:08 2016 +0200
@@ -34,9 +34,18 @@
 "
 ! !
 
-
 !SourceCodeManagerError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerError.st,v 1.3 2011-08-12 11:36:52 stefan Exp $'
+    ^ '$Header: SourceCodeManagerError.st 1909 2012-03-31 00:14:49Z vranyj1 $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: SourceCodeManagerError.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st	Fri Jul 29 06:57:08 2016 +0200
@@ -228,5 +228,14 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st,v 1.5 2013-03-27 12:02:47 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId:: SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st 1971 2012-09-27 19:37:25Z vranyj1                               ง'
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SystemProfiler.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,232 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#SystemProfiler
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'System-Profiler'
+!
+
+Object subclass:#Valgrind
+	instanceVariableNames:''
+	classVariableNames:'Instance'
+	poolDictionaries:''
+	privateIn:SystemProfiler
+!
+
+!SystemProfiler primitiveDefinitions!
+%{
+
+#include "stx_libbasic3-config.h"
+
+#ifdef HAS_VALGRIND
+# include <valgrind/valgrind.h>
+# ifdef HAS_CALLGRIND
+#  include <valgrind/callgrind.h>
+# endif
+#endif
+
+%}
+! !
+
+!SystemProfiler class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    This class exposes API for systems-being-profiled provided
+    by Valgrind (and in future maybe by some others, OProfile, CodeXL 
+    comes to mind). The APIs exposed depends on the profiler itself, 
+    so no aim for an unified API here.
+
+    Historical note: This class used to be called Profiler and
+    also served as an entrypoint for the VM's builtin bytecode-counting
+    profiler I (JV) wrote for CellStore guys back then. However, 
+    it has never been used, not even by them. For practical profiling,
+    system profiler such a Valgrind/Callgrind or AMD's CodeXL gives
+    much better insight. Thus the bytecode-counting profiler has been
+    obsoleted.
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+        http://valgrind.org/
+        http://oprofile.sourceforge.net/news/
+
+"
+! !
+
+!SystemProfiler class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    "/ For backward compatibility. See "Historical note" in #documentation
+    Profiler := self.
+
+    "Modified (comment): / 31-05-2016 / 22:16:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!SystemProfiler class methodsFor:'accessing'!
+
+valgrind
+    "Returns an interface object to control
+     valgrind profiler"
+
+    ^Valgrind theOneAndOnlyInstance
+
+    "Created: / 01-11-2012 / 22:19:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!SystemProfiler::Valgrind class methodsFor:'documentation'!
+
+documentation
+"
+    A Smalltalk interface to control callgrind profiler.
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+        Callgrind 
+            http://valgrind.org/docs/manual/cl-manual.html
+        KCachegrind
+            http://kcachegrind.sourceforge.net/html/Home.html
+
+"
+! !
+
+!SystemProfiler::Valgrind class methodsFor:'instance creation'!
+
+flushSingleton
+    "flushes the cached singleton"
+
+    Instance := nil
+
+    "
+     self flushSingleton
+    "
+!
+
+new
+    "returns a singleton"
+
+    ^ self theOneAndOnlyInstance.
+!
+
+theOneAndOnlyInstance
+    "returns a singleton"
+
+    Instance isNil ifTrue:[
+        Instance := self basicNew initialize.
+    ].
+    ^ Instance.
+! !
+
+!SystemProfiler::Valgrind methodsFor:'callgrind-instrumentation'!
+
+callgrindInstrumentationStart
+    "Turn on callgrind instrumentation"
+
+%{
+#ifdef HAS_CALLGRIND
+    CALLGRIND_START_INSTRUMENTATION;
+    RETURN ( self );
+#endif
+%}.
+    self error:'No callgrind support'
+
+    "Created: / 01-11-2012 / 22:31:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+callgrindInstrumentationStop
+    "Turn off callgrind instrumentation"
+
+%{
+#ifdef HAS_CALLGRIND
+    CALLGRIND_STOP_INSTRUMENTATION;
+    RETURN ( self );
+#endif
+%}.
+    self error:'No callgrind support'
+
+    "Created: / 01-11-2012 / 22:31:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!SystemProfiler::Valgrind methodsFor:'queries'!
+
+hasValgrindSupport
+    "Return true, if valgrind support is compiled in, false otherwise"
+%{
+#ifdef HAS_VALGRIND
+    RETURN ( true );
+#endif
+%}.
+    ^ false
+
+!
+
+hasCallgrindSupport
+    "Return true, if callgrind support is compiled in, false otherwise"
+%{
+#ifdef HAS_CALLGRIND
+    RETURN ( true );
+#endif
+%}.
+    ^ false
+
+!
+
+runningUnderValgrind
+    "Return true, if the VM is running under valgrind,
+     false otherwise"
+
+%{
+#ifdef HAS_VALGRIND
+    RETURN ( (RUNNING_ON_VALGRIND) ? true : false );
+#endif
+%}.
+    ^ false
+
+    "Created: / 01-11-2012 / 22:31:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+
+
+
+SystemProfiler initialize!
--- a/TimestampChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/TimestampChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -35,6 +35,7 @@
 "
 ! !
 
+
 !TimestampChange methodsFor:'applying'!
 
 apply
@@ -45,6 +46,7 @@
     "Created: / 06-11-2008 / 08:57:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
 
+
 !TimestampChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -54,9 +56,19 @@
     ].
 ! !
 
+
 !TimestampChange class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic3/TimestampChange.st,v 1.3 2013-03-06 17:13:40 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: TimestampChange.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
 
--- a/TraceBuffer.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/TraceBuffer.st	Fri Jul 29 06:57:08 2016 +0200
@@ -132,5 +132,15 @@
 !TraceBuffer class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/TraceBuffer.st,v 1.2 2010-12-03 09:08:31 stefan Exp $'
+    ^ 'งHeader: /cvs/stx/stx/libbasic3/TraceBuffer.st,v 1.2 2010/12/03 09:08:31 stefan Exp ง'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
+version_SVN
+    ^ 'งId: TraceBuffer.st 1909 2012-03-31 00:14:49Z vranyj1 ง'
 ! !
+
--- a/TraitClassTraitDefinitionChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/TraitClassTraitDefinitionChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#TraitClassTraitDefinitionChange
 	instanceVariableNames:'baseTrait traitComposition'
 	classVariableNames:''
--- a/TraitDefinitionChange.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/TraitDefinitionChange.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 ClassChange subclass:#TraitDefinitionChange
 	instanceVariableNames:'baseTrait traitComposition category'
 	classVariableNames:''
--- a/VSEFileSourceWriter.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/VSEFileSourceWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2015 by eXept Software AG
               All Rights Reserved
--- a/VisualAgeChunkFileSourceWriter.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/VisualAgeChunkFileSourceWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 SmalltalkChunkFileSourceWriter subclass:#VisualAgeChunkFileSourceWriter
 	instanceVariableNames:''
 	classVariableNames:''
--- a/abbrev.stc	Thu Jul 28 15:03:23 2016 +0200
+++ b/abbrev.stc	Fri Jul 29 06:57:08 2016 +0200
@@ -2,6 +2,8 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 AbstractSourceCodeManager AbstractSourceCodeManager stx:libbasic3 'System-SourceCodeManagement' 0
+BeeProjectWriter BeeProjectWriter stx:libbasic3 'Kernel-Classes-Support' 0
+BeeSourceWriter BeeSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
 CallChain CallChain stx:libbasic3 'System-Debugging-Support' 0
 Change Change stx:libbasic3 'System-Changes' 0
 ChangeDeltaInformation ChangeDeltaInformation stx:libbasic3 'System-Changes' 0
@@ -14,7 +16,7 @@
 HistoryManager HistoryManager stx:libbasic3 'System-Changes-History' 0
 MessageTally MessageTally stx:libbasic3 'System-Debugging-Support' 0
 MessageTracer MessageTracer stx:libbasic3 'System-Debugging-Support' 0
-MethodFinder MethodFinder stx:libbasic3 'Interface-MethodFinder' 0
+MethodFinder MethodFinder stx:libbasic3 'Interface-Tools' 0
 ProfileTree ProfileTree stx:libbasic3 'System-Debugging-Support' 0
 ProjectChecker ProjectChecker stx:libbasic3 'System-Support-Projects' 0
 ProjectProblem ProjectProblem stx:libbasic3 'System-Support-Projects' 0
@@ -23,11 +25,13 @@
 SourceCodeManagerUtilities SourceCodeManagerUtilities stx:libbasic3 'System-SourceCodeManagement' 0
 SystemEnvironment SystemEnvironment stx:libbasic3 'Kernel-Classes' 0
 SystemOrganizer SystemOrganizer stx:libbasic3 'Kernel-Support' 0
+SystemProfiler SystemProfiler stx:libbasic3 'System-Profiler' 0
 TraceBuffer TraceBuffer stx:libbasic3 'System-Debugging-Support' 0
-VSEFileSourceWriter VSEFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
 VersionInfo VersionInfo stx:libbasic3 'System-SourceCodeManagement' 0
 WrappedMethod WrappedMethod stx:libbasic3 'Kernel-Methods' 0
 stx_libbasic3 stx_libbasic3 stx:libbasic3 '* Projects & Packages *' 3
+BeeProjectDefinitionWriter BeeProjectDefinitionWriter stx:libbasic3 'Kernel-Classes-Support' 0
+BeeProjectSourceWriter BeeProjectSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
 CVSSourceCodeManager CVSSourceCodeManager stx:libbasic3 'System-SourceCodeManagement' 0
 CVSVersionInfo CVSVersionInfo stx:libbasic3 'System-SourceCodeManagement' 0
 ChangeSetDiffEntry ChangeSetDiffEntry stx:libbasic3 'System-Changes-Diff' 0
@@ -50,8 +54,6 @@
 SourceCodeManagerUtilitiesForContainerBasedManagers SourceCodeManagerUtilitiesForContainerBasedManagers stx:libbasic3 'System-SourceCodeManagement' 0
 SourceCodeManagerUtilitiesForWorkspaceBasedManagers SourceCodeManagerUtilitiesForWorkspaceBasedManagers stx:libbasic3 'System-SourceCodeManagement' 0
 StoreSourceCodeManager StoreSourceCodeManager stx:libbasic3 'System-SourceCodeManagement' 0
-VSEChunkFileSourceWriter VSEChunkFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
-VSEPackageFileSourceWriter VSEPackageFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
 ClassCategoryChange ClassCategoryChange stx:libbasic3 'System-Changes' 0
 ClassClassVariableChange ClassClassVariableChange stx:libbasic3 'System-Changes' 0
 ClassCommentChange ClassCommentChange stx:libbasic3 'System-Changes' 0
@@ -77,6 +79,9 @@
 MethodPackageChange MethodPackageChange stx:libbasic3 'System-Changes' 0
 MethodPrivacyChange MethodPrivacyChange stx:libbasic3 'System-Changes' 0
 MethodRemoveChange MethodRemoveChange stx:libbasic3 'System-Changes' 0
-VisualAgeChunkFileSourceWriter VisualAgeChunkFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
+TraitClassTraitDefinitionChange TraitClassTraitDefinitionChange stx:libbasic3 'System-Changes' 0
 TraitDefinitionChange TraitDefinitionChange stx:libbasic3 'System-Changes' 0
-TraitClassTraitDefinitionChange TraitClassTraitDefinitionChange stx:libbasic3 'System-Changes' 0
+VSEFileSourceWriter VSEFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
+VSEChunkFileSourceWriter VSEChunkFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
+VSEPackageFileSourceWriter VSEPackageFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
+VisualAgeChunkFileSourceWriter VisualAgeChunkFileSourceWriter stx:libbasic3 'Kernel-Classes-Support' 0
--- a/bc.mak	Thu Jul 28 15:03:23 2016 +0200
+++ b/bc.mak	Fri Jul 29 06:57:08 2016 +0200
@@ -46,7 +46,7 @@
 
 OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
 
-ALL::  classLibRule
+ALL:: stx_libbasic3-config.h classLibRule
 
 classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
 
@@ -59,6 +59,13 @@
 
 
 
+stx_libbasic3-config.h: stx_libbasic3-config.bat
+	call stx_libbasic3-config.bat
+
+clean::
+	del stx_libbasic3-config.h
+
+
 
 
 
@@ -71,79 +78,93 @@
 
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
-$(OUTDIR)AbstractSourceCodeManager.$(O) AbstractSourceCodeManager.$(H): AbstractSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)CallChain.$(O) CallChain.$(H): CallChain.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)Change.$(O) Change.$(H): Change.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
-$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)HTMLDocGenerator.$(O) HTMLDocGenerator.$(H): HTMLDocGenerator.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)HistoryManager.$(O) HistoryManager.$(H): HistoryManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MessageTally.$(O) MessageTally.$(H): MessageTally.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MessageTracer.$(O) MessageTracer.$(H): MessageTracer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MethodFinder.$(O) MethodFinder.$(H): MethodFinder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ProfileTree.$(O) ProfileTree.$(H): ProfileTree.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ProjectChecker.$(O) ProjectChecker.$(H): ProjectChecker.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ProjectProblem.$(O) ProjectProblem.$(H): ProjectProblem.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeCache.$(O) SourceCodeCache.$(H): SourceCodeCache.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerError.$(O) SourceCodeManagerError.$(H): SourceCodeManagerError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilities.$(O) SourceCodeManagerUtilities.$(H): SourceCodeManagerUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SystemEnvironment.$(O) SystemEnvironment.$(H): SystemEnvironment.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SystemOrganizer.$(O) SystemOrganizer.$(H): SystemOrganizer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)TraceBuffer.$(O) TraceBuffer.$(H): TraceBuffer.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
-$(OUTDIR)VersionInfo.$(O) VersionInfo.$(H): VersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)WrappedMethod.$(O) WrappedMethod.$(H): WrappedMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)stx_libbasic3.$(O) stx_libbasic3.$(H): stx_libbasic3.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)CVSSourceCodeManager.$(O) CVSSourceCodeManager.$(H): CVSSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)CVSVersionInfo.$(O) CVSVersionInfo.$(H): CVSVersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffEntry.$(O) ChangeSetDiffEntry.$(H): ChangeSetDiffEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeSetDiffComponent.$(H) $(STCHDR)
-$(OUTDIR)ChangeSetDiffSet.$(O) ChangeSetDiffSet.$(H): ChangeSetDiffSet.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeSetDiffComponent.$(H) $(STCHDR)
-$(OUTDIR)ClassChange.$(O) ClassChange.$(H): ClassChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)CompositeChange.$(O) CompositeChange.$(H): CompositeChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)DataBaseSourceCodeManager.$(O) DataBaseSourceCodeManager.$(H): DataBaseSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)DataBaseSourceCodeManagerUtilities.$(O) DataBaseSourceCodeManagerUtilities.$(H): DataBaseSourceCodeManagerUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)DoItChange.$(O) DoItChange.$(H): DoItChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)FileBasedSourceCodeManager.$(O) FileBasedSourceCodeManager.$(H): FileBasedSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)FileInChange.$(O) FileInChange.$(H): FileInChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)GitSourceCodeManager.$(O) GitSourceCodeManager.$(H): GitSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)InvalidChange.$(O) InvalidChange.$(H): InvalidChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)MercurialSourceCodeManager.$(O) MercurialSourceCodeManager.$(H): MercurialSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)MethodChangeNotificationParameter.$(O) MethodChangeNotificationParameter.$(H): MethodChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)NameSpaceCreationChange.$(O) NameSpaceCreationChange.$(H): NameSpaceCreationChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)OtherChange.$(O) OtherChange.$(H): OtherChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
-$(OUTDIR)PerforceSourceCodeManager.$(O) PerforceSourceCodeManager.$(H): PerforceSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)SVNVersionInfo.$(O) SVNVersionInfo.$(H): SVNVersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilitiesForContainerBasedManagers.$(O) SourceCodeManagerUtilitiesForContainerBasedManagers.$(H): SourceCodeManagerUtilitiesForContainerBasedManagers.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(O) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(H): SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
-$(OUTDIR)StoreSourceCodeManager.$(O) StoreSourceCodeManager.$(H): StoreSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
-$(OUTDIR)ClassCategoryChange.$(O) ClassCategoryChange.$(H): ClassCategoryChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassClassVariableChange.$(O) ClassClassVariableChange.$(H): ClassClassVariableChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassCommentChange.$(O) ClassCommentChange.$(H): ClassCommentChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassDefinitionChange.$(O) ClassDefinitionChange.$(H): ClassDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassInitializeChange.$(O) ClassInitializeChange.$(H): ClassInitializeChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassInstVarDefinitionChange.$(O) ClassInstVarDefinitionChange.$(H): ClassInstVarDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassOtherChange.$(O) ClassOtherChange.$(H): ClassOtherChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveChange.$(O) ClassPrimitiveChange.$(H): ClassPrimitiveChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassRemoveChange.$(O) ClassRemoveChange.$(H): ClassRemoveChange.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)ClassRenameChange.$(O) ClassRenameChange.$(H): ClassRenameChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)InfoChange.$(O) InfoChange.$(H): InfoChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\OtherChange.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryChangeNotificationParameter.$(O) MethodCategoryChangeNotificationParameter.$(H): MethodCategoryChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryRenameChange.$(O) MethodCategoryRenameChange.$(H): MethodCategoryRenameChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)MethodChange.$(O) MethodChange.$(H): MethodChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
-$(OUTDIR)MethodRemoveChangeNotificationParameter.$(O) MethodRemoveChangeNotificationParameter.$(H): MethodRemoveChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)MethodTrapChangeNotificationParameter.$(O) MethodTrapChangeNotificationParameter.$(H): MethodTrapChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
-$(OUTDIR)TimestampChange.$(O) TimestampChange.$(H): TimestampChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\OtherChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveDefinitionsChange.$(O) ClassPrimitiveDefinitionsChange.$(H): ClassPrimitiveDefinitionsChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveFunctionsChange.$(O) ClassPrimitiveFunctionsChange.$(H): ClassPrimitiveFunctionsChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)ClassPrimitiveVariablesChange.$(O) ClassPrimitiveVariablesChange.$(H): ClassPrimitiveVariablesChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
-$(OUTDIR)MethodCategoryChange.$(O) MethodCategoryChange.$(H): MethodCategoryChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodDefinitionChange.$(O) MethodDefinitionChange.$(H): MethodDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodPackageChange.$(O) MethodPackageChange.$(H): MethodPackageChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodPrivacyChange.$(O) MethodPrivacyChange.$(H): MethodPrivacyChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
-$(OUTDIR)MethodRemoveChange.$(O) MethodRemoveChange.$(H): MethodRemoveChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
+$(OUTDIR)AbstractSourceCodeManager.$(O) AbstractSourceCodeManager.$(C) AbstractSourceCodeManager.$(H): AbstractSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectWriter.$(O) BeeProjectWriter.$(C) BeeProjectWriter.$(H): BeeProjectWriter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BeeSourceWriter.$(O) BeeSourceWriter.$(C) BeeSourceWriter.$(H): BeeSourceWriter.st $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
+$(OUTDIR)CallChain.$(O) CallChain.$(C) CallChain.$(H): CallChain.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Change.$(O) Change.$(C) Change.$(H): Change.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(C) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(C) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)ChangeSet.$(O) ChangeSet.$(C) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SmalltalkChunkFileSourceWriter.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(C) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(C) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(C) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HTMLDocGenerator.$(O) HTMLDocGenerator.$(C) HTMLDocGenerator.$(H): HTMLDocGenerator.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HistoryManager.$(O) HistoryManager.$(C) HistoryManager.$(H): HistoryManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MessageTally.$(O) MessageTally.$(C) MessageTally.$(H): MessageTally.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MessageTracer.$(O) MessageTracer.$(C) MessageTracer.$(H): MessageTracer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MethodFinder.$(O) MethodFinder.$(C) MethodFinder.$(H): MethodFinder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ProfileTree.$(O) ProfileTree.$(C) ProfileTree.$(H): ProfileTree.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ProjectChecker.$(O) ProjectChecker.$(C) ProjectChecker.$(H): ProjectChecker.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ProjectProblem.$(O) ProjectProblem.$(C) ProjectProblem.$(H): ProjectProblem.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeCache.$(O) SourceCodeCache.$(C) SourceCodeCache.$(H): SourceCodeCache.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerError.$(O) SourceCodeManagerError.$(C) SourceCodeManagerError.$(H): SourceCodeManagerError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilities.$(O) SourceCodeManagerUtilities.$(C) SourceCodeManagerUtilities.$(H): SourceCodeManagerUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SystemEnvironment.$(O) SystemEnvironment.$(C) SystemEnvironment.$(H): SystemEnvironment.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SystemOrganizer.$(O) SystemOrganizer.$(C) SystemOrganizer.$(H): SystemOrganizer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SystemProfiler.$(O) SystemProfiler.$(C) SystemProfiler.$(H): SystemProfiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)TraceBuffer.$(O) TraceBuffer.$(C) TraceBuffer.$(H): TraceBuffer.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
+$(OUTDIR)VersionInfo.$(O) VersionInfo.$(C) VersionInfo.$(H): VersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)WrappedMethod.$(O) WrappedMethod.$(C) WrappedMethod.$(H): WrappedMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)stx_libbasic3.$(O) stx_libbasic3.$(C) stx_libbasic3.$(H): stx_libbasic3.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectDefinitionWriter.$(O) BeeProjectDefinitionWriter.$(C) BeeProjectDefinitionWriter.$(H): BeeProjectDefinitionWriter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\BeeProjectWriter.$(H) $(STCHDR)
+$(OUTDIR)BeeProjectSourceWriter.$(O) BeeProjectSourceWriter.$(C) BeeProjectSourceWriter.$(H): BeeProjectSourceWriter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\BeeProjectWriter.$(H) $(STCHDR)
+$(OUTDIR)CVSSourceCodeManager.$(O) CVSSourceCodeManager.$(C) CVSSourceCodeManager.$(H): CVSSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)CVSVersionInfo.$(O) CVSVersionInfo.$(C) CVSVersionInfo.$(H): CVSVersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffEntry.$(O) ChangeSetDiffEntry.$(C) ChangeSetDiffEntry.$(H): ChangeSetDiffEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeSetDiffComponent.$(H) $(STCHDR)
+$(OUTDIR)ChangeSetDiffSet.$(O) ChangeSetDiffSet.$(C) ChangeSetDiffSet.$(H): ChangeSetDiffSet.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeSetDiffComponent.$(H) $(STCHDR)
+$(OUTDIR)ClassChange.$(O) ClassChange.$(C) ClassChange.$(H): ClassChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)CompositeChange.$(O) CompositeChange.$(C) CompositeChange.$(H): CompositeChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)DataBaseSourceCodeManager.$(O) DataBaseSourceCodeManager.$(C) DataBaseSourceCodeManager.$(H): DataBaseSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)DataBaseSourceCodeManagerUtilities.$(O) DataBaseSourceCodeManagerUtilities.$(C) DataBaseSourceCodeManagerUtilities.$(H): DataBaseSourceCodeManagerUtilities.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)DoItChange.$(O) DoItChange.$(C) DoItChange.$(H): DoItChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)FileBasedSourceCodeManager.$(O) FileBasedSourceCodeManager.$(C) FileBasedSourceCodeManager.$(H): FileBasedSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)FileInChange.$(O) FileInChange.$(C) FileInChange.$(H): FileInChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)GitSourceCodeManager.$(O) GitSourceCodeManager.$(C) GitSourceCodeManager.$(H): GitSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)InvalidChange.$(O) InvalidChange.$(C) InvalidChange.$(H): InvalidChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)MercurialSourceCodeManager.$(O) MercurialSourceCodeManager.$(C) MercurialSourceCodeManager.$(H): MercurialSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)MethodChangeNotificationParameter.$(O) MethodChangeNotificationParameter.$(C) MethodChangeNotificationParameter.$(H): MethodChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)NameSpaceCreationChange.$(O) NameSpaceCreationChange.$(C) NameSpaceCreationChange.$(H): NameSpaceCreationChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)OtherChange.$(O) OtherChange.$(C) OtherChange.$(H): OtherChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(STCHDR)
+$(OUTDIR)PerforceSourceCodeManager.$(O) PerforceSourceCodeManager.$(C) PerforceSourceCodeManager.$(H): PerforceSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)SVNVersionInfo.$(O) SVNVersionInfo.$(C) SVNVersionInfo.$(H): SVNVersionInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilitiesForContainerBasedManagers.$(O) SourceCodeManagerUtilitiesForContainerBasedManagers.$(C) SourceCodeManagerUtilitiesForContainerBasedManagers.$(H): SourceCodeManagerUtilitiesForContainerBasedManagers.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(O) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(C) SourceCodeManagerUtilitiesForWorkspaceBasedManagers.$(H): SourceCodeManagerUtilitiesForWorkspaceBasedManagers.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\SourceCodeManagerUtilities.$(H) $(STCHDR)
+$(OUTDIR)StoreSourceCodeManager.$(O) StoreSourceCodeManager.$(C) StoreSourceCodeManager.$(H): StoreSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
+$(OUTDIR)ClassCategoryChange.$(O) ClassCategoryChange.$(C) ClassCategoryChange.$(H): ClassCategoryChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassClassVariableChange.$(O) ClassClassVariableChange.$(C) ClassClassVariableChange.$(H): ClassClassVariableChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassCommentChange.$(O) ClassCommentChange.$(C) ClassCommentChange.$(H): ClassCommentChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassDefinitionChange.$(O) ClassDefinitionChange.$(C) ClassDefinitionChange.$(H): ClassDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassInitializeChange.$(O) ClassInitializeChange.$(C) ClassInitializeChange.$(H): ClassInitializeChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassInstVarDefinitionChange.$(O) ClassInstVarDefinitionChange.$(C) ClassInstVarDefinitionChange.$(H): ClassInstVarDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassOtherChange.$(O) ClassOtherChange.$(C) ClassOtherChange.$(H): ClassOtherChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveChange.$(O) ClassPrimitiveChange.$(C) ClassPrimitiveChange.$(H): ClassPrimitiveChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassRemoveChange.$(O) ClassRemoveChange.$(C) ClassRemoveChange.$(H): ClassRemoveChange.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)ClassRenameChange.$(O) ClassRenameChange.$(C) ClassRenameChange.$(H): ClassRenameChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)InfoChange.$(O) InfoChange.$(C) InfoChange.$(H): InfoChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\OtherChange.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryChangeNotificationParameter.$(O) MethodCategoryChangeNotificationParameter.$(C) MethodCategoryChangeNotificationParameter.$(H): MethodCategoryChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryRenameChange.$(O) MethodCategoryRenameChange.$(C) MethodCategoryRenameChange.$(H): MethodCategoryRenameChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)MethodChange.$(O) MethodChange.$(C) MethodChange.$(H): MethodChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(STCHDR)
+$(OUTDIR)MethodRemoveChangeNotificationParameter.$(O) MethodRemoveChangeNotificationParameter.$(C) MethodRemoveChangeNotificationParameter.$(H): MethodRemoveChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)MethodTrapChangeNotificationParameter.$(O) MethodTrapChangeNotificationParameter.$(C) MethodTrapChangeNotificationParameter.$(H): MethodTrapChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic3\ChangeNotificationParameter.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChangeNotificationParameter.$(H) $(STCHDR)
+$(OUTDIR)TimestampChange.$(O) TimestampChange.$(C) TimestampChange.$(H): TimestampChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\OtherChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveDefinitionsChange.$(O) ClassPrimitiveDefinitionsChange.$(C) ClassPrimitiveDefinitionsChange.$(H): ClassPrimitiveDefinitionsChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveFunctionsChange.$(O) ClassPrimitiveFunctionsChange.$(C) ClassPrimitiveFunctionsChange.$(H): ClassPrimitiveFunctionsChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)ClassPrimitiveVariablesChange.$(O) ClassPrimitiveVariablesChange.$(C) ClassPrimitiveVariablesChange.$(H): ClassPrimitiveVariablesChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassPrimitiveChange.$(H) $(STCHDR)
+$(OUTDIR)MethodCategoryChange.$(O) MethodCategoryChange.$(C) MethodCategoryChange.$(H): MethodCategoryChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodDefinitionChange.$(O) MethodDefinitionChange.$(C) MethodDefinitionChange.$(H): MethodDefinitionChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodPackageChange.$(O) MethodPackageChange.$(C) MethodPackageChange.$(H): MethodPackageChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodPrivacyChange.$(O) MethodPrivacyChange.$(C) MethodPrivacyChange.$(H): MethodPrivacyChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
+$(OUTDIR)MethodRemoveChange.$(O) MethodRemoveChange.$(C) MethodRemoveChange.$(H): MethodRemoveChange.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\ClassChange.$(H) $(INCLUDE_TOP)\stx\libbasic3\MethodChange.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ConfigurableFeatures.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\UserPreferences.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
+
+# **Must be at end**
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+!IFDEF HGROOT
+$(OUTDIR)stx_libbasic3.$(O): $(HGROOT)\.hg\dirstate
+!ENDIF
--- a/bmake.bat	Thu Jul 28 15:03:23 2016 +0200
+++ b/bmake.bat	Fri Jul 29 06:57:08 2016 +0200
@@ -7,6 +7,7 @@
 @REM Kludge got Mercurial, cannot be implemented in Borland make
 @FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
 @IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+
 make.exe -N -f bc.mak  %DEFINES% %*
 
 
--- a/extensions.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/extensions.st	Fri Jul 29 06:57:08 2016 +0200
@@ -162,7 +162,7 @@
 
 !stx_libbasic3 class methodsFor:'documentation'!
 
-extensionsVersion_CVS
-    ^ '$Header$'
+extensionsVersion_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
-
--- a/libInit.cc	Thu Jul 28 15:03:23 2016 +0200
+++ b/libInit.cc	Fri Jul 29 06:57:08 2016 +0200
@@ -1,5 +1,5 @@
 /*
- * $Header: /cvs/stx/stx/libbasic3/libInit.cc,v 1.112 2015-01-27 20:36:23 cg Exp $
+ * $Header$
  *
  * DO NOT EDIT
  * automagically generated from the projectDefinition: stx_libbasic3.
@@ -16,91 +16,176 @@
 DLL_EXPORT void _libstx_libbasic3_InitDefinition() INIT_TEXT_SECTION;
 #endif
 
-void _libstx_libbasic3_InitDefinition(pass, __pRT__, snd)
-OBJ snd; struct __vmData__ *__pRT__; {
-__BEGIN_PACKAGE2__("libstx_libbasic3__DFN", _libstx_libbasic3_InitDefinition, "stx:libbasic3");
-_stx_137libbasic3_Init(pass,__pRT__,snd);
+extern void _AbstractSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BeeProjectWriter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BeeSourceWriter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CallChain_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _Change_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeDeltaInformation_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeNotificationParameter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeSetDiff_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeSetDiffComponent_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassOrganizer_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HTMLDocGenerator_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HistoryManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MessageTally_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MessageTracer_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodFinder_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ProfileTree_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ProjectChecker_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ProjectProblem_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SourceCodeCache_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SourceCodeManagerError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SourceCodeManagerUtilities_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SystemEnvironment_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SystemOrganizer_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SystemProfiler_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _TraceBuffer_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _VersionInfo_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _WrappedMethod_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _stx_137libbasic3_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BeeProjectDefinitionWriter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _BeeProjectSourceWriter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CVSSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CVSVersionInfo_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeSetDiffEntry_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ChangeSetDiffSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CompositeChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DataBaseSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DataBaseSourceCodeManagerUtilities_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DoItChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _FileBasedSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _FileInChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _GitSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _InvalidChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MercurialSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodChangeNotificationParameter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _NameSpaceCreationChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _OtherChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _PerforceSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SVNVersionInfo_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SourceCodeManagerUtilitiesForContainerBasedManagers_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SourceCodeManagerUtilitiesForWorkspaceBasedManagers_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _StoreSourceCodeManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassCategoryChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassClassVariableChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassCommentChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassDefinitionChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassInitializeChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassInstVarDefinitionChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassOtherChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassPrimitiveChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassRemoveChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassRenameChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _InfoChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodCategoryChangeNotificationParameter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodCategoryRenameChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodRemoveChangeNotificationParameter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodTrapChangeNotificationParameter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _TimestampChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassPrimitiveDefinitionsChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassPrimitiveFunctionsChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassPrimitiveVariablesChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodCategoryChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodDefinitionChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodPackageChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodPrivacyChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MethodRemoveChange_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 
-__END_PACKAGE__();
+
+void _libstx_libbasic3_InitDefinition(int pass, struct __vmData__ *__pRT__, OBJ snd)
+{
+  __BEGIN_PACKAGE2__("libstx_libbasic3__DFN", _libstx_libbasic3_InitDefinition, "stx:libbasic3");
+    _stx_137libbasic3_Init(pass,__pRT__,snd);
+
+  __END_PACKAGE__();
 }
 
-void _libstx_libbasic3_Init(pass, __pRT__, snd)
-OBJ snd; struct __vmData__ *__pRT__; {
-__BEGIN_PACKAGE2__("libstx_libbasic3", _libstx_libbasic3_Init, "stx:libbasic3");
-_AbstractSourceCodeManager_Init(pass,__pRT__,snd);
-_CallChain_Init(pass,__pRT__,snd);
-_Change_Init(pass,__pRT__,snd);
-_ChangeDeltaInformation_Init(pass,__pRT__,snd);
-_ChangeNotificationParameter_Init(pass,__pRT__,snd);
-_ChangeSet_Init(pass,__pRT__,snd);
-_ChangeSetDiff_Init(pass,__pRT__,snd);
-_ChangeSetDiffComponent_Init(pass,__pRT__,snd);
-_ClassOrganizer_Init(pass,__pRT__,snd);
-_HTMLDocGenerator_Init(pass,__pRT__,snd);
-_HistoryManager_Init(pass,__pRT__,snd);
-_MessageTally_Init(pass,__pRT__,snd);
-_MessageTracer_Init(pass,__pRT__,snd);
-_MethodFinder_Init(pass,__pRT__,snd);
-_ProfileTree_Init(pass,__pRT__,snd);
-_ProjectChecker_Init(pass,__pRT__,snd);
-_ProjectProblem_Init(pass,__pRT__,snd);
-_SourceCodeCache_Init(pass,__pRT__,snd);
-_SourceCodeManagerError_Init(pass,__pRT__,snd);
-_SourceCodeManagerUtilities_Init(pass,__pRT__,snd);
-_SystemEnvironment_Init(pass,__pRT__,snd);
-_SystemOrganizer_Init(pass,__pRT__,snd);
-_TraceBuffer_Init(pass,__pRT__,snd);
-_VersionInfo_Init(pass,__pRT__,snd);
-_WrappedMethod_Init(pass,__pRT__,snd);
-_stx_137libbasic3_Init(pass,__pRT__,snd);
-_CVSSourceCodeManager_Init(pass,__pRT__,snd);
-_CVSVersionInfo_Init(pass,__pRT__,snd);
-_ChangeSetDiffEntry_Init(pass,__pRT__,snd);
-_ChangeSetDiffSet_Init(pass,__pRT__,snd);
-_ClassChange_Init(pass,__pRT__,snd);
-_CompositeChange_Init(pass,__pRT__,snd);
-_DataBaseSourceCodeManager_Init(pass,__pRT__,snd);
-_DataBaseSourceCodeManagerUtilities_Init(pass,__pRT__,snd);
-_DoItChange_Init(pass,__pRT__,snd);
-_FileBasedSourceCodeManager_Init(pass,__pRT__,snd);
-_FileInChange_Init(pass,__pRT__,snd);
-_GitSourceCodeManager_Init(pass,__pRT__,snd);
-_InvalidChange_Init(pass,__pRT__,snd);
-_MercurialSourceCodeManager_Init(pass,__pRT__,snd);
-_MethodChangeNotificationParameter_Init(pass,__pRT__,snd);
-_NameSpaceCreationChange_Init(pass,__pRT__,snd);
-_OtherChange_Init(pass,__pRT__,snd);
-_PerforceSourceCodeManager_Init(pass,__pRT__,snd);
-_SVNVersionInfo_Init(pass,__pRT__,snd);
-_SourceCodeManagerUtilitiesForContainerBasedManagers_Init(pass,__pRT__,snd);
-_SourceCodeManagerUtilitiesForWorkspaceBasedManagers_Init(pass,__pRT__,snd);
-_StoreSourceCodeManager_Init(pass,__pRT__,snd);
-_ClassCategoryChange_Init(pass,__pRT__,snd);
-_ClassClassVariableChange_Init(pass,__pRT__,snd);
-_ClassCommentChange_Init(pass,__pRT__,snd);
-_ClassDefinitionChange_Init(pass,__pRT__,snd);
-_ClassInitializeChange_Init(pass,__pRT__,snd);
-_ClassInstVarDefinitionChange_Init(pass,__pRT__,snd);
-_ClassOtherChange_Init(pass,__pRT__,snd);
-_ClassPrimitiveChange_Init(pass,__pRT__,snd);
-_ClassRemoveChange_Init(pass,__pRT__,snd);
-_ClassRenameChange_Init(pass,__pRT__,snd);
-_InfoChange_Init(pass,__pRT__,snd);
-_MethodCategoryChangeNotificationParameter_Init(pass,__pRT__,snd);
-_MethodCategoryRenameChange_Init(pass,__pRT__,snd);
-_MethodChange_Init(pass,__pRT__,snd);
-_MethodRemoveChangeNotificationParameter_Init(pass,__pRT__,snd);
-_MethodTrapChangeNotificationParameter_Init(pass,__pRT__,snd);
-_TimestampChange_Init(pass,__pRT__,snd);
-_ClassPrimitiveDefinitionsChange_Init(pass,__pRT__,snd);
-_ClassPrimitiveFunctionsChange_Init(pass,__pRT__,snd);
-_ClassPrimitiveVariablesChange_Init(pass,__pRT__,snd);
-_MethodCategoryChange_Init(pass,__pRT__,snd);
-_MethodDefinitionChange_Init(pass,__pRT__,snd);
-_MethodPackageChange_Init(pass,__pRT__,snd);
-_MethodPrivacyChange_Init(pass,__pRT__,snd);
-_MethodRemoveChange_Init(pass,__pRT__,snd);
+void _libstx_libbasic3_Init(int pass, struct __vmData__ *__pRT__, OBJ snd)
+{
+  __BEGIN_PACKAGE2__("libstx_libbasic3", _libstx_libbasic3_Init, "stx:libbasic3");
+    _AbstractSourceCodeManager_Init(pass,__pRT__,snd);
+    _BeeProjectWriter_Init(pass,__pRT__,snd);
+    _BeeSourceWriter_Init(pass,__pRT__,snd);
+    _CallChain_Init(pass,__pRT__,snd);
+    _Change_Init(pass,__pRT__,snd);
+    _ChangeDeltaInformation_Init(pass,__pRT__,snd);
+    _ChangeNotificationParameter_Init(pass,__pRT__,snd);
+    _ChangeSet_Init(pass,__pRT__,snd);
+    _ChangeSetDiff_Init(pass,__pRT__,snd);
+    _ChangeSetDiffComponent_Init(pass,__pRT__,snd);
+    _ClassOrganizer_Init(pass,__pRT__,snd);
+    _HTMLDocGenerator_Init(pass,__pRT__,snd);
+    _HistoryManager_Init(pass,__pRT__,snd);
+    _MessageTally_Init(pass,__pRT__,snd);
+    _MessageTracer_Init(pass,__pRT__,snd);
+    _MethodFinder_Init(pass,__pRT__,snd);
+    _ProfileTree_Init(pass,__pRT__,snd);
+    _ProjectChecker_Init(pass,__pRT__,snd);
+    _ProjectProblem_Init(pass,__pRT__,snd);
+    _SourceCodeCache_Init(pass,__pRT__,snd);
+    _SourceCodeManagerError_Init(pass,__pRT__,snd);
+    _SourceCodeManagerUtilities_Init(pass,__pRT__,snd);
+    _SystemEnvironment_Init(pass,__pRT__,snd);
+    _SystemOrganizer_Init(pass,__pRT__,snd);
+    _SystemProfiler_Init(pass,__pRT__,snd);
+    _TraceBuffer_Init(pass,__pRT__,snd);
+    _VersionInfo_Init(pass,__pRT__,snd);
+    _WrappedMethod_Init(pass,__pRT__,snd);
+    _stx_137libbasic3_Init(pass,__pRT__,snd);
+    _BeeProjectDefinitionWriter_Init(pass,__pRT__,snd);
+    _BeeProjectSourceWriter_Init(pass,__pRT__,snd);
+    _CVSSourceCodeManager_Init(pass,__pRT__,snd);
+    _CVSVersionInfo_Init(pass,__pRT__,snd);
+    _ChangeSetDiffEntry_Init(pass,__pRT__,snd);
+    _ChangeSetDiffSet_Init(pass,__pRT__,snd);
+    _ClassChange_Init(pass,__pRT__,snd);
+    _CompositeChange_Init(pass,__pRT__,snd);
+    _DataBaseSourceCodeManager_Init(pass,__pRT__,snd);
+    _DataBaseSourceCodeManagerUtilities_Init(pass,__pRT__,snd);
+    _DoItChange_Init(pass,__pRT__,snd);
+    _FileBasedSourceCodeManager_Init(pass,__pRT__,snd);
+    _FileInChange_Init(pass,__pRT__,snd);
+    _GitSourceCodeManager_Init(pass,__pRT__,snd);
+    _InvalidChange_Init(pass,__pRT__,snd);
+    _MercurialSourceCodeManager_Init(pass,__pRT__,snd);
+    _MethodChangeNotificationParameter_Init(pass,__pRT__,snd);
+    _NameSpaceCreationChange_Init(pass,__pRT__,snd);
+    _OtherChange_Init(pass,__pRT__,snd);
+    _PerforceSourceCodeManager_Init(pass,__pRT__,snd);
+    _SVNVersionInfo_Init(pass,__pRT__,snd);
+    _SourceCodeManagerUtilitiesForContainerBasedManagers_Init(pass,__pRT__,snd);
+    _SourceCodeManagerUtilitiesForWorkspaceBasedManagers_Init(pass,__pRT__,snd);
+    _StoreSourceCodeManager_Init(pass,__pRT__,snd);
+    _ClassCategoryChange_Init(pass,__pRT__,snd);
+    _ClassClassVariableChange_Init(pass,__pRT__,snd);
+    _ClassCommentChange_Init(pass,__pRT__,snd);
+    _ClassDefinitionChange_Init(pass,__pRT__,snd);
+    _ClassInitializeChange_Init(pass,__pRT__,snd);
+    _ClassInstVarDefinitionChange_Init(pass,__pRT__,snd);
+    _ClassOtherChange_Init(pass,__pRT__,snd);
+    _ClassPrimitiveChange_Init(pass,__pRT__,snd);
+    _ClassRemoveChange_Init(pass,__pRT__,snd);
+    _ClassRenameChange_Init(pass,__pRT__,snd);
+    _InfoChange_Init(pass,__pRT__,snd);
+    _MethodCategoryChangeNotificationParameter_Init(pass,__pRT__,snd);
+    _MethodCategoryRenameChange_Init(pass,__pRT__,snd);
+    _MethodChange_Init(pass,__pRT__,snd);
+    _MethodRemoveChangeNotificationParameter_Init(pass,__pRT__,snd);
+    _MethodTrapChangeNotificationParameter_Init(pass,__pRT__,snd);
+    _TimestampChange_Init(pass,__pRT__,snd);
+    _ClassPrimitiveDefinitionsChange_Init(pass,__pRT__,snd);
+    _ClassPrimitiveFunctionsChange_Init(pass,__pRT__,snd);
+    _ClassPrimitiveVariablesChange_Init(pass,__pRT__,snd);
+    _MethodCategoryChange_Init(pass,__pRT__,snd);
+    _MethodDefinitionChange_Init(pass,__pRT__,snd);
+    _MethodPackageChange_Init(pass,__pRT__,snd);
+    _MethodPrivacyChange_Init(pass,__pRT__,snd);
+    _MethodRemoveChange_Init(pass,__pRT__,snd);
 
-_stx_137libbasic3_extensions_Init(pass,__pRT__,snd);
-__END_PACKAGE__();
+    _stx_137libbasic3_extensions_Init(pass,__pRT__,snd);
+  __END_PACKAGE__();
 }
--- a/packages/AbstractPackage.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractPackage.st	Fri Jul 29 06:57:08 2016 +0200
@@ -114,5 +114,5 @@
 !AbstractPackage class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackage.st,v 1.3 2006-01-10 09:25:15 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractPackage.st,v 1.3 2006-01-10 09:25:15 cg Exp $'
 ! !
--- a/packages/AbstractPackageBrowser.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractPackageBrowser.st	Fri Jul 29 06:57:08 2016 +0200
@@ -118,5 +118,5 @@
 !AbstractPackageBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageBrowser.st,v 1.3 2006-01-10 09:25:27 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractPackageBrowser.st,v 1.3 2006-01-10 09:25:27 cg Exp $'
 ! !
--- a/packages/AbstractPackageDetails.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractPackageDetails.st	Fri Jul 29 06:57:08 2016 +0200
@@ -70,5 +70,5 @@
 !AbstractPackageDetails class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageDetails.st,v 1.3 2006-01-10 09:25:06 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractPackageDetails.st,v 1.3 2006-01-10 09:25:06 cg Exp $'
 ! !
--- a/packages/AbstractPackageManager.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractPackageManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -156,5 +156,5 @@
 !AbstractPackageManager class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageManager.st,v 1.4 2006-08-24 08:39:01 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractPackageManager.st,v 1.4 2006-08-24 08:39:01 cg Exp $'
 ! !
--- a/packages/AbstractPackageNotebookApplication.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractPackageNotebookApplication.st	Fri Jul 29 06:57:08 2016 +0200
@@ -314,5 +314,5 @@
 !AbstractPackageNotebookApplication class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageNotebookApplication.st,v 1.3 2006-01-10 09:25:10 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractPackageNotebookApplication.st,v 1.3 2006-01-10 09:25:10 cg Exp $'
 ! !
--- a/packages/AbstractTestCases.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/AbstractTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -189,5 +189,5 @@
 !AbstractTestCases class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractTestCases.st,v 1.3 2006-01-10 09:29:37 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/AbstractTestCases.st,v 1.3 2006-01-10 09:29:37 cg Exp $'
 ! !
--- a/packages/ChangeFaker.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/ChangeFaker.st	Fri Jul 29 06:57:08 2016 +0200
@@ -172,7 +172,7 @@
 !ChangeFaker class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ChangeFaker.st,v 1.3 2006-01-10 09:29:32 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/ChangeFaker.st,v 1.3 2006-01-10 09:29:32 cg Exp $'
 ! !
 
 ChangeFaker initialize!
--- a/packages/ChangesHelper.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/ChangesHelper.st	Fri Jul 29 06:57:08 2016 +0200
@@ -52,5 +52,5 @@
 !ChangesHelper class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ChangesHelper.st,v 1.2 2006-01-10 09:29:34 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/ChangesHelper.st,v 1.2 2006-01-10 09:29:34 cg Exp $'
 ! !
--- a/packages/ClassPrerequisite.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/ClassPrerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -53,5 +53,5 @@
 !ClassPrerequisite class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ClassPrerequisite.st,v 1.2 2006-01-10 09:29:39 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/ClassPrerequisite.st,v 1.2 2006-01-10 09:29:39 cg Exp $'
 ! !
--- a/packages/DefaultPackage.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/DefaultPackage.st	Fri Jul 29 06:57:08 2016 +0200
@@ -155,5 +155,5 @@
 !DefaultPackage class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/DefaultPackage.st,v 1.2 2006-01-10 09:29:41 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/DefaultPackage.st,v 1.2 2006-01-10 09:29:41 cg Exp $'
 ! !
--- a/packages/DictionaryStack.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/DictionaryStack.st	Fri Jul 29 06:57:08 2016 +0200
@@ -149,5 +149,5 @@
 !DictionaryStack class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/DictionaryStack.st,v 1.2 2006-01-10 09:25:12 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/DictionaryStack.st,v 1.2 2006-01-10 09:25:12 cg Exp $'
 ! !
--- a/packages/Package.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/Package.st	Fri Jul 29 06:57:08 2016 +0200
@@ -2336,5 +2336,5 @@
 !Package class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/Package.st,v 1.9 2006-08-24 08:38:50 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/Package.st,v 1.9 2006-08-24 08:38:50 cg Exp $'
 ! !
--- a/packages/PackageBrowser.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageBrowser.st	Fri Jul 29 06:57:08 2016 +0200
@@ -586,5 +586,5 @@
 !PackageBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageBrowser.st,v 1.4 2006-01-10 09:25:17 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageBrowser.st,v 1.4 2006-01-10 09:25:17 cg Exp $'
 ! !
--- a/packages/PackageDetails.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageDetails.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1979,5 +1979,5 @@
 !PackageDetails class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageDetails.st,v 1.4 2006-01-10 09:25:03 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageDetails.st,v 1.4 2006-01-10 09:25:03 cg Exp $'
 ! !
--- a/packages/PackageError.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageError.st	Fri Jul 29 06:57:08 2016 +0200
@@ -111,5 +111,5 @@
 !PackageError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageError.st,v 1.4 2006-01-10 09:29:56 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageError.st,v 1.4 2006-01-10 09:29:56 cg Exp $'
 ! !
--- a/packages/PackageHandler.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageHandler.st	Fri Jul 29 06:57:08 2016 +0200
@@ -80,5 +80,5 @@
 !PackageHandler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageHandler.st,v 1.3 2006-01-10 09:32:12 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageHandler.st,v 1.3 2006-01-10 09:32:12 cg Exp $'
 ! !
--- a/packages/PackageManager.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1093,7 +1093,7 @@
 !PackageManager class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageManager.st,v 1.9 2006-08-24 08:38:42 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageManager.st,v 1.9 2006-08-24 08:38:42 cg Exp $'
 ! !
 
 PackageManager initialize!
--- a/packages/PackageManagerTests.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageManagerTests.st	Fri Jul 29 06:57:08 2016 +0200
@@ -726,5 +726,5 @@
 !PackageManagerTests class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageManagerTests.st,v 1.4 2006-01-10 09:31:56 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageManagerTests.st,v 1.4 2006-01-10 09:31:56 cg Exp $'
 ! !
--- a/packages/PackageNotification.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageNotification.st	Fri Jul 29 06:57:08 2016 +0200
@@ -47,5 +47,5 @@
 !PackageNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageNotification.st,v 1.3 2006-01-10 09:32:07 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageNotification.st,v 1.3 2006-01-10 09:32:07 cg Exp $'
 ! !
--- a/packages/PackageOpener.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageOpener.st	Fri Jul 29 06:57:08 2016 +0200
@@ -40,5 +40,5 @@
 !PackageOpener class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageOpener.st,v 1.2 2006-01-10 09:32:10 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageOpener.st,v 1.2 2006-01-10 09:32:10 cg Exp $'
 ! !
--- a/packages/PackagePrerequisite.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackagePrerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -52,5 +52,5 @@
 !PackagePrerequisite class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackagePrerequisite.st,v 1.2 2006-01-10 09:32:00 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackagePrerequisite.st,v 1.2 2006-01-10 09:32:00 cg Exp $'
 ! !
--- a/packages/PackageProperties.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageProperties.st	Fri Jul 29 06:57:08 2016 +0200
@@ -449,5 +449,5 @@
 !PackageProperties class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageProperties.st,v 1.2 2006-01-10 09:31:58 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageProperties.st,v 1.2 2006-01-10 09:31:58 cg Exp $'
 ! !
--- a/packages/PackageSaver.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageSaver.st	Fri Jul 29 06:57:08 2016 +0200
@@ -40,5 +40,5 @@
 !PackageSaver class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSaver.st,v 1.2 2006-01-10 09:31:51 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageSaver.st,v 1.2 2006-01-10 09:31:51 cg Exp $'
 ! !
--- a/packages/PackageSelector.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageSelector.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1812,5 +1812,5 @@
 !PackageSelector class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSelector.st,v 1.5 2006-08-24 08:38:35 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageSelector.st,v 1.5 2006-08-24 08:38:35 cg Exp $'
 ! !
--- a/packages/PackageSmalltalkManipulationTestCases.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageSmalltalkManipulationTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -1217,5 +1217,5 @@
 !PackageSmalltalkManipulationTestCases class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSmalltalkManipulationTestCases.st,v 1.6 2006-01-10 09:31:41 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageSmalltalkManipulationTestCases.st,v 1.6 2006-01-10 09:31:41 cg Exp $'
 ! !
--- a/packages/PackageTestCases.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackageTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -399,5 +399,5 @@
 !PackageTestCases class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageTestCases.st,v 1.5 2006-01-10 09:31:48 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackageTestCases.st,v 1.5 2006-01-10 09:31:48 cg Exp $'
 ! !
--- a/packages/PackagesInstalled.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PackagesInstalled.st	Fri Jul 29 06:57:08 2016 +0200
@@ -159,5 +159,5 @@
 !PackagesInstalled class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackagesInstalled.st,v 1.2 2006-01-10 09:32:15 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PackagesInstalled.st,v 1.2 2006-01-10 09:32:15 cg Exp $'
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractPackage.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,118 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#AbstractPackage
+	instanceVariableNames:'name category'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package'
+!
+
+!AbstractPackage class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!AbstractPackage class methodsFor:'default'!
+
+defaultCategoryName
+    ^ #'__NoName__'  
+! !
+
+!AbstractPackage methodsFor:'accessing'!
+
+category
+    "return the value of the instance variable 'category'. 
+    Is initialized by the initialize method"
+    ^ category
+!
+
+category:something
+    "set the value of the instance variable 'category' (automatically generated)"
+
+    category := something.
+!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+
+    ^ name
+!
+
+name:aSymbol
+    "set the value of the instance variable 'name' (automatically generated)"
+    self assert:(aSymbol isSymbol).  "needed for quick comparison. NO STRINGS!!"
+    name := aSymbol.
+! !
+
+!AbstractPackage methodsFor:'initialization'!
+
+initialize
+    category := self class defaultCategoryName.
+! !
+
+!AbstractPackage methodsFor:'installation / deinstallation'!
+
+install
+    self subclassResponsibility
+!
+
+uninstall
+    self subclassResponsibility
+! !
+
+!AbstractPackage methodsFor:'queries'!
+
+isInCategoryNamed:aName 
+    ^ category = aName
+! !
+
+!AbstractPackage methodsFor:'queries-type'!
+
+isDolphinPackage
+    ^ false
+!
+
+isStxPackage
+    ^ false
+! !
+
+!AbstractPackage methodsFor:'saving'!
+
+save
+    self subclassResponsibility
+!
+
+saveAs:aFilename
+    self subclassResponsibility
+! !
+
+!AbstractPackage class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackage.st,v 1.3 2006/01/10 09:25:15 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractPackageBrowser.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,122 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+ApplicationModel subclass:#AbstractPackageBrowser
+	instanceVariableNames:'applicationAspects'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+!AbstractPackageBrowser class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!AbstractPackageBrowser methodsFor:'accessing'!
+
+applicationAspects
+    applicationAspects ifNil:[
+        applicationAspects := Dictionary new
+    ].
+    ^ applicationAspects
+!
+
+applicationAspects:something
+    "set the value of the instance variable 'applicationAspects' (automatically generated)"
+
+    applicationAspects := something.
+!
+
+declareDependents
+!
+
+masterApplication:aMasterApplication
+    aMasterApplication ifNil:[
+        ^ self.
+    ].
+    
+    self applicationAspects: aMasterApplication applicationAspects.
+    self declareDependents.
+    ^ super masterApplication:aMasterApplication.
+!
+
+packagesNamed:aCollectionOfPackageNamesOrSymbol 
+    |aCollectionOfPackageNames|
+    aCollectionOfPackageNames := aCollectionOfPackageNamesOrSymbol.
+    aCollectionOfPackageNames isSymbol ifTrue:[
+        aCollectionOfPackageNames := Array with:aCollectionOfPackageNamesOrSymbol.
+    ].
+    [(aCollectionOfPackageNamesOrSymbol includes:nil)] whileTrue:[
+        aCollectionOfPackageNamesOrSymbol remove:nil
+    ].
+    
+    ^ self packageManager packagesNamed:aCollectionOfPackageNames
+!
+
+packagesSelected
+    ^ self packagesSelectedHolder value
+!
+
+undeclareDependents
+! !
+
+!AbstractPackageBrowser methodsFor:'accessing - shared'!
+
+applicationAspectsAt:anIdentifier ifAbsent:aBlock
+    ^ self applicationAspects at:anIdentifier ifAbsent:aBlock
+!
+
+applicationAspectsAt:aSymbol ifAbsentPut:anObject
+    ^ self applicationAspects at:aSymbol ifAbsentPut:anObject
+!
+
+applicationAspectsAt:anIdentifier put:anObject
+    ^ self applicationAspects at:anIdentifier put:anObject
+!
+
+packageManager
+    ^ self applicationAspectsAt:#packageManager ifAbsent:[nil]
+!
+
+packageManager:aPackageManager
+    ^ self applicationAspectsAt:#packageManager put:aPackageManager
+!
+
+packagesSelectedHolder
+    ^ self applicationAspectsAt:#packagesSelectedHolder ifAbsent:[ValueHolder new]
+!
+
+packagesSelectedHolder:aPackageManager
+    ^ self applicationAspectsAt:#packagesSelectedHolder put:aPackageManager
+! !
+
+!AbstractPackageBrowser class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageBrowser.st,v 1.3 2006/01/10 09:25:27 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractPackageDetails.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,74 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageNotebookApplication subclass:#AbstractPackageDetails
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+!AbstractPackageDetails class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!AbstractPackageDetails methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "Invoked when an object that I depend upon sends a change notification."
+    (self packagesSelectedHolder == changedObject) ifTrue:[
+        self packagesSelectedHolderChanged:aParameter
+    ].
+! !
+
+!AbstractPackageDetails methodsFor:'changes'!
+
+declareDependents
+    "assumed that the removeDependents has been called"
+    self packagesSelectedHolder addDependent:self.
+!
+
+packagesSelectedHolderChanged:packagesSelected 
+
+    self updateWithPackages:packagesSelected
+!
+
+removeDependents
+    "assumed that the removeDependents has been called"
+    self packagesSelectedHolder removeDependent:self.
+!
+
+updateWithPackages:packages
+    self subclassResponsibility
+! !
+
+!AbstractPackageDetails class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageDetails.st,v 1.3 2006/01/10 09:25:06 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractPackageManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,160 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#AbstractPackageManager
+	instanceVariableNames:'packages'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Managers'
+!
+
+!AbstractPackageManager class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!AbstractPackageManager class methodsFor:'instance creation'!
+
+new
+    ^ self basicNew initialize
+! !
+
+!AbstractPackageManager class methodsFor:'defaults'!
+
+defaultPackages
+    ^ Dictionary new.
+! !
+
+!AbstractPackageManager class methodsFor:'factory'!
+
+newDefaultPackage
+    ^ (self newPackageNamed:(Project noProjectID)) mergeFromImage.
+!
+
+newPackageNamed:aString
+    ^ self packageClass named:aString
+! !
+
+!AbstractPackageManager methodsFor:'accessing'!
+
+packages
+    ^ packages
+!
+
+packages:something
+    "set the value of the instance variable 'packages' (automatically generated)"
+
+    packages := something.
+! !
+
+!AbstractPackageManager methodsFor:'api'!
+
+installPackage:aPackage
+    "installs aPackage into the image."
+    self subclassResponsibility
+!
+
+loadPackage:aFilename
+    "loads a package ready for installation into the image"
+    self subclassResponsibility
+!
+
+savePackage:aPackage
+    "saves package"
+    self subclassResponsibility
+!
+
+savePackage:aPackage as:aFilename
+    "saves package"
+    self subclassResponsibility
+!
+
+uninstallPackage:aPackage
+    "uninstalls aPackage from the image"
+    self subclassResponsibility
+!
+
+unloadPackage:aPackage
+    "unloads the package from the receiver"
+    self subclassResponsibility
+! !
+
+!AbstractPackageManager methodsFor:'enumerating'!
+
+packagesDo:aOneArgBlock
+    self packagesDo:aOneArgBlock excluding:#().
+!
+
+packagesDo:aOneArgBlock excluding:aCollectionOrObject
+    "iterate through all packages except for aCollection of packages. Return the receiver.
+    also look at #packagesDo: if you dont want to exclude anything"
+    (aCollectionOrObject isCollection) ifTrue:[
+	self packages do:[:aPackage |
+	    (aCollectionOrObject includes:aPackage) ifFalse:[
+		aOneArgBlock value:aPackage.
+	    ].
+	].
+	^ self.
+    ].
+
+    self packages do:[:aPackage |
+	(aCollectionOrObject == aPackage) ifFalse:[
+	    aOneArgBlock value:aPackage.
+	].
+    ].
+! !
+
+!AbstractPackageManager methodsFor:'initialization'!
+
+initialize
+    packages := self class defaultPackages.
+    ChangeSet current addDependent:self.
+"/    Smalltalk addDependent:self.
+!
+
+uninitialize
+    packages := self class defaultPackages.
+    ChangeSet current removeDependent:self.
+"/    Smalltalk removeDependent:self.
+! !
+
+!AbstractPackageManager methodsFor:'queries'!
+
+includesPackage:aPackage
+    ^ packages includesKey:aPackage name
+!
+
+includesPackageNamed:aPackageName
+
+    ^ packages includesKey:aPackageName
+! !
+
+!AbstractPackageManager class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageManager.st,v 1.4 2006/08/24 08:39:01 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractPackageNotebookApplication.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,318 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageBrowser subclass:#AbstractPackageNotebookApplication
+	instanceVariableNames:'selectedTabHolder canvasHolder tabListHolder tabApplications'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+!AbstractPackageNotebookApplication class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!AbstractPackageNotebookApplication class methodsFor:'constant values'!
+
+applicationName
+    ^ 'No name' asSymbol
+! !
+
+!AbstractPackageNotebookApplication class methodsFor:'defaults'!
+
+tabsNames
+    ^ self tabsNamesAndClasses keys asOrderedCollection sort:[:x :y |
+            x < y
+      ]
+
+"/    ^ #( 
+"/            #(#'Classes'         #Classes)
+"/            #(#'Loose Methods'   #LooseMethod)
+"/            #(#'Scripts'         #Scripts)
+"/            #(#'Prerequisites'   #Prerequisites)
+"/            #(#'Comment'         #Comment)
+"/       ).
+!
+
+tabsNamesAndClasses
+    | dic |
+    dic := Dictionary new.
+
+    self privateClasses do:[:aPrivateClass |  
+            dic at:aPrivateClass applicationName  put:aPrivateClass name
+    ].                                       
+    ^ dic
+
+"/    ^ #( 
+"/            #(#'Classes'         #Classes)
+"/            #(#'Loose Methods'   #LooseMethod)
+"/            #(#'Scripts'         #Scripts)
+"/            #(#'Prerequisites'   #Prerequisites)
+"/            #(#'Comment'         #Comment)
+"/       ).
+! !
+
+!AbstractPackageNotebookApplication class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::AbstractPackageNotebookApplication andSelector:#windowSpec
+     Packages::AbstractPackageNotebookApplication new openInterface:#windowSpec
+     Packages::AbstractPackageNotebookApplication open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageDetails'
+          #name: 'Packages::PackageDetails'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 329 359)
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#NoteBookViewSpec
+              #name: 'PackageDetailsNotebook'
+              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+              #model: #selectedTabHolder
+              #menu: #tabListHolder
+              #selectConditionBlock: #packageDetailsChangeToTabNumber:
+              #canvas: #canvasHolder
+              #postBuildCallback: #selectInitialTab
+            )
+           )
+         
+        )
+      )
+! !
+
+!AbstractPackageNotebookApplication class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+        #list
+        #selectionHolder
+      ).
+
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'accessing'!
+
+selectedTab:aSymbol 
+    ^ self selectedTabHolder value:aSymbol
+!
+
+tabApplications
+    "return the value of the instance variable 'tabApplications' (automatically generated)"
+    tabApplications ifNil:[
+        tabApplications := Dictionary new
+    ].
+    ^ tabApplications
+!
+
+tabApplications:something
+    "set the value of the instance variable 'tabApplications' (automatically generated)"
+
+    tabApplications := something.
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'actions'!
+
+packageDetailsChangeToTabNamed:aSymbol
+    "return a boolean validating if you can change the current selected
+     tab to the tab represented by aSymbol"
+    aSymbol == self selectedTab ifTrue:[
+        ^ self. "do nothing... dont think this can happen 
+                but it means that the #validateChangeTo: methods do not need this check!!"
+    ].
+    ^ (self instanceAtTab:self selectedTab) validateCanChange:(self instanceAtTab:aSymbol)
+!
+
+packageDetailsChangeToTabNumber:anInteger
+    "return a boolean validating if you can change the current selected
+     tab to the tab represented by anInteger"
+    ^ self packageDetailsChangeToTabNamed:(self tabListHolder value at:anInteger)
+!
+
+selectInitialTab
+    self selectedTab:self tabListHolder value first.
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'aspects'!
+
+canvasHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    canvasHolder isNil ifTrue:[
+        canvasHolder := ValueHolder with:(SubCanvas new) .
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       canvasHolder addDependent:self.
+"/       canvasHolder onChangeSend:#canvasHolderChanged to:self.
+    ].
+    ^ canvasHolder.
+!
+
+selectedTab
+    ^ selectedTabHolder value
+!
+
+selectedTabHolder
+
+    selectedTabHolder isNil ifTrue:[
+        selectedTabHolder := ValueHolder new.
+       selectedTabHolder addDependent:self.
+       selectedTabHolder onChangeSend:#selectedTabHolderChanged to:self.
+    ].
+    ^ selectedTabHolder.
+!
+
+tabListHolder
+    "holds the names of the tab in a tabList"
+    tabListHolder isNil ifTrue:[
+        tabListHolder := ValueHolder with:(self class tabsNames).
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       tabList addDependent:self.
+"/       tabList onChangeSend:#tabListChanged to:self.
+    ].
+    ^ tabListHolder.
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'changes'!
+
+selectedTabHolderChanged
+    | instance |
+    instance := self instanceAtTab:self selectedTab.
+
+    instance ifNil:[
+        ^ self
+    ].
+    self canvasHolder value client:(instance).
+!
+
+updateWithPackages:packages
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'factory'!
+
+applicationClassAt:aSymbol 
+    ^ Smalltalk classNamed:(self class tabsNamesAndClasses at:aSymbol).
+
+
+
+
+
+
+
+!
+
+instanceAtTab:aSymbol 
+    | anInstance |
+    ^ self tabApplications at:aSymbol ifAbsentPut:[
+        anInstance := (self applicationClassAt:aSymbol) new.
+        anInstance masterApplication:self.
+        anInstance
+    ].
+! !
+
+!AbstractPackageNotebookApplication methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+    ^ super postOpenWith:aBuilder
+! !
+
+!AbstractPackageNotebookApplication class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractPackageNotebookApplication.st,v 1.3 2006/01/10 09:25:10 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__AbstractTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,193 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+TestCase subclass:#AbstractTestCases
+	instanceVariableNames:''
+	classVariableNames:'ClearUpFiles'
+	poolDictionaries:''
+	category:'Package-TestCases'
+!
+
+Notification subclass:#PackageTestCaseNotification
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:AbstractTestCases
+!
+
+!AbstractTestCases class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+         (james@miraculix)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+history
+    "Created: / 30.1.2003 / 10:54:54 / james"
+! !
+
+!AbstractTestCases methodsFor:'factory'!
+
+packageTestCaseNotification
+    ^ PackageTestCaseNotification
+! !
+
+!AbstractTestCases methodsFor:'helpers'!
+
+aDolphinTestFilePac
+    ^ '~/AvatarChat.pac' asFilename.
+!
+
+assertSmalltalkIncludesAllClassNames:aCollectionOfSymbols 
+    aCollectionOfSymbols do:[:aSymbol |
+        self shouldnt:((Smalltalk at:aSymbol ifAbsent:[nil]) == nil).
+    ].
+!
+
+assertSmalltalkIncludesAllLooseMethods:aCollectionOfLooseMethods
+
+    aCollectionOfLooseMethods do:[:aPackagedMethod |   | class |
+        class := (Smalltalk at:aPackagedMethod mclass name).
+        self assert:(class methodDictionary keys includes:aPackagedMethod name).
+    ].
+!
+
+createMethodFor:aClass source:aString
+    aClass
+        compile:aString
+        classified:'aDummyClassification'
+        notifying:nil.
+!
+
+createTestCaseDirectory
+    "create the testcase directory if i"
+    | testCaseDirectory |
+    (testCaseDirectory := self testCaseDirectory) exists ifFalse:[
+        testCaseDirectory makeDirectory.
+    ].
+!
+
+createTestCaseFilenameFor:aFilenameOrString 
+    ^ self testCaseDirectory filenameFor:aFilenameOrString asFilename
+!
+
+initializePackageManager
+    PackageManager initialize.
+!
+
+packageManager
+    ^ PackageManager smalltalkPackageManager
+!
+
+removeClassNamed:aSymbol 
+    (Smalltalk at:aSymbol) ifNotNil:[
+        ^ (Smalltalk at:aSymbol) removeFromSystem.
+    ]
+!
+
+shouldntSmalltalkIncludesAllClassNames:aCollectionOfSymbols 
+    aCollectionOfSymbols do:[:aSymbol |
+        self assert:((Smalltalk at:aSymbol ifAbsent:[nil]) == nil).
+    ].
+
+!
+
+shouldntSmalltalkIncludesAllLooseMethods:aCollectionOfLooseMethods
+
+    aCollectionOfLooseMethods do:[:aMethod |  | class|
+        class := (Smalltalk classNamed:aMethod className).
+        "if class is nil then the test has also passed"
+        class ifNotNil:[
+            self shouldnt:(class methodDictionary keys includes:aMethod name).
+        ].
+
+    ].
+!
+
+testCaseDirectory
+    ^ (Filename named:'~/work/stx/testCases/')
+! !
+
+!AbstractTestCases methodsFor:'initialize / release'!
+
+setUp
+    "common setup - invoked before testing"
+    self initialize.
+    super setUp
+!
+
+tearDown
+    "common cleanup - invoked after testing"
+
+    super tearDown
+! !
+
+!AbstractTestCases methodsFor:'instance creation'!
+
+createClassNamed:aClassName 
+    self createClassNamed:aClassName inheritsFrom:#Object
+!
+
+createClassNamed:aClassName inheritsFrom:anInheritingClassName
+    ^ (Smalltalk at:anInheritingClassName) 
+        subclass:aClassName
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        category:'AAAAA'
+        classInstanceVariableNames:''
+! !
+
+!AbstractTestCases methodsFor:'queries'!
+
+clearUpFiles
+    ClearUpFiles ifNil:[
+        ClearUpFiles := false.
+    ].
+
+    ^ ClearUpFiles
+! !
+
+!AbstractTestCases class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/AbstractTestCases.st,v 1.3 2006/01/10 09:29:37 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__ChangeFaker.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,178 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#ChangeFaker
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+ClassChange subclass:#ClassPackageChange
+	instanceVariableNames:'oldPackageName'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ChangeFaker
+!
+
+MethodChange subclass:#MethodPackageChange
+	instanceVariableNames:'oldPackageName'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ChangeFaker
+!
+
+!ChangeFaker class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!ChangeFaker class methodsFor:'initialization'!
+
+initialize
+"/    Smalltalk addDependent:self.
+!
+
+update:something with:aParameter from:changedObject
+    | oldPackageName movedClass methodOwnedClass oldMethod|
+    (something == #projectOrganization) ifTrue:[
+        aParameter ifNil:[
+            "no need to know about this. It has probably already been past here already!!"
+            ^ self
+        ].
+
+        aParameter size == 1 ifTrue:[
+            Transcript 
+                    nextPutAll:'From PackageManager>>update:with:from:' ; 
+                    cr;
+                    nextPutAll:'When does this happen' ; 
+                    cr.
+                    "checking out changedObject = Smalltalk"
+
+            ^ self.
+        ].
+
+        aParameter size == 2 ifTrue:[
+               oldPackageName := aParameter second.
+               movedClass := aParameter first.
+               (oldPackageName isSymbol) ifTrue:[
+               
+               self classMovePackageChangeWithClass:movedClass
+                    oldPackageName:oldPackageName.
+
+            ^ self.
+            ] ifFalse:[  
+                "it is a method move but the change will be called again as 3 parameters
+                 it is implemented in two ways. One by NewSystemBrowser>>moveMethods:toProject:
+                 and  Method>>package i only care for the one implemented in method as it gives
+                 me the previous package information"
+                ^ self
+            ].
+        ].
+
+        aParameter size == 3 ifTrue:[
+                oldMethod := (aParameter second).
+                methodOwnedClass := (aParameter first).
+                oldPackageName :=  (aParameter third).
+                self 
+                    methodMovePackageChangeWithMethod:oldMethod      
+                    class:methodOwnedClass 
+                    oldPackageName:oldPackageName.
+                ^ self.
+        ].
+        self breakPoint:''.
+    ].
+! !
+
+!ChangeFaker class methodsFor:'accessing'!
+
+changeSet
+    ^ ChangeSet current
+! !
+
+!ChangeFaker class methodsFor:'faked - changes'!
+
+classMovePackageChangeWithClass:class oldPackageName:oldPackageName 
+    | fakedChange |
+    fakedChange := ClassPackageChange className:class name oldPackageName:oldPackageName.
+    self changeSet changed:#addChange: with:fakedChange.
+!
+
+methodMovePackageChangeWithMethod:movedMethod class:methodOwnedClass oldPackageName:oldPackageName
+    | fakedChange |
+    fakedChange := (MethodPackageChange new) 
+            previousVersion:movedMethod;
+            className:methodOwnedClass name;
+            oldPackageName:oldPackageName.
+
+    self changeSet changed:#addChange: with:fakedChange.
+! !
+
+!ChangeFaker::ClassPackageChange class methodsFor:'instance creation'!
+
+className:className oldPackageName:oldPackageName 
+    ^ (self basicNew) 
+            className:className;
+            oldPackageName:oldPackageName;
+            package:(Smalltalk classNamed:className) package
+! !
+
+!ChangeFaker::ClassPackageChange methodsFor:'accessing'!
+
+oldPackageName
+    "return the value of the instance variable 'oldPackageName' (automatically generated)"
+
+    ^ oldPackageName
+!
+
+oldPackageName:something
+    "set the value of the instance variable 'oldPackageName' (automatically generated)"
+
+    oldPackageName := something.
+! !
+
+!ChangeFaker::MethodPackageChange methodsFor:'accessing'!
+
+oldPackageName
+    "return the value of the instance variable 'oldPackageName' (automatically generated)"
+
+    ^ oldPackageName
+!
+
+oldPackageName:something
+    "set the value of the instance variable 'oldPackageName' (automatically generated)"
+
+    oldPackageName := something.
+! !
+
+!ChangeFaker class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ChangeFaker.st,v 1.3 2006/01/10 09:29:32 cg Exp $'
+! !
+
+ChangeFaker initialize!
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__ChangesHelper.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,56 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#ChangesHelper
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+!ChangesHelper class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!ChangesHelper class methodsFor:'accessing'!
+
+getCurrentMethodFromMethodChange:aChange
+    | classOrNil |
+    classOrNil := Smalltalk classNamed:(aChange className).
+    classOrNil ifNil:[
+        ^ nil
+    ].
+
+    ^ classOrNil compiledMethodAt:aChange selector
+! !
+
+!ChangesHelper class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ChangesHelper.st,v 1.2 2006/01/10 09:29:34 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__ClassPrerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,57 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Prerequisite subclass:#ClassPrerequisite
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Prerequisite'
+!
+
+!ClassPrerequisite class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!ClassPrerequisite methodsFor:'evaluation'!
+
+testCondition
+    "returns a boolean"
+    ^ (Smalltalk at:name) notNil
+! !
+
+!ClassPrerequisite methodsFor:'queries'!
+
+isClassPrerequisite
+    ^ true
+! !
+
+!ClassPrerequisite class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/ClassPrerequisite.st,v 1.2 2006/01/10 09:29:39 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__DefaultPackage.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,159 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Package subclass:#DefaultPackage
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package'
+!
+
+!DefaultPackage class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!DefaultPackage methodsFor:'changes'!
+
+classChange:classChange
+    | newClass |
+    newClass := (Smalltalk classNamed:classChange className).
+    newClass ifNil:[
+        self error:'The class named ', newClass name,
+            'does not exist!! It is expected to exist from a class change!!'
+    ].
+
+    self addedClass:newClass.
+    self changed:#classChange: with:classChange
+!
+
+classDefinitionChange:aClassDefinitionChange 
+    | newClass |
+    newClass := (Smalltalk classNamed:aClassDefinitionChange className).
+    newClass ifNil:[
+        self error:'The class named ', newClass name,
+            'does not exist!! It is expected to exist from a class redefinition action!!'
+    ].
+
+    self addedClass:newClass.
+    self changed:#classDefinitionChange: with:aClassDefinitionChange
+!
+
+classInstVarDefinitionChange:aClassInstVarDefinitionChange 
+
+    | newClass |
+    newClass := (Smalltalk classNamed:aClassInstVarDefinitionChange className).
+    newClass ifNil:[
+        self error:'The class named ', newClass name,
+            'does not exist!! It is expected to exist from a class redefinition action!!'
+    ].
+
+    self addedClass:newClass.
+    self changed:#classDefinitionChange: with:aClassInstVarDefinitionChange
+!
+
+classRemoveChange:aClassRemoveChange
+
+    self removedClassNamed:aClassRemoveChange className.
+    self changed:#classRemoveChange: with:aClassRemoveChange
+!
+
+methodChanged:aMethodChange
+    "a method as changed. The receiver must be responsible for all changes to the image
+    so if it is not. make sure it does now!!"
+    |aMethodName aClassName aMethod |
+    aMethodName := aMethodChange selector.
+    aClassName := aMethodChange className asSymbol.
+    aMethod := (Smalltalk classNamed:aClassName) compiledMethodAt:aMethodName.
+
+    self addedMethod:aMethod.
+    self changed:#methodChanged: with:aMethodChange
+!
+
+methodRemoveChange:aMethodRemoveChange 
+
+    self removedMethodNamed:aMethodRemoveChange selector forClassNamed:aMethodRemoveChange className.
+    self changed:#methodRemoveChange: with:aMethodRemoveChange
+! !
+
+!DefaultPackage methodsFor:'queries'!
+
+isDependentOnClassChange:classChange
+    "checks to see if the receiver is affected by the change. returns a boolean
+    "
+    ^ classChange changeClass package == name
+"/    ^ (super isDependentOnClassChange:classChange) not
+!
+
+isDependentOnClassDefinitionChange:aClassDefinitionChange 
+    ^ aClassDefinitionChange changeClass package == name "and:[
+        (super isDependentOnClassDefinitionChange:aClassDefinitionChange) not
+    ]                                                      "
+
+!
+
+isDependentOnClassInstVarDefinitionChange:aClassInstVarDefinitionChange 
+    ^ aClassInstVarDefinitionChange changeClass package == name
+
+"/    ^ (super isDependentOnClassInstVarDefinitionChange:aClassInstVarDefinitionChange) not
+!
+
+isDependentOnClassRemoveChange:aClassRemoveChange
+    | classBeingRemoved |
+    classBeingRemoved := ClassRemoveChange::ClassBeingRemovedQuery query.
+    ^ classBeingRemoved package == name
+    
+"/    ^ (super isDependentOnClassRemoveChange:aClassRemoveChange)
+!
+
+isDependentOnClassRenameChange:classChange
+
+    ^ classChange changeClass package == name
+"/    ^ (super isDependentOnClassRenameChange:classChange) not
+!
+
+isDependentOnMethodCategoryChange:aMethodRemoveChange 
+    ^ (super isDependentOnMethodCategoryChange:aMethodRemoveChange)
+!
+
+isDependentOnMethodCategoryRenameChange:aMethodRemoveChange 
+    ^ (super isDependentOnMethodCategoryRenameChange:aMethodRemoveChange)
+!
+
+isDependentOnMethodChange:aMethodChange
+    ^ (super isDependentOnMethodChange:aMethodChange) not
+!
+
+isDependentOnMethodRemoveChange:aMethodRemoveChange 
+    ^ (super isDependentOnMethodRemoveChange:aMethodRemoveChange) not
+! !
+
+!DefaultPackage class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/DefaultPackage.st,v 1.2 2006/01/10 09:29:41 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__DictionaryStack.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,153 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#DictionaryStack
+	instanceVariableNames:'collection'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+!DictionaryStack class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!DictionaryStack class methodsFor:'instance creation'!
+
+new
+    ^ self basicNew initialize.
+! !
+
+!DictionaryStack methodsFor:'* As yet uncategorized *'!
+
+collect:aBlock
+    ^ collection values collect:aBlock
+! !
+
+!DictionaryStack methodsFor:'adding & removing'!
+
+atKey:aSymbol 
+    
+    ^ collection at:aSymbol
+!
+
+atKey:aSymbol ifAbsent:aBlock
+    
+    ^ collection at:aSymbol ifAbsent:aBlock
+!
+
+pop
+    collection removeKey:collection last key
+!
+
+pop:aNumber 
+
+    aNumber timesRepeat:[ self pop].
+!
+
+popAt:aKey 
+    collection removeKey:aKey.
+!
+
+popAt:aKey ifAbsent:aBlock
+    collection removeKey:aKey ifAbsent:aBlock.
+!
+
+pull
+    ^ self pop
+!
+
+pull:aNumber
+    | col |
+    col :=  collection last:aNumber.
+    self pop:aNumber.
+    ^ col
+!
+
+pullAt:aKey 
+    ^ collection removeKey:aKey.
+!
+
+pullAt:aKey ifAbsent:aBlock
+    ^ collection removeKey:aKey ifAbsent:aBlock.
+!
+
+push:aPackage 
+    
+    ^ collection at:aPackage name put:aPackage
+!
+
+removeKey:aSymbol 
+    
+    ^ collection removeKey:aSymbol
+!
+
+top
+    ^ collection last value
+! !
+
+!DictionaryStack methodsFor:'enumerating'!
+
+do:aBlock 
+    "goes through all the objects in the collection"
+    collection reverseDo:[:anAssociation | aBlock value:anAssociation value]
+!
+
+select:aBlock 
+    ^ collection values select:aBlock
+! !
+
+!DictionaryStack methodsFor:'initialization'!
+
+initialize
+    collection := OrderedDictionary new.
+! !
+
+!DictionaryStack methodsFor:'queries'!
+
+includes:aPackage
+    ^ collection includes:aPackage
+!
+
+includesKey:aKey
+    ^ (collection includesKey:aKey)
+!
+
+isEmpty
+    ^ collection isEmpty
+!
+
+size
+    ^ collection size
+! !
+
+!DictionaryStack class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/DictionaryStack.st,v 1.2 2006/01/10 09:25:12 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__Package.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,2340 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackage subclass:#Package
+	instanceVariableNames:'packageHandler packagedClasses packagedMethods packageComment
+		prerequisites scripts isDirty isInstalled packageVersion
+		overriddenClassChanges overriddenMethodChanges blockedMethods'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package'
+!
+
+Package class instanceVariableNames:'CurrentPackage'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
+Object subclass:#PackagedClass
+	instanceVariableNames:'name package instanceDefinition classDefinition
+		instanceVariableNames classVariableNames
+		classInstanceVariableNames poolDictionaries category'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Package
+!
+
+Object subclass:#ClassSide
+	instanceVariableNames:'instanceSide'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Package::PackagedClass
+!
+
+Object subclass:#PackagedMethod
+	instanceVariableNames:'name package category source ownedClassName'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Package
+!
+
+Object subclass:#PackagedScript
+	instanceVariableNames:'string receiver'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Package
+!
+
+!Package class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+	 (james@miraculix)
+
+    [instance variables:]
+
+	blockedMethods                <Dictionary>
+					    A reference of methods that the receiver is NOT responsible for
+					    but the receiver is responsible for the method's class. It usage is
+					    the same as a filter would be.
+
+	overriddenChanges                <Dictionary1><Dictionary2><Dictionary3>
+					    This variable helps the receiver keep its original state. When a
+					    method changes it is held here so we can get the original. So the package
+					    is still responsible for the overridden changes.
+
+					    There are two way items can become added to overriddenChanges:
+						1) through loading packages - too many of these may not be desirable.
+						2) through editing a package - default package 'overrides it!!'
+
+					    DESIGN: it is designed with dictionaries containing dictionaries as - for the
+						time being - to cope with different types of change. At the moment being
+						methodChanges (and soon classChanges). It is easier to search for changes
+						by using this hierarchy of dictionaries, and - i think - it is quite
+						extendable.
+						The only problem i can see with it is lingering dictionaries which are not deleted
+						when they contain nothing.
+
+
+
+
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+examples
+"
+
+   more  examples to be added:
+								[exBegin]
+    ... add code fragment for
+    ... executable example here ...
+								[exEnd]
+"
+!
+
+history
+    "Created: / 31.3.2003 / 16:45:04 / james"
+! !
+
+!Package class methodsFor:'instance creation'!
+
+named:aString
+    "create a new package named aString "
+    ^ self named:aString asSymbol addToManager:nil.    "or 'self defaultPackageManager'"
+!
+
+named:aString addToManager:aManager
+    ^ self named:aString withClasses:nil withMethods:nil addToManager:aManager
+!
+
+named:aString withClasses:classes
+    ^ self named:aString withClasses:classes withMethods:nil addToManager:nil
+!
+
+named:aString withClasses:classes withMethods:methods addToManager:aManager
+    "create a new package named aString "
+    |anInstance |
+    anInstance := self new name:aString.
+    classes ifNotNil:[
+	anInstance addedClasses:classes.
+    ].
+    methods ifNotNil:[
+	anInstance addedMethods:methods.
+    ].
+
+    aManager ifNotNil:[
+	aManager addPackage:anInstance.
+    ].
+    ^ anInstance
+!
+
+named:aString withMethods:methods
+    ^ self named:aString withClasses:nil withMethods:methods addToManager:nil
+! !
+
+!Package class methodsFor:'defaults'!
+
+defaultBlockedMethodsCollection
+    ^ Dictionary new
+!
+
+defaultOverriddenChangesCollection
+    "a dictionary of sets. The keys are the classes and
+    the sets are a collection of selectors!!"
+    ^ Dictionary new
+!
+
+defaultPackagedClassesCollection
+    ^ Dictionary new
+!
+
+defaultPackagedMethodsCollection
+    ^ Dictionary new
+!
+
+defaultPrerequisiteCollection
+    ^ PrerequisiteCollection new
+!
+
+defaultScriptsCollection
+    ^ IdentityDictionary new
+!
+
+newDefaultPackage
+    ^ self named:(Project noProjectID).
+!
+
+packageManager
+    ^ self packageManagerClass smalltalkPackageManager.
+!
+
+packageManagerClass
+    ^ PackageManager.
+! !
+
+!Package class methodsFor:'private - instance creation'!
+
+new
+    "creates a new package and initialize's"
+    | anInstance |
+    anInstance := self basicNew initialize.
+    ^ anInstance
+! !
+
+!Package methodsFor:'accessing'!
+
+blockedMethods
+    "return the value of the instance variable 'blockedMethods' (automatically generated)"
+
+    ^ blockedMethods
+!
+
+blockedMethods:something
+    "set the value of the instance variable 'blockedMethods' (automatically generated)"
+
+    blockedMethods := something.
+!
+
+blockedMethodsAtClassNamed:arg
+    ^ (blockedMethods at:arg ifAbsent:[nil])
+!
+
+blockedMethodsAtClassNamed:aClassName ifAbsentPut:anObject
+    ^ blockedMethods at:aClassName ifAbsentPut:anObject
+!
+
+blockedMethodsRemoveAtClassNamed:arg ifAbsent:aBlock
+    ^ (blockedMethods removeKey:arg ifAbsent:aBlock)
+!
+
+classNames
+    ^ self packagedClasses values collect:[:aPackagedClass |
+	aPackagedClass name
+    ].
+!
+
+classPrerequisites
+    ^ prerequisites select:[:aPre |
+	aPre isClassPrerequisite
+    ].
+
+!
+
+filename
+    "return the value of the instance variable 'filename' (automatically generated)"
+
+    ^ packageHandler filename
+!
+
+getInterestedMethodsFromClass:aClass
+    | aClassName |
+    aClassName := aClass name.
+    ^ aClass methodDictionary copy values select:[:aMethod |
+	self definesSelector:aMethod name forClassNamed:aClassName
+    ]
+!
+
+getInterestedPackagedMethodsFromClass:aClass
+    | aClassName aPackagedClass|
+
+    aClassName := aClass name.
+    (aPackagedClass := self packagedClassNamed:aClassName) ifNotNil:[
+	^ aPackagedClass packagedMethods
+    ].
+
+    ^ (packagedMethods at:aClassName ifAbsent:[^ OrderedCollection new ]) values
+"/    ^ aClass methodDictionary copy values collectAndselect:[:aMethod |
+"/        self definesSelector:aMethod name forClassNamed:aClassName
+"/    ]
+"/
+
+!
+
+isDirty
+   "has the receiver been changed by adding scripts or added classes since the
+    time it is loaded. This instance variable is NOT affected by changes in the image!!
+    but it could be worked out by looking at the receivers variables!!"
+
+   ^ isDirty "? true" "not needed because set by initialize"
+!
+
+isDirty:aBoolean
+    isDirty := aBoolean
+!
+
+isInstalled
+    "return the value of the instance variable 'isInstalled' (automatically generated)"
+
+    ^ isInstalled
+!
+
+isInstalled:something
+    "set the value of the instance variable 'isInstalled' (automatically generated)"
+
+    isInstalled := something.
+!
+
+looseMethodAtClass:aClassName atMethodName:aMethodName
+    self looseMethods do:[:aLooseMethod |
+	((aLooseMethod name == aMethodName) and:[
+	    aLooseMethod className == aClassName]) ifTrue:[
+		^ aLooseMethod
+	].
+
+    ].
+    ^ nil
+!
+
+looseMethods
+    | col mthdInImage |
+    col := OrderedCollection new.
+    self packagedMethods keysAndValuesDo:[:key :aDic | | looseMethodsInKey|
+
+	looseMethodsInKey := aDic keysAndValuesDo:[:selector :aPackagedMethod  | |collectValue|
+	    aPackagedMethod isLoose ifTrue:[
+		mthdInImage := aPackagedMethod methodInImage.
+		   col add:aPackagedMethod.
+	    ].
+	].
+
+    ].
+
+    ^ col.
+!
+
+packageComment
+    "return the value of the instance variable 'packageComment' (automatically generated)"
+
+    ^ packageComment
+!
+
+packageComment:something
+    "set the value of the instance variable 'packageComment' (automatically generated)"
+
+    packageComment := something.
+!
+
+packageHandler
+    "return the value of the instance variable 'packageHandler' (automatically generated)"
+
+    packageHandler isNil ifTrue:[
+	packageHandler := PackageHandler forPackage:self.
+    ].
+    ^ packageHandler
+!
+
+packageHandler:something
+    "set the value of the instance variable 'packageHandler' (automatically generated)"
+
+    packageHandler := something.
+!
+
+packagePrerequisites
+    ^ prerequisites select:[:aPre |
+	aPre isPackagePrerequisite
+    ].
+
+!
+
+packageType
+    ^ 'STX Package' copy.
+!
+
+packageVersion
+    "return the value of the instance variable 'packageVersion' (automatically generated)"
+
+    ^ packageVersion
+!
+
+packageVersion:something
+    "set the value of the instance variable 'packageVersion' (automatically generated)"
+
+    packageVersion := something.
+!
+
+packagedClasses
+    "return the value of the instance variable 'packagedClasses' (automatically generated)"
+
+    ^ packagedClasses
+!
+
+packagedMethods
+    "return the value of the instance variable 'packagedMethods' (automatically generated)"
+
+    ^ packagedMethods
+!
+
+packagedMethodsAtClassName:arg ifAbsent:aBlock
+    ^ (packagedMethods at:arg ifAbsent:aBlock)
+!
+
+packagedMethodsAtClassNamed:arg
+    ^ (self packagedMethodsAtClassNamed:arg ifAbsent:[])
+!
+
+packagedMethodsAtClassNamed:arg ifAbsent:aBlock
+    ^ (packagedMethods at:arg ifAbsent:aBlock)
+!
+
+packagedMethodsAtClassNamed:arg ifAbsentPut:aBlock
+    ^ (packagedMethods at:arg ifAbsentPut:aBlock)
+!
+
+packagedMethodsForClass:arg ifAbsent:aBlock
+    ^ (packagedMethods at:arg ifAbsent:aBlock)
+!
+
+prerequisites
+    "return the value of the instance variable 'prerequisites' (automatically generated)"
+
+    ^ prerequisites
+!
+
+scripts
+    "return the value of the instance variable 'scripts' (automatically generated)"
+
+    ^ scripts
+! !
+
+!Package methodsFor:'adding & removing'!
+
+addBlockedMethodNamed:aMethodName forClassNamed:aClassName
+    ^ (self blockedMethodsAtClassNamed:aClassName ifAbsentPut:[Set new]) add:aMethodName.
+!
+
+addOverriddenClassChange:aPackagedClass byPackageNamed:byPackageName
+    "add an overridden method. under #package -> #className -> #classChangeNamespace -> aPackagedClass"
+    | className |
+    self assert:(byPackageName isSymbol).
+    className := aPackagedClass name.
+
+    ((overriddenClassChanges at:byPackageName ifAbsentPut:[Set new])
+	add:className)
+!
+
+addOverriddenMethodChange:aPackagedMethod byPackageNamed:byPackageNamed
+    "add an overridden method. under #package -> #methodClassName -> #packagedMethod"
+    | methodClassName |
+    methodClassName := aPackagedMethod ownedClassName.
+    "so that we have this method stored"
+    self addPackagedMethod:aPackagedMethod.
+
+    (((overriddenMethodChanges at:byPackageNamed ifAbsentPut:[Dictionary new])
+	at:methodClassName ifAbsentPut:[Set new]) add:aPackagedMethod name)
+!
+
+addPackagedClass:aPackagedClass
+    "adds a class to the receiver.
+     NOTE: Does not mark the receiver as dirty.
+     That is the responsibility of the called of this method!!"
+    aPackagedClass isClass ifTrue:[
+	self error:'I am expected a PackagedClass not a Class'.
+    ].
+    self packagedClasses at:aPackagedClass name put:(aPackagedClass).
+    ^ aPackagedClass
+!
+
+addPackagedMethod:aPackagedMethod
+    "add or replace aPackagedMethod from the receiver"
+    | aPackagedMethodsOwnedClass |
+    aPackagedMethodsOwnedClass := aPackagedMethod ownedClassName.
+    ^ (self packagedMethodsAtClassNamed:aPackagedMethodsOwnedClass ifAbsentPut:[Dictionary new])
+		at:aPackagedMethod name put:aPackagedMethod.
+!
+
+addPackagedMethods:somePackageMethods
+
+    somePackageMethods do:[:aPackageMethod |
+	self addPackagedMethod:aPackageMethod copy.
+    ].
+    ^ somePackageMethods
+!
+
+addPrerequisite:aPrerequisite
+    prerequisites add:aPrerequisite
+!
+
+addedPackagedClasses:somePackagedClasses
+    somePackagedClasses do:[:each |
+	self addedPackagedClass:each
+    ].
+    ^ somePackagedClasses
+!
+
+packagedClassesRemoveAtClassName:aKey ifAbsent:aBlock
+    ^ self packagedClasses removeKey:aKey ifAbsent:aBlock
+!
+
+removeBlockedMethodNamed:aMethodName forClassNamed:aClassName
+    ^ (self blockedMethodsAtClassNamed:aClassName) remove:aMethodName.
+!
+
+removeBlockedMethodsForClassNamed:aClassName ifAbsent:aBlock
+    ^ (blockedMethods removeKey:aClassName ifAbsent:aBlock).
+!
+
+removeOverriddenMethodNamed:aMethodName forClassNamed:aClassName
+    ^ self
+	removeOverriddenMethodNamed:aMethodName
+	forClassNamed:aClassName
+	ifAbsent:[self error:'trying to remove a method that does not exist!!'"should i keep this?"]
+!
+
+removeOverriddenMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock
+
+    | dictionaryOfMethodNamesAndPackagedMethods removedPackagedMethod|
+
+    overriddenMethodChanges values do:[:aDictionaryOfClassNamesAndPackagedMethods |
+	(dictionaryOfMethodNamesAndPackagedMethods :=
+	    aDictionaryOfClassNamesAndPackagedMethods at:aClassName ifAbsent:[nil]).
+	dictionaryOfMethodNamesAndPackagedMethods ifNotNil:[
+	    removedPackagedMethod := (dictionaryOfMethodNamesAndPackagedMethods remove:aMethodName ifAbsent:[nil]).
+	    removedPackagedMethod ifNotNil:[  "once found it can just exit as there should not be any more here!!"
+		^ self
+	    ].
+	].
+
+    ].
+!
+
+scriptAt:aSymbol
+    ^ scripts at:aSymbol ifAbsent:[PackagedScript string:(String new) receiver:self]
+!
+
+scriptAt:aSymbol put:aString
+    scripts at:aSymbol put:aString
+! !
+
+!Package methodsFor:'adding & removing - basic'!
+
+basicAddedClass:aClass
+    "add a representation of a class (PackagedClass) to the receiver.
+    Look in aClass to see if we need to add any blocked methods - this could
+    be done by the manager but is done locally to avoid too many message sends"
+    | newPackagedClass |
+    self assert:(aClass isMeta not).
+    newPackagedClass := (self newPackagedClass:aClass).
+    self basicAddedPackagedClass:newPackagedClass.
+
+    (aClass methodDictionary copy) keysAndValuesDo:[:aMethodName :aMethod |
+	(aMethod package == self name) ifFalse:[
+	    newPackagedClass addBlockedMethodNamed:aMethodName.
+	].
+    ].
+    ^ aClass
+
+
+!
+
+basicAddedMethod:aMethod
+    "needed for as it does not have a change notification and does not mark the receiver
+    as dirty"
+    | aPackagedMethod aMethodName aMethodClassName|
+
+    aMethodClassName :=  aMethod mclass name asSymbol.
+    aMethodName := aMethod name.
+
+    (self includesPackagedClassNamed:aMethodClassName) ifTrue:[
+	^ (self packagedClassNamed:aMethodClassName) addMethodNamed:aMethodName
+    ].
+
+    aPackagedMethod := (self newPackagedMethodSelector:aMethodName className:aMethodClassName source:aMethod source).
+
+    self addPackagedMethod:aPackagedMethod.
+
+    ^ aPackagedMethod "if nil, the method is still to be installed. Could use a dummy here instead??"
+!
+
+basicAddedPackagedClass:aPackagedClass
+    "Add a class to a package. Return the aClass.
+    This only works when 'aClass package == name' if not and error will occur.
+    This method is called only AFTER the class package has changed!! This class
+    is NOT responsible for changing values in classes!!
+    "
+    | aPackagedClassName |
+    aPackagedClassName := aPackagedClass name.
+    self assert:(aPackagedClassName isSymbol).
+    (aPackagedClass package == self) ifFalse:[
+	self error:'Cannot add ', aPackagedClassName, ' to package ''', name,
+	    ''' as the class ',  aPackagedClassName, Character cr asString,
+	    ' belongs in the package''', aPackagedClass package name asString,''''.
+    ].
+    (self includesPackagedClassNamed:aPackagedClass name) ifTrue:[
+	(self overriddenClassChangesIncludesClassNamed:aPackagedClass name) ifFalse:[
+	    PackageError raiseAddedClassFailedNamed:aPackagedClass name toPackage:self.
+	].
+    ].
+
+    self removeOverriddenClassNamed:aPackagedClassName ifAbsent:[nil].
+    self removeBlockedMethodsForClassNamed:aPackagedClassName ifAbsent:[nil].
+    self packagedClasses at:aPackagedClassName put:(aPackagedClass).
+    ^ aPackagedClass
+!
+
+basicRemoveClassNamed:aSymbol
+
+    packagedClasses removeKey:aSymbol ifAbsent:[
+	"how much information do i need to recover from this error?"
+	PackageError raiseCannotRemoveClassNamed:aSymbol fromPackage:self
+	"'Cannot remove packagedClass ', aSymbol asString,
+	    ' from package: ', name string."
+    ].
+    self blockedMethodsRemoveAtClassNamed:aSymbol ifAbsent:[nil "a blocked method is not always there!!"].
+    self removeOverriddenClassNamed:aSymbol ifAbsent:[nil "a overridden class is not always there!!"].
+    ^ aSymbol
+!
+
+basicRemoveMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock
+    "remove method named aMethodName from the receiver. If it is in loose methods, remove it,
+    if the receiver just owns the class, add it to the blockedMethods if teh blockedMethods already have it,
+    evaluate aBlock"
+    | aPackagedMethod |
+    (self includesPackagedClassNamed:aClassName) ifTrue:[
+	^ (self packagedClassNamed:aClassName) basicRemoveMethodNamed:aMethodName ifAbsent:aBlock
+    ].
+
+    (self packagedMethodsAtClassName:aClassName ifAbsent:aBlock)
+	removeKey:aMethodName ifAbsent:aBlock.
+
+    (self overriddenChangesIncludesMethodName:aMethodName forClassNamed:aClassName) ifTrue:[
+	self removeOverriddenMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock
+    ].
+
+    ^ aPackagedMethod
+
+
+! !
+
+!Package methodsFor:'api - accessing'!
+
+changePackageOverrideFromPackage:fromPackage toPackage:toPackage forClassNamed:className
+    "assumes that all the checks have been made that this className and these
+    packages do exist!!"
+    | overridenClassChangesHoldersForPackage |
+    overridenClassChangesHoldersForPackage := (overriddenClassChanges at:fromPackage name).
+    overridenClassChangesHoldersForPackage remove:className.
+
+    self overrideClassNamed:className byPackageNamed:toPackage name.
+
+    "cleanUp empty collections which are not needed!!"
+    overriddenClassChanges size == 0 ifTrue:[
+	(overriddenClassChanges removeKey:fromPackage name)
+    ].
+!
+
+changeSet
+    | changeSet |
+    changeSet := ChangeSet new.
+    packagedClasses do:[:aPackagedClass |
+       changeSet addAll:aPackagedClass changeSet
+    ].
+    self looseMethods do:[:aPackageMethod | | aMethod aClass |
+	changeSet addMethodChange:aPackageMethod method in:aPackageMethod ownedClass
+    ].
+
+    ^ changeSet
+!
+
+classCategories
+    | return |
+    return := Set new.  "to make sure that each category is unique"
+    self packagedClassesDo:[:aPackagedClass |
+	return add:aPackagedClass category.
+    ].
+    ^ return asOrderedCollection sort:[:x :y | x > y].
+!
+
+classesInCategory:aCategory
+    | collectingClasses |
+    collectingClasses := OrderedCollection new.
+
+    self packagedClassesDo:[:aPackagedClass |
+	aPackagedClass category == aCategory ifTrue:[
+	    collectingClasses add: aPackagedClass.
+	].
+    ].
+    ^ collectingClasses
+!
+
+overriddenClassNamesByPackage:aPackage
+    ^ (overriddenClassChanges at:aPackage name ifAbsent:[^#() "empty"]) asOrderedCollection.
+!
+
+overriddenClassesByPackage:aPackage
+    ^ (self overriddenClassNamesByPackage:aPackage) collect:[:aPackagedClassName |
+	self packagedClassNamed:aPackagedClassName
+    ]
+!
+
+overriddingPackageNameAtClassName:aClassName
+    "returns a PackagedClass or nil"
+    overriddenClassChanges keysAndValuesDo:[:packageName :aSetOfClassNames |
+	(aSetOfClassNames includes:aClassName) ifTrue:[
+	    ^ packageName
+	].
+    ].
+    ^ nil.
+!
+
+packagedClassNamed:aSymbol
+    ^ (self packagedClassNamed:aSymbol ifAbsent:[nil])
+!
+
+packagedClassNamed:aSymbol ifAbsent:aBlock
+    | classWithoutClassEnding |
+    classWithoutClassEnding := (aSymbol asString copyUpTo:Character space) asSymbol.
+
+    (classWithoutClassEnding size < aSymbol asString size) ifTrue:[
+	"here i am making a crude assumption that aSymbol is refering to the class side of a class.
+	whether i should check if this is true or not is another matter..."
+	^ (packagedClasses at:classWithoutClassEnding ifAbsent:[^ aBlock value]) classSide
+    ].
+
+    ^ (packagedClasses at:aSymbol "or classWithoutClassEnding" ifAbsent:[^ aBlock value])
+!
+
+packagedMethodNamed:aSymbol forClassNamed:aClassName
+    ^ (self packagedMethodNamed:aSymbol forClassNamed:aClassName ifAbsent:[nil])
+!
+
+packagedMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock
+    | returnValue  packagedMethodsAtClassName |
+    packagedMethodsAtClassName := (self packagedMethods at:aClassName ifAbsent:[nil]).
+    packagedMethodsAtClassName ifNotNil:[
+	returnValue := packagedMethodsAtClassName at:aMethodName ifAbsent:[nil].
+    ].
+
+    returnValue ifNil:[
+	(self definesSelector:aMethodName forClassNamed:aClassName) ifTrue:[| smalltalkMethod|
+	    smalltalkMethod := (Smalltalk classNamed:aClassName) compiledMethodAt:aMethodName.
+	    smalltalkMethod ifNil:[^ self error:'I am in an impossible state!!'].
+	    ^ self newPackagedMethodWithMethod:smalltalkMethod
+
+	].
+	aBlock value
+    ].
+
+    ^ returnValue.
+!
+
+workingPackage
+    "Breaks encapsulation, but handy... may need a re-think"
+    ^ Class packageQuerySignal query.
+! !
+
+!Package methodsFor:'api - adding & removing'!
+
+addClassNamed:aClass
+    "called when adding a class on startup."
+    ^ self addPackagedClass:(PackagedClass name:aClass package:self)
+!
+
+addMethodNamed:aMethodName forClassNamed:aClassName
+    "This is what i should sort out on MONDAY!!!!!!!!!! This is wrong!!!!!! I should be handed down the
+    REAL methods which are added to me so that i can extract the source!!"
+    | aPackagedMethod |
+
+    (self includesPackagedClassNamed:aClassName) ifTrue:[
+	^ (self packagedClassNamed:aClassName) addMethodNamed:aMethodName
+    ].
+
+    aPackagedMethod := (self newPackagedMethodSelector:aMethodName  className:aClassName).
+
+    self addPackagedMethod:aPackagedMethod.
+
+    self markDirty.
+    ^ aPackagedMethod "if nil, the method is still to be installed. Could use a dummy here instead??"
+!
+
+addedClass:aClass
+    "Add a class to a package. Return the aClass.
+    This only works when 'aClass package == name' if not and error will occur.
+    This method is called only AFTER the class package has changed!! This class
+    is NOT responsible for changing values in classes!!
+    "
+    self basicAddedClass:aClass.
+    self markDirty.
+    self changed:#addedClass: with:aClass.
+    ^ aClass
+!
+
+addedClasses:aClasses
+    "Add a class to a package. Return the aClass"
+    aClasses do:[:aClass |
+	self basicAddedClass:aClass.
+    ].
+
+    self markDirty.
+    self changed:#addClasses: with:aClasses.
+    ^ aClasses
+!
+
+addedMethod:aMethod
+    "Add a method to a package. Return the aMethod"
+    self basicAddedMethod:aMethod.
+    self markDirty.
+    self changed:#addedMethod: with:aMethod.
+    ^ aMethod
+!
+
+addedMethods:someMethods
+    "Add someMethods to a package. Return the someMethods"
+    someMethods do:[:aMethod |
+	self basicAddedMethod:aMethod.
+    ].
+    self markDirty.
+    self changed:#addedMethods: with:someMethods.
+    ^ someMethods
+!
+
+addedPackagedClass:aPackagedClass
+    "Add a class to a package. Return the aClass.
+    This only works when 'aClass package == name' if not and error will occur.
+    This method is called only AFTER the class package has changed!! This class
+    is NOT responsible for changing values in classes!!
+    "
+
+    self basicAddedPackagedClass:aPackagedClass.
+    self markDirty.
+    self changed:#addedPackagedClass: with:aPackagedClass.
+    ^ aPackagedClass
+!
+
+addedPackagedClass:packagedClass blockedMethods:aSetOfBlockedMethods
+    "Add a class to a package. Return the aClass.
+    This only works when 'aClass package == name' if not and error will occur.
+    This method is called only AFTER the class package has changed!! This class
+    is NOT responsible for changing values in classes!!
+    "
+    | blockedMethodsAtClassName |
+
+    self addedPackagedClass:packagedClass.
+    aSetOfBlockedMethods size > 0 ifTrue:[
+	blockedMethodsAtClassName := (self blockedMethodsAtClassNamed:packagedClass name ifAbsentPut:[Set new]).
+	blockedMethodsAtClassName addAll:aSetOfBlockedMethods.
+    ].
+    ^ packagedClass
+!
+
+overrideClassNamed:classBeingOverriddenName byPackageNamed:byPackageName
+    | originalClassDefinition |
+
+    self assert:(byPackageName ~= name).
+    originalClassDefinition := (self packagedClassNamed: classBeingOverriddenName).
+    originalClassDefinition ifNil:[
+	PackageError raiseWithOverrideClassErrorClassNotFound:classBeingOverriddenName fromPackage:self
+    ].
+
+    self addOverriddenClassChange:originalClassDefinition byPackageNamed:byPackageName.
+    self changed:#overrideClassNamed:byPackageNamed: with:(Array with:classBeingOverriddenName with:byPackageName)
+!
+
+overrideMethod:methodBeingOverridden byPackageNamed:byPackageName
+    | originalMethodDefinition |
+
+    originalMethodDefinition :=
+	(self newPackagedMethodSelector:methodBeingOverridden name
+		className:methodBeingOverridden mclass name asSymbol
+		source:methodBeingOverridden source).
+
+    originalMethodDefinition ifNil:[
+	PackageError raiseWithOverrideMethodErrorMethodNotFound:methodBeingOverridden fromPackage:self
+    ].
+
+    self addOverriddenMethodChange:originalMethodDefinition byPackageNamed:byPackageName.
+    self changed:#overrideMethod: with:methodBeingOverridden
+!
+
+overrideMethod:methodBeingOverridden forClassNamed:aClassName byPackageNamed:byPackageName
+    | originalMethodDefinition methodName |
+
+    self assert:(byPackageName ~= name).
+    (methodBeingOverridden isKindOf:Method) ifTrue:[
+	"unbound methods do not know there name so i have to do this... This could be done in Method>>selector"
+	(methodName := methodBeingOverridden name) ifNil:[
+	    methodName := (methodBeingOverridden source upTo:Character space) asSymbol.
+	].
+
+	originalMethodDefinition :=
+	    (self newPackagedMethodSelector:methodName
+		    className:aClassName
+		    source:methodBeingOverridden source).
+
+	originalMethodDefinition ifNil:[
+	    PackageError raiseWithOverrideMethodErrorMethodNotFound:methodBeingOverridden fromPackage:self
+	].
+    ] ifFalse:[
+	(methodBeingOverridden isKindOf:(Package::PackagedMethod)) ifFalse:[
+	    self error:'This method needs a PackagedMethod or a Method'
+	].
+	originalMethodDefinition := methodBeingOverridden.
+    ].
+
+    self addOverriddenMethodChange:originalMethodDefinition byPackageNamed:byPackageName.
+    self changed:#overrideMethod: with:methodBeingOverridden
+!
+
+removeFromSystem
+    self packagedClassesDo:[:aPackagedClass |
+	aPackagedClass removeFromSystem
+    ].
+
+    self packagedMethodsDo:[:aPackagedMethod |
+	aPackagedMethod removeFromSystem
+    ].
+!
+
+removeOverriddenClassNamed:aClassNameSymbol
+
+    ^ self removeOverriddenClassNamed:aClassNameSymbol ifAbsent:[self error:'Class not found!!']
+!
+
+removeOverriddenClassNamed:aClassNameSymbol ifAbsent:aBlock
+
+    overriddenClassChanges copy keysAndValuesDo:[:aPackageName :aSet |
+	aSet remove:aClassNameSymbol ifAbsent:aBlock.
+	aSet isEmpty ifTrue:[
+	    overriddenClassChanges removeKey:aPackageName.
+	].
+    ].
+
+    overriddenMethodChanges copy keysAndValuesDo:[:aPackageName :aDic |
+	(aDic removeKey:aClassNameSymbol ifAbsent:aBlock).
+	aDic isEmpty ifTrue:[
+	    overriddenMethodChanges removeKey:aPackageName
+	].
+    ].
+!
+
+removedClassNamed:aSymbol
+    self basicRemoveClassNamed:aSymbol.
+    self markDirty.
+    self changed:#removedClassNamed: with:aSymbol.
+    ^ aSymbol
+!
+
+removedMethod:aMethod
+    ^ self
+	removedMethodNamed:aMethod name
+	forClassNamed:aMethod mclass name.
+!
+
+removedMethodNamed:aMethodName forClassNamed:aClassName
+    "note: could also create a loose method object which could be more useful"
+    ^ self removedMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:[self error:'I should know this method!!']
+!
+
+removedMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock
+    "note: could also create a loose method object which could be more useful"
+    | aPackagedMethod |
+    aPackagedMethod := self basicRemoveMethodNamed:aMethodName forClassNamed:aClassName ifAbsent:aBlock.
+    self markDirty.
+    self changed:#removedMethodNamed:forClassNamed: with:(Array with:(aMethodName)with:(aClassName)).
+    ^ aPackagedMethod
+! !
+
+!Package methodsFor:'api - changes'!
+
+classDefinitionChange:aClassDefinitionChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+    At present a classDefinitionChange does not result in a class changing packages!!
+    If it does then this method needs to change and put this change type in overridden changes!!
+    "
+    self markDirty.
+    self changed:#classDefinitionChange: with:aClassDefinitionChange
+!
+
+classInstVarDefinitionChange:aClassInstVarDefinitionChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+    At present a classInstVarDefinitionChange does not result in a class changing packages!!
+    If it does then this method needs to change and put this change type in overridden changes!!
+    "
+    self markDirty.
+    self changed:#classInstVarDefinitionChange: with:aClassInstVarDefinitionChange
+!
+
+classRemoveChange:aClassRemoveChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+    At the moment i store the original package information in the instance variable
+    packagedClasses, and this is where i get the original class definition from!! It might be
+    an idea to get this info from aClassRemoveChange like it is done in methodRemoveChange.
+    Then we would not need the packageClasses themselves and just storing symbolic links
+    to the classesand create the packageClasses on the fly when needed.
+    "
+    |classBeingRemoved  originalClassDefinition interestedMethods |
+
+    classBeingRemoved := ClassRemoveChange::ClassBeingRemovedQuery query.
+    originalClassDefinition := (self packagedClassNamed: classBeingRemoved name).
+    interestedMethods := self getInterestedPackagedMethodsFromClass:classBeingRemoved.
+    interestedMethods do:[:aPackagedMethod |
+	self addPackagedMethod:aPackagedMethod.
+	self overrideMethod:aPackagedMethod forClassNamed:classBeingRemoved name byPackageNamed:#Smalltalk
+    ].
+    (originalClassDefinition isNil and:[interestedMethods isEmpty]) ifTrue:[
+	self error:'Oops. I should know this!! look #isDependentOnClassRemoveChange: This should be called
+	    before me and should work!!)'
+    ].
+    originalClassDefinition ifNotNil:[
+	self addOverriddenClassChange:originalClassDefinition byPackageNamed:#Smalltalk.
+    ].
+    self changed:#classRemoveChange:
+!
+
+classRenameChange:aClassRenameChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+    This action requires the receiver to change all references to the old class name to the
+    new name.
+    "
+    | newClass newPackagedClass|
+    newClass := (Smalltalk classNamed:aClassRenameChange className).
+    newClass ifNil:[
+	self error:'The class named ', newClass name,
+	    'does not exist!! It is expected to exist from a rename action!!'
+    ].
+
+    self packagedClassesRemoveAtClassName:aClassRenameChange oldName ifAbsent:[nil].
+    newPackagedClass := self newPackagedClass:newClass.
+    self addedPackagedClass:newPackagedClass.
+    self markDirty.
+    self changed:#classRenameChange: with:aClassRenameChange
+!
+
+markClean
+    self isDirty:false.
+!
+
+markDirty
+    self isDirty:true
+!
+
+methodCategoryChange:aChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+     This is not considered a 'major change'. Therefore do nothing to the receiver to indicate that
+     this method (specified by aChange) has been overriden or change. Just mark the receiver as
+     dirty
+    "
+    self markDirty.
+    self changed:#methodCategoryRenameChange: with:aChange
+!
+
+methodCategoryRenameChange:aChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+     This is not considered a 'major change'. Therefore do nothing to the receiver to indicate that
+     this method (specified by aChange) has been overriden or change. Just mark the receiver as
+     dirty
+    "
+    self markDirty.
+    self changed:#methodCategoryRenameChange: with:aChange
+!
+
+methodChanged:aMethodChange
+    "assumes that checks to see if the receiver is affected by the change have been made
+    a method as changed.
+
+    There are really two types of change that come in here. A 'new method change' and a
+    'method redefinition'.
+
+    If the receiver is dependent on the change there are two things that
+    can happen depending on the change:
+
+	1)  if the receiver owns the class but not the method
+	    - to keep the package consistant - we add a blocked method to the receiver
+
+	2)  if the receiver has a loose method defining the method
+	    add an overriddenMethod change - to store the original.
+
+    Context note:
+	at present a change to a methods results ALWAYS in the default package owning the method.
+	so here we assume that the current version package is NEVER the receiver!! This could be
+	added functionality option later on (i have no way of testing this now).
+    "
+    | previousVersion aMethodName aClassName aPackagedMethod byPackageName |
+
+    aMethodName     := aMethodChange selector.
+    aClassName      := aMethodChange className asSymbol.
+    previousVersion := aMethodChange previousVersion.
+    aPackagedMethod := self
+			newPackagedMethodSelector:aMethodName
+			className:aClassName
+			source:previousVersion.
+    byPackageName := aPackagedMethod currentPackageOwner.
+
+    (self includesPackagedClassNamed:aClassName) ifTrue:[
+	previousVersion ifNil:[
+	    "should only really happen in Default class - at least for the time being.
+	    This is because as is noted in - 'Context note' - above"
+	    ^ self newMethodChanged:aMethodChange
+	].
+
+	previousVersion package asSymbol == self name ifTrue:[
+	    ^ self addOverriddenMethodChange:aPackagedMethod byPackageNamed:byPackageName.
+	].
+	Transcript nextPutAll:'i should NEVER be here.... either isDependentOnMethodChange does not
+		    work correctly OR i have just gone a bit bonkers!! From Package>>#methodChanged:';cr.
+    ].
+
+    "when i am here aMethodChange is in with my packageMethods (loose method)
+    the following should be true(but is it needed???):
+	previousVersion package asSymbol == self name
+    "
+
+    self addOverriddenMethodChange:aPackagedMethod byPackageNamed:byPackageName.
+
+    self changed:#methodChanged: with:aMethodChange
+!
+
+methodRemoveChange:aMethodRemoveChange
+    "assumes that checks to see if the receiver is affected by the change have been made.
+    A method that i am dependant on has been removed. I could be dependent on it's class
+    or the method itself (then it would be a loose method).
+
+    There is one special case where i would be dependent on the class but not the method.
+    In this case i just remove the blocked method from my blocked method list!!
+    Otherwise adds changes to overriddenChanges.
+    "
+    | aMethodName aClassName methodBeingRemoved overriddenByPackage |
+    aMethodName := aMethodRemoveChange selector.
+    aClassName := aMethodRemoveChange className asSymbol.
+    methodBeingRemoved := aMethodRemoveChange previousVersion.
+
+    (self blockedMethodsIncludeMethodName:aMethodName forClassNamed:aClassName) ifTrue:[
+	self removeBlockedMethodNamed:aMethodName forClassNamed:aClassName.
+	self changed:#methodChanged: with:aMethodRemoveChange.
+	^ self.
+    ].
+    overriddenByPackage := self workingPackage.
+    overriddenByPackage == name ifTrue:[
+	overriddenByPackage := #Smalltalk
+    ].
+    self overrideMethod:methodBeingRemoved forClassNamed:aClassName byPackageNamed:#Smalltalk.
+    self changed:#methodChanged: with:aMethodRemoveChange.
+!
+
+newMethodChanged:aMethodChange
+    "a new method has been created. In this case i must be dependent on the method's class
+    so i need to block this method from my 'view of the world'."
+    | aMethodName aClassName |
+    aMethodName := aMethodChange selector.
+    aClassName := aMethodChange className.
+    ^ self addBlockedMethodNamed:aMethodName forClassNamed:aClassName
+! !
+
+!Package methodsFor:'api - prerequisites'!
+
+addClassNamePrerequisite:aClassName
+    "changed sent in the following call"
+    ^ self addClassNamePrerequisite:aClassName ifFailString:''.
+!
+
+addClassNamePrerequisite:aName ifFailString:aString
+    |returnValue|
+
+    returnValue := self
+		addPrerequisite:(self newClassPrerequisiteNamed:aName
+			ifFailString:aString).
+    self changed:#addClassNamePrerequisite: with:aName.
+    ^ returnValue
+!
+
+addPackageNamePrerequisite:aName
+    "changed sent in the following call"
+    ^ self addPackageNamePrerequisite:aName ifFailString:''.
+!
+
+addPackageNamePrerequisite:aName ifFailString:aString
+    |returnValue|
+
+    returnValue := self
+		addPrerequisite:(self newPackagePrerequisiteNamed:aName
+			ifFailString:aString).
+    self changed:#addPackageNamePrerequisite: with:aName.
+    ^ returnValue
+! !
+
+!Package methodsFor:'api - scripts'!
+
+postInstallScript
+    ^ self scriptAt:#postInstall
+!
+
+postInstallScriptString:aString
+    self scriptAt:#postInstall put:(self newPackageScriptWithString:aString).
+    self changed:#postInstallScriptString: with:aString.
+!
+
+postUninstallScript
+    ^ self scriptAt:#postUninstall
+!
+
+postUninstallScriptString:aString
+    self scriptAt:#postUninstall put:(self newPackageScriptWithString:aString).
+    self changed:#postUninstallScriptString: with:aString.
+!
+
+preInstallScript
+    ^ (self scriptAt:#preInstall)
+!
+
+preInstallScriptString:aString
+    self scriptAt:#preInstall put:(self newPackageScriptWithString:aString).
+    self changed:#preInstallScriptString: with:aString.
+!
+
+preUninstallScript
+    ^ self scriptAt:#preUninstall
+!
+
+preUninstallScriptString:aString
+    self scriptAt:#preUninstall put:(self newPackageScriptWithString:aString).
+    self changed:#preUninstallScriptString: with:aString.
+! !
+
+!Package methodsFor:'api - uninstall'!
+
+uninstallFromManager:aPackageManager
+
+    self packagedClasses copy do:[:aPackagedClass |
+	"i remove here from packagedClasses so a shallow copy is needed!!"
+	aPackageManager
+	    removeClassNamed:aPackagedClass name
+	    fromPackage:self
+	    moveToDefaultPackage:false.
+    ].
+
+    self checkOkToUninstall.
+    self basicUninstall.
+! !
+
+!Package methodsFor:'api-moving'!
+
+movedClassNamed:aClassName toPackage:newOwnerPackage
+    "Note: all the methods of the class have also been moved to newOwnerPackage BUT
+    we do not have to do anything about that here!! We also do not get any change messages
+    and we - in effect - get this change for free :-) as now newOwnerPackage owns the class!!"
+    | packagedClass blockedMethods|
+    packagedClass := self packagedClassNamed:aClassName.
+    blockedMethods := self blockedMethodsAtClassNamed:aClassName.
+
+    packagedClass ifNil:[
+	PackageError raiseCannotMoveClassNamed:aClassName toPackage:newOwnerPackage.
+    ].
+    packagedClass package:newOwnerPackage.
+
+    PackageError removeClassError handle:[:ex |
+	PackageError raiseCannotMoveClassNamed:aClassName toPackage:newOwnerPackage.
+    ] do:[
+	self removedClassNamed:aClassName.
+    ].
+    newOwnerPackage addedPackagedClass:packagedClass blockedMethods:blockedMethods.
+    self markDirty.
+    self changed:#'movedClassNamed:toPackage:'
+	with:(Array with:aClassName with:newOwnerPackage).
+
+!
+
+movedMethod:aMethod toPackage:newOwnerPackage
+    self removedMethod:aMethod.
+    newOwnerPackage addedMethod:aMethod.
+! !
+
+!Package methodsFor:'checks'!
+
+readyForInstall
+    #ToDo.
+!
+
+readyForUninstall
+    #ToDo.
+! !
+
+!Package methodsFor:'enumerating'!
+
+classesInSystemDo:aBlock
+    self packagedClassesDo:[:aPackage | | aClass |
+	(aClass"orNil" := aPackage classInSmalltalk) ifNotNil:[
+	    aBlock value:aClass
+	].
+    ].
+!
+
+loosePackagedMethodsDo:aBlock
+    self looseMethods do:aBlock.
+!
+
+packagedClassesDo:aOneArgBlock
+   ^ packagedClasses do:aOneArgBlock
+!
+
+packagedMethodsDo:aBlock
+    self packagedMethods values do:[:aDicOfPackagedMethods |
+	aDicOfPackagedMethods values do:aBlock
+    ].
+
+
+
+! !
+
+!Package methodsFor:'factory'!
+
+newClassPrerequisiteNamed:aName ifFailString:aString
+    ^ ClassPrerequisite named:aName ifFailString:aString.
+!
+
+newOverriddenChangeWithChange:aChange
+    ^ OverriddenChange newChange:aChange package:self.
+!
+
+newPackagePrerequisiteNamed:aName ifFailString:aString
+    ^ PackagePrerequisite named:aName ifFailString:aString.
+!
+
+newPackageScriptWithString:aString
+    ^ PackagedScript string:aString receiver:self
+!
+
+newPackagedClass:aClass
+    ^ (PackagedClass class:aClass package:self)
+!
+
+newPackagedMethodSelector:aMethodSelector  className:aClassName
+    ^ PackagedMethod new
+	    name:aMethodSelector;
+	    ownedClassName: aClassName;
+	    package:self.
+!
+
+newPackagedMethodSelector:aMethodSelector  className:aClassName source:aSourceString
+    ^ PackagedMethod
+	    name:aMethodSelector
+	    ownedClassName: aClassName
+	    category:String new
+	    package:self
+	    source:aSourceString
+!
+
+newPackagedMethodWithMethod:aMethod
+    ^ PackagedMethod
+	    name:aMethod selector
+	    ownedClassName: aMethod mclass name
+	    category:aMethod category
+	    package:self
+	    source:aMethod source
+! !
+
+!Package methodsFor:'initialization'!
+
+initialize
+
+    packagedClasses := self class defaultPackagedClassesCollection.
+    packagedMethods := self class defaultPackagedMethodsCollection.
+    blockedMethods := self class defaultBlockedMethodsCollection.
+
+    overriddenClassChanges := self class defaultOverriddenChangesCollection.
+    overriddenMethodChanges := self class defaultOverriddenChangesCollection.
+
+    prerequisites := self class defaultPrerequisiteCollection.
+    scripts := self class defaultScriptsCollection.
+
+    isDirty := false.
+    isInstalled := false. "not sure about this..."
+    super initialize.
+!
+
+initializeClasses
+    self classesInSystemDo:[:aClass |
+	aClass initialize.
+    ].
+!
+
+initializeInstalled
+    "initialize as if the receiver as if it has just been loaded"
+    | myName packagedClass |
+    myName := self name.
+    self isDirty:false.
+    self isInstalled:true.
+    self classesInSystemDo:[:aClass |
+	aClass setPackage:myName.
+	"get initial information"
+	packagedClass := (self packagedClassNamed:aClass name).
+	packagedClass instanceDefinition:aClass definition
+			classDefinition:aClass class definition
+			category:aClass category
+
+    ].
+    "you need to set the working package to the package you are loading... maybe???"
+"/    self looseMethodsDo:[:aMethod |
+"/        aMethod setPackage:myName
+"/    ].
+!
+
+initializeLoaded
+    "initialize as if the receiver as just been loaded"
+    self isDirty:false.
+    self isInstalled:false.
+! !
+
+!Package methodsFor:'printing'!
+
+printOn:aStream
+
+    'named:', self name.
+    aStream nextPutAll:self class printString.
+    aStream nextPutAll:' named:'.
+    aStream nextPut:$'.
+    aStream nextPutAll:self name.
+    aStream nextPut:$'.
+! !
+
+!Package methodsFor:'queries'!
+
+blockedMethodsIncludeMethodName:aMethodName forClassNamed:aClassName
+    | blockedMethods |
+    blockedMethods := (self blockedMethodsAtClassNamed:aClassName).
+    blockedMethods ifNil:[
+	^ false.
+    ].
+
+    ^ blockedMethods includes:aMethodName
+!
+
+definesSelector:aMethodSymbol forClassNamed:aClassSymbol
+    "checks to see if the receiver defines a method selector associated
+    with a class symbol."
+
+    | theClass dictionaryOfPackagedMethods |
+
+    (theClass := self packagedClassNamed:aClassSymbol) ifNil:[
+	dictionaryOfPackagedMethods := self packagedMethods at:aClassSymbol ifAbsent:[^ false].
+	dictionaryOfPackagedMethods at:aMethodSymbol ifAbsent:[^ false]. "assumes a packagedMethod is returned"
+	aMethodSymbol ifNil:[
+	    ^ false.
+	].
+	^ true.
+    ].
+
+    "if i am here then i know the class!!"
+    (self blockedMethodsIncludeMethodName:aMethodSymbol forClassNamed:aClassSymbol) ifTrue:[
+	^ false.
+    ].
+
+    aMethodSymbol ifNil:[
+	^ false.
+    ].
+
+    ^ true.
+!
+
+includesPackagedClassNamed:aSymbol
+
+    ^ (self packagedClassNamed:aSymbol) notNil
+!
+
+isOverridden
+    ^ ((overriddenMethodChanges notEmpty) or:[(overriddenClassChanges notEmpty)])
+!
+
+isPackage
+    ^ true
+!
+
+overriddenChangesIncludesClassNamed:aClassName
+
+
+    overriddenClassChanges values do:[:aSetOfClassNames |
+	(aSetOfClassNames includes:aClassName) ifTrue:[
+	    ^ true
+	].
+    ].
+    overriddenMethodChanges values do:[:aColOfDics |
+	(aColOfDics  keys includes:aClassName) ifTrue:[
+	    ^ true
+	].
+    ].
+
+    ^ false
+
+!
+
+overriddenChangesIncludesMethodName:aMethodName forClassNamed:aClassName
+    | aSetOfPackageMethods |
+
+    overriddenMethodChanges values do:[:aDicOfClassNamesAndMethods |
+	aSetOfPackageMethods := (aDicOfClassNamesAndMethods at:aClassName ifAbsent:[nil]).
+	aSetOfPackageMethods ifNotNil:[
+	    (aSetOfPackageMethods includes:aMethodName) ifTrue:[
+		^ true
+	    ].
+	].
+
+    ].
+
+    ^ false
+!
+
+overriddenClassChangesIncludesClassNamed:aClassName
+
+    overriddenClassChanges isEmpty ifTrue:[
+	^ false
+    ].
+
+    overriddenClassChanges values do:[:aSetOfClassNames |
+	(aSetOfClassNames includes:aClassName) ifTrue:[
+	    ^ true
+	].
+    ].
+
+    ^ false
+!
+
+overriddenMethodChangesIncludesClassNamed:aClassName
+
+    overriddenMethodChanges isEmpty ifTrue:[
+	^ false
+    ].
+
+    overriddenClassChanges values do:[:aDic |
+	(aDic keys includes:aClassName) ifTrue:[
+	    ^ true
+	].
+    ].
+
+    ^ false
+! !
+
+!Package methodsFor:'queries - dependents'!
+
+hasRelationshipWithClassNamed:aClassName
+    "checks to see if the receiver has got some sort of relationship with
+    aClassName such as a method or a class. returns a boolean
+    "
+    self assert:aClassName isSymbol.
+
+    ^ ((self includesPackagedClassNamed:aClassName) or:[
+	    (self packagedMethods at:aClassName ifAbsent:[nil])notNil] )
+!
+
+isDependentOnClassNamed:aClassName
+    "checks to see if the receiver is dependent on aClassName. returns a boolean
+    "
+    | packagedClass  classCheck methodCheck packagedMethods |
+    self assert:aClassName isSymbol.
+    classCheck := true.
+    methodCheck := true.
+
+    (self hasRelationshipWithClassNamed:aClassName) ifFalse:[
+	^ false
+    ].
+
+    packagedClass := (self packagedClassNamed:aClassName) ifNotNil:[
+	classCheck := (self overriddingPackageNameAtClassName:aClassName) isNil
+    ].
+
+    (packagedMethods := self packagedMethods at:aClassName ifAbsent:[nil]) ifNotNil:[
+	packagedMethods keys do:[:aMethodSelector |
+	   (self isDependentOnMethodNamed:aMethodSelector forClassNamed:aClassName) ifFalse:[
+		methodCheck := false.
+	    ].
+	].
+
+    ].
+
+    ^ classCheck or:[methodCheck].
+!
+
+isDependentOnMethodNamed:aMethodSelector forClassNamed:aMethodClassName
+    "If the receiver is responsible for the change return true or false."
+    (self definesSelector:aMethodSelector forClassNamed:aMethodClassName) ifTrue:[
+	(self includesPackagedClassNamed:aMethodClassName) ifTrue:[
+	    (self blockedMethodsIncludeMethodName:aMethodSelector forClassNamed:aMethodClassName) ifTrue:[
+		^ false.
+	    ].
+	].
+
+	(self overriddenChangesIncludesMethodName:aMethodSelector forClassNamed:aMethodClassName) ifTrue:[
+	    ^ false.
+	].
+	^ true.
+    ].
+
+
+
+    ^ false
+! !
+
+!Package methodsFor:'uninstall'!
+
+basicUninstall
+
+    self preUninstallScript evaluate.
+    self uninstallDependentPackages.
+    self uninstallClasses.
+    self uninstallLooseMethods.
+    self initializeLoaded.
+    self postUninstallScript evaluate.
+!
+
+checkOkToUninstall
+    #toDo.
+!
+
+uninstallClasses
+    self classesInSystemDo:[:aClass |
+	aClass removeFromSystem.
+    ]
+!
+
+uninstallDependentPackages
+    #toDo
+!
+
+uninstallLooseMethods
+    self loosePackagedMethodsDo:[:aLooseMethod |
+	aLooseMethod removeFromSystem.
+    ].
+! !
+
+!Package::PackagedClass class methodsFor:'instance creation'!
+
+class:aClass package:aPackage
+    | anInstance|
+    anInstance := (self basicNew name:aClass name package:aPackage).
+    (aClass isLoaded) ifFalse:[
+	"could also be dependant on Smalltalk!!"
+	aClass addDependent:anInstance. "get the definition when the class is autoloaded"
+	anInstance category: aClass category.
+	^ anInstance.
+    ].
+    anInstance instanceDefinition: aClass definition
+	    classDefinition: aClass class definition
+	    category: aClass category.
+
+    ^ anInstance
+!
+
+name:aClassName package:aPackage
+    ^ (self basicNew name:aClassName package:aPackage).
+! !
+
+!Package::PackagedClass methodsFor:'accessing'!
+
+category
+    ^ category ifNil:['' copy].
+!
+
+category:something
+    "set the value of the instance variable 'category' (automatically generated)"
+
+    category := something.
+!
+
+classDefinition
+    "return the value of the instance variable 'classDefinition' (automatically generated)"
+
+    ^ classDefinition
+!
+
+classInstanceVariableNames
+    "return the value of the instance variable 'classInstanceVariableNames' (automatically generated)"
+
+    ^ classInstanceVariableNames
+!
+
+classVariableNames
+    "return the value of the instance variable 'classVariableNames' (automatically generated)"
+
+    ^ classVariableNames
+!
+
+instanceDefinition
+    "return the value of the instance variable 'instanceDefinition' (automatically generated)"
+
+    ^ instanceDefinition
+!
+
+instanceDefinition:instanceDefinitionArg classDefinition:classDefinitionArg category:categoryArg
+    "set instance variables (automatically generated)"
+
+    instanceDefinition := instanceDefinitionArg.
+    classDefinition := classDefinitionArg.
+    category := categoryArg.
+!
+
+instanceVariableNames
+    "return the value of the instance variable 'instanceVariableNames' (automatically generated)"
+
+    ^ instanceVariableNames
+!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+
+    ^ name
+!
+
+name:nameArg package:packageArg
+    "set instance variables (automatically generated)"
+
+    name := nameArg.
+    package := packageArg.
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:aPackage
+    "if the receiver IS in smalltalk change the class in smalltalk.
+    I hope this wont make the functionality get a bit hairy..."
+
+    self isInSmalltalk ifTrue:[
+	self classInSmalltalk package:aPackage name
+    ].
+    package := aPackage.
+!
+
+privateClasses
+    "borrowed implementation from Class>>privateClasses.
+    This implementation looks into the receiver's package to look for
+    privateClasses. IF the receiver is installed in Smalltalk then these private classes
+    associated with the receiver are also its privateClasses!! Although this may not happen
+    often
+    "
+    ^ self privateClassesOrAll:false
+
+
+
+!
+
+privateClassesOrAll:allOfThem
+    "implementation based on Class>>privateClasesOrNil: "
+    |classes myName myNamePrefix myNamePrefixLen cls|
+
+    myName := self name.
+    myNamePrefix := myName , '::'.
+    myNamePrefixLen := myNamePrefix size.
+
+    package packagedClasses keys do:[:nm |
+	(nm startsWith:myNamePrefix) ifTrue:[
+	    (allOfThem
+	    or:[(nm indexOf:$: startingAt:myNamePrefixLen + 1) == 0]) ifTrue:[
+		cls := package packagedClassNamed:nm.
+
+		(cls notNil) ifTrue:[
+		    classes isNil ifTrue:[
+			classes := IdentitySet new:10.
+		    ].
+		    classes add:cls.
+		]
+	    ]
+	]
+    ].
+    self isInSmalltalk ifTrue:[
+	^ classes ? (OrderedCollection new) addAll:(self classInSmalltalk privateClasses)
+    ].
+    ^ classes ? #()
+!
+
+shortName
+    "copied from ClassDescription>>nameWithoutPrefix "
+    |nm idx|
+
+    nm := self name.
+    idx := nm lastIndexOf:$:.
+    idx == 0 ifTrue:[
+	^ nm
+    ].
+    ^ (nm copyFrom:idx+1) asSymbol. "asSymbol was added"
+! !
+
+!Package::PackagedClass methodsFor:'api'!
+
+addBlockedMethodNamed:aMethodName
+    ^ package addBlockedMethodNamed:aMethodName forClassNamed:name
+!
+
+addMethodNamed:aMethodName
+    | aPackagedMethod |
+    (self blockedMethodsIncludeMethodName:aMethodName) ifTrue:[
+	self removeBlockedMethodNamed:aMethodName.
+	self markDirty.
+	^ aPackagedMethod.
+    ].
+
+    (self overriddenChangesIncludesMethodName:aMethodName) ifTrue:[
+     "it should not be consider overriden anymore has the method has just been
+      added to the receiver!! And we dont need to add it as an extra method either
+      as i now am a 'holder for this method!!' But to show this i need to mark myself dirty"
+	self markDirty.
+	self removeOverriddenMethodNamed:aMethodName.
+	^ aPackagedMethod.
+    ].
+
+    "if i am here the method is in effect added as the package the receiver is related to
+    knows the class and does not include any blocked methods for the method aMethodName"
+!
+
+applyIntoSmalltalk
+
+    Parser evaluate:(instanceDefinition).
+    Parser evaluate:(classDefinition).
+
+!
+
+basicRemoveMethodNamed:aMethodName ifAbsent:aBlock
+    (self blockedMethodsIncludeMethodName:aMethodName) ifTrue:[
+	^ aBlock value
+    ]. "the receiver does not know this method!!"
+
+    self addBlockedMethodNamed:aMethodName.
+
+    (self overriddenChangesIncludesMethodName:aMethodName) ifTrue:[
+	self removeOverriddenMethodNamed:aMethodName
+    ].
+!
+
+changeSet
+    | theClass |
+    (theClass := self classInSmalltalk) ifNil:[
+	^ ChangeSet new
+    ].
+
+    theClass autoload.
+
+    ^ ChangeSet forExistingClass:theClass
+!
+
+classInSmalltalk
+    self isInSmalltalk ifTrue:[
+	^ Smalltalk classNamed:name
+    ].
+
+    ^ nil
+!
+
+classSide
+    "an interface to the class side of the receiver"
+    ^ ClassSide instanceSide:self.
+!
+
+definesSelector:aSelector
+    ^ package definesSelector:aSelector forClassNamed:name
+!
+
+isInSmalltalk
+    "if evaluates to false, it should not be in Smalltalk."
+    | classInSmalltalk|
+    ((package packagedClassNamed:name) == self) ifFalse:[
+	^ false.
+    ].
+
+    ^ (package isDependentOnClassNamed:name) and:[
+	(classInSmalltalk := Smalltalk classNamed:name) notNil and:[
+	    (classInSmalltalk package == package name)
+	].
+    ].
+!
+
+markDirty
+    ^ package markDirty
+!
+
+overriddenChangesIncludesMethodName:aMethodName
+    ^ package overriddenChangesIncludesMethodName:aMethodName forClassNamed:name
+!
+
+packagedMethods
+    | isMyClassInSmalltalkGone possibleClassRemoved classInSmalltalk definedMethods packagedMethodsInClass |
+
+    possibleClassRemoved := ClassRemoveChange::ClassBeingRemovedQuery query.
+    isMyClassInSmalltalkGone := possibleClassRemoved notNil.
+
+    isMyClassInSmalltalkGone ifTrue:[
+	definedMethods := possibleClassRemoved methodDictionary copy values select:[:aMethod |
+	    self definesSelector:aMethod name
+	].
+
+	^ definedMethods collect:[:aMethod |
+	    package newPackagedMethodWithMethod:aMethod
+	].
+    ].
+    packagedMethodsInClass := (package packagedMethods at:name ifAbsent:[Dictionary new]).
+
+    (classInSmalltalk := Smalltalk classNamed: name) ifNil:[
+	^ packagedMethodsInClass
+    ].
+
+    definedMethods := classInSmalltalk methodDictionary copy values select:[:aMethod |
+	self definesSelector:aMethod name
+    ].
+    "get from package or create on the fly packaged methods"
+   ^ definedMethods collect:[:aMethod |
+	packagedMethodsInClass at:aMethod name ifAbsent:[
+	   package newPackagedMethodWithMethod:aMethod
+	].
+    ].
+!
+
+removeBlockedMethodNamed:aMethodName
+    ^ package removeBlockedMethodNamed:aMethodName  forClassNamed:name
+!
+
+removeFromPackage
+   ^ package basicRemoveClassNamed:name
+!
+
+removeFromSystem
+    | class |
+    self removeFromPackage.
+    (class := self classInSmalltalk) ifNotNil:[
+	class removeFromSystem.
+    ].
+!
+
+removeOverriddenMethodNamed:aMethodName
+    ^ package removeOverriddenMethodNamed:aMethodName forClassNamed:name.
+! !
+
+!Package::PackagedClass methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+     | definition|
+    (changedObject == self classInSmalltalk) ifTrue:[
+	changedObject isLoaded ifTrue:[
+	    changedObject removeDependent:self. "dont need you any more"
+	    definition := changedObject definition.
+	].
+    ].
+! !
+
+!Package::PackagedClass methodsFor:'printing'!
+
+printOn:aStream
+    aStream nextPutAll:'(PackagedClass named:#', name, ')'.
+! !
+
+!Package::PackagedClass methodsFor:'queries'!
+
+blockedMethodsIncludeMethodName:aMethodName
+    ^ package blockedMethodsIncludeMethodName:aMethodName  forClassNamed:name.
+!
+
+isLoaded
+    ^ self classInSmalltalk isLoaded.
+!
+
+isPrivate
+    "there may be a better way of doing this... but i cannot get this information
+    out from the image as this class may not implemented!!"
+    | readStream |
+    self isInSmalltalk ifTrue:[
+	^ self classInSmalltalk isPrivate.
+    ].
+    readStream := ((Parser parseExpression:instanceDefinition) selector readStream).
+
+    [readStream atEnd] whileFalse:[
+	((readStream upTo:$:) asSymbol == #privateIn:) ifTrue:[
+	    ^ true
+	].
+    ].
+
+    ^ false
+! !
+
+!Package::PackagedClass::ClassSide class methodsFor:'instance creation'!
+
+instanceSide:aPackagedClass
+    ^ self basicNew instanceSide:aPackagedClass
+! !
+
+!Package::PackagedClass::ClassSide methodsFor:'accessing'!
+
+instanceSide
+    "return the value of the instance variable 'instanceSide' (automatically generated)"
+
+    ^ instanceSide
+!
+
+instanceSide:something
+    "set the value of the instance variable 'instanceSide' (automatically generated)"
+
+    instanceSide := something.
+!
+
+name
+    ^ (instanceSide name, ' class') asSymbol
+!
+
+package
+    ^ instanceSide package
+! !
+
+!Package::PackagedClass::ClassSide methodsFor:'api'!
+
+addBlockedMethodNamed:aMethodName
+    ^ self package addBlockedMethodNamed:aMethodName forClassNamed:self name
+!
+
+addMethodNamed:aMethodName
+    | aPackagedMethod |
+    (self blockedMethodsIncludeMethodName:aMethodName) ifTrue:[
+	self removeBlockedMethodNamed:aMethodName.
+	self markDirty.
+	^ aPackagedMethod.
+    ].
+
+    (self overriddenChangesIncludesMethodName:aMethodName) ifTrue:[
+     "it should not be consider overriden anymore has the method has just been
+      added to the receiver!! And we dont need to add it as an extra method either
+      as i now am a 'holder for this method!!' But to show this i need to mark myself dirty"
+	self markDirty.
+	self removeOverriddenMethodNamed:aMethodName.
+	^ aPackagedMethod.
+    ].
+
+    "if i am here the method is in effect added as the package the receiver is related to
+    knows the class and does not include any blocked methods for the method aMethodName"
+!
+
+basicRemoveMethodNamed:aMethodName ifAbsent:aBlock
+    (self blockedMethodsIncludeMethodName:aMethodName) ifTrue:[
+	^ aBlock value
+    ]. "the receiver does not know this method!!"
+
+    self addBlockedMethodNamed:aMethodName.
+
+    (self overriddenChangesIncludesMethodName:aMethodName) ifTrue:[
+	self removeOverriddenMethodNamed:aMethodName
+    ].
+!
+
+blockedMethodsIncludeMethodName:aMethodName
+    ^ self package blockedMethodsIncludeMethodName:aMethodName  forClassNamed:self name.
+!
+
+markDirty
+    ^ self package markDirty
+!
+
+overriddenChangesIncludesMethodName:aMethodName
+    ^ self package overriddenChangesIncludesMethodName:aMethodName forClassNamed:self name
+!
+
+removeBlockedMethodNamed:aMethodName
+    ^ self package removeBlockedMethodNamed:aMethodName  forClassNamed:self name
+!
+
+removeOverriddenMethodNamed:aMethodName
+    ^ self package removeOverriddenMethodNamed:aMethodName forClassNamed:self name.
+! !
+
+!Package::PackagedMethod class methodsFor:'instance creation'!
+
+name:aMethodName ownedClassName: aClassName  category:aCategory package:aPackage source:source
+    self assert:(aClassName isSymbol).
+    self assert:(aMethodName isSymbol).
+    ^ self basicNew name:aMethodName ownedClassName: aClassName category:aCategory package:aPackage source:source
+! !
+
+!Package::PackagedMethod methodsFor:'accessing'!
+
+category
+    (self isInSmalltalk) ifTrue:[
+	^ self method category.
+    ].
+    ^ nil.
+!
+
+currentPackageOwner
+    | class method |
+    class := (Smalltalk classNamed:ownedClassName).
+    class ifNil:[
+	^ nil.
+    ].
+    method := class compiledMethodAt:self name.
+
+    method ifNil:[
+	^ nil
+    ].
+
+    ^ method package
+!
+
+isCommitted
+    "return the value of the instance variable 'isCommitted' (automatically generated)"
+
+    ^ isCommitted
+!
+
+methodInImage
+    | myClass |
+    myClass := Smalltalk classNamed:ownedClassName.
+    myClass ifNil:[^ nil].
+
+    ^ myClass compiledMethodAt:self name.
+!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+
+    ^ name
+!
+
+name:something
+    "set the value of the instance variable 'name' (automatically generated)"
+
+    name := something.
+!
+
+name:nameArg ownedClassName:classNameArg category:categoryArg package:packageArg source:sourceArg
+    name := nameArg.
+    ownedClassName := classNameArg.
+    category := categoryArg.
+    package := packageArg.
+    source :=  sourceArg.
+!
+
+ownedClass
+    ^ Compiler evaluate:ownedClassName
+	in:nil
+	receiver:nil
+	notifying:nil
+	logged:false
+	ifFail:[nil]
+	compile:false
+
+
+
+"
+    (self new ownedClassName:'Integer') ownedClass
+"
+!
+
+ownedClassName
+    "return the value of the instance variable 'className' (automatically generated)"
+
+    ^ ownedClassName
+!
+
+ownedClassName:something
+    "set the value of the instance variable 'className' (automatically generated)"
+    self assert:(something isSymbol).
+    ownedClassName := something.
+!
+
+ownedClassShortName
+    "copied from ClassDescription>>nameWithoutPrefix "
+    |nm idx|
+
+    nm := self ownedClassName.
+    idx := nm lastIndexOf:$:.
+    idx == 0 ifTrue:[
+	^ nm
+    ].
+    ^ (nm copyFrom:idx+1) asSymbol. "asSymbol was added"
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:something
+    "set the value of the instance variable 'package' (automatically generated)"
+
+    package := something.
+!
+
+source
+    source isNil ifTrue:[
+	self isInSmalltalk ifFalse:[
+	    ^ '** no method - no source **' copy.
+	].
+	source := self method source.
+    ].
+
+    ^ source.
+!
+
+source:something
+    "set the value of the instance variable 'source' (automatically generated)"
+
+    source := something.
+! !
+
+!Package::PackagedMethod methodsFor:'fileIn/Out'!
+
+fileOutOn:aWriteStream
+
+    aWriteStream nextPut:$!!.
+    aWriteStream nextPutAll:ownedClassName asString.
+    aWriteStream nextPutAll:' methodsFor:'.
+    aWriteStream nextPut:$'.
+    aWriteStream nextPutAll:(self category).
+    aWriteStream nextPut:$'.
+    aWriteStream nextPut:$!!.
+    aWriteStream cr.
+
+    aWriteStream nextPutAll:self source.
+    aWriteStream nextPut:$!!.
+    aWriteStream cr.
+! !
+
+!Package::PackagedMethod methodsFor:'method - api'!
+
+mclass
+    ^ (Smalltalk classNamed:ownedClassName)
+!
+
+removeFromPackage
+    ^ package removedMethodNamed:name forClassNamed:ownedClassName ifAbsent:[nil]
+!
+
+removeFromSystem
+    | classInSmalltalk |
+    self removeFromPackage.
+    (self isInSmalltalk) ifTrue:[
+	classInSmalltalk := Smalltalk classNamed:ownedClassName.
+	classInSmalltalk ifNotNil:[
+	    classInSmalltalk removeSelector:name.
+	]
+    ].
+!
+
+selector
+    ^ name
+! !
+
+!Package::PackagedMethod methodsFor:'printing'!
+
+printOn:aStream
+    self isLoose ifTrue:[
+	aStream nextPutAll:'LooseMethod:'.
+    ] ifFalse:[
+	aStream nextPutAll:'Method:'.
+    ].
+
+    aStream nextPutAll:self ownedClassShortName.
+    aStream nextPutAll:'->', name printString.
+    aStream cr.
+! !
+
+!Package::PackagedMethod methodsFor:'queries'!
+
+isInSmalltalk
+    ^ (package overriddenChangesIncludesMethodName:name forClassNamed:ownedClassName) not and:[
+	(package blockedMethodsIncludeMethodName:name forClassNamed:ownedClassName) not
+    ]
+
+
+!
+
+isLoose
+    ^ (package includesPackagedClassNamed:ownedClassName) not
+!
+
+isTheSameAsInImage
+    | myClass method|
+    (myClass := (Smalltalk at:ownedClassName)) ifNotNil:[
+	(method :=(myClass methodDictionary at:name ifAbsent:[nil])) ifNotNil:[
+	    ^ method source = source. "there is a more efficient way but i have forgotten"
+	].
+
+    ].
+    ^ false.
+!
+
+method
+    | myClass|
+    (myClass := self ownedClass) ifNotNil:[
+	^ (myClass methodDictionary at:name ifAbsent:[nil]).
+    ].
+    self halt.
+    ^ nil.
+! !
+
+!Package::PackagedScript class methodsFor:'instance creation'!
+
+string:aString receiver:aPackage
+    ^ self basicNew string:aString receiver:aPackage
+! !
+
+!Package::PackagedScript methodsFor:'accessing'!
+
+getString
+    ^ string
+!
+
+string:stringArg receiver:receiverArg
+    "set instance variables (automatically generated)"
+
+    string := stringArg.
+    receiver := receiverArg.
+! !
+
+!Package::PackagedScript methodsFor:'evaluation'!
+
+evaluate
+    ^ Compiler evaluate:string receiver:receiver.
+! !
+
+!Package::PackagedScript methodsFor:'printing'!
+
+printOn:aStream
+      aStream nextPutAll:'Compiler evaluate:'.
+      aStream nextPut:$'.
+      aStream nextPutAll:string.
+      aStream nextPut:$'.
+      aStream nextPutAll:' receiver:('.
+      aStream nextPutAll:(receiver printString).
+      aStream nextPut:$).
+
+"
+    self string:'1 + 1' receiver:nil
+"
+! !
+
+!Package class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/Package.st,v 1.9 2006/08/24 08:38:50 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageBrowser.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,590 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageBrowser subclass:#PackageBrowser
+	instanceVariableNames:'packageSelectorSelectionHolder packageDetailsApplicationHolder
+		packageSelectorApplicationHolder'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+!PackageBrowser class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+         (james@miraculix)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+examples
+"
+  Starting the application:
+                                                                [exBegin]
+    Packages::PackageBrowser open
+
+                                                                [exEnd]
+
+  more examples to be added:
+                                                                [exBegin]
+    ... add code fragment for 
+    ... executable example here ...
+                                                                [exEnd]
+"
+!
+
+history
+    "Created: / 19.3.2003 / 11:23:18 / james"
+! !
+
+!PackageBrowser class methodsFor:'interface specs'!
+
+XXXwindowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageBrowser andSelector:#windowSpec
+     Packages::PackageBrowser new openInterface:#windowSpec
+     Packages::PackageBrowser open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageBrowser'
+          #name: 'Packages::PackageBrowser'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 777 532)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#VariableHorizontalPanelSpec
+              #name: 'VariableHorizontalPanel1'
+              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+              #showHandle: true
+              #snapMode: #both
+              #component: 
+             #(#SpecCollection
+                #collection: #(
+                 #(#SubCanvasSpec
+                    #name: 'PackageSelector'
+                    #hasHorizontalScrollBar: false
+                    #hasVerticalScrollBar: false
+                    #majorKey: #'Packages::PackageSelector'
+                    #subAspectHolders: 
+                   #(#Array
+                      
+                     #(#SubChannelInfoSpec
+                        #subAspect: #packagesSelectedHolder
+                        #aspect: #packagesSelectedHolder
+                      )
+                    )
+                    #createNewApplication: true
+                    #createNewBuilder: true
+                    #postBuildCallback: #packageSelectorCreated:
+                  )
+                 #(#SubCanvasSpec
+                    #name: 'PackageDetails'
+                    #hasHorizontalScrollBar: false
+                    #hasVerticalScrollBar: false
+                    #majorKey: #'Packages::PackageDetails'
+                    #createNewApplication: true
+                    #createNewBuilder: true
+                    #postBuildCallback: #packageDetailsCreated:
+                  )
+                 )
+               
+              )
+              #handles: #(#Any 0.260695 1.0)
+            )
+           )
+         
+        )
+      )
+!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageBrowser andSelector:#windowSpec
+     Packages::PackageBrowser new openInterface:#windowSpec
+     Packages::PackageBrowser open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageBrowser'
+          #name: 'Packages::PackageBrowser'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 777 532)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#MenuPanelSpec
+              #name: 'ToolBar1'
+              #layout: #(#LayoutFrame 0 0 0 0 0 1 30 0)
+              #menu: #menu
+              #textDefault: true
+            )
+           #(#VariableHorizontalPanelSpec
+              #name: 'VariableHorizontalPanel1'
+              #layout: #(#LayoutFrame 0 0.0 30 0.0 0 1.0 0 1.0)
+              #showHandle: true
+              #snapMode: #both
+              #component: 
+             #(#SpecCollection
+                #collection: #(
+                 #(#SubCanvasSpec
+                    #name: 'PackageSelector'
+                    #hasHorizontalScrollBar: false
+                    #hasVerticalScrollBar: false
+                    #majorKey: #'Packages::PackageSelector'
+                    #subAspectHolders: 
+                   #(#Array
+                      
+                     #(#SubChannelInfoSpec
+                        #subAspect: #packagesSelectedHolder
+                        #aspect: #packagesSelectedHolder
+                      )
+                    )
+                    #createNewApplication: true
+                    #createNewBuilder: true
+                    #postBuildCallback: #packageSelectorCreated:
+                  )
+                 #(#SubCanvasSpec
+                    #name: 'PackageDetails'
+                    #hasHorizontalScrollBar: false
+                    #hasVerticalScrollBar: false
+                    #majorKey: #'Packages::PackageDetails'
+                    #createNewApplication: true
+                    #createNewBuilder: true
+                    #postBuildCallback: #packageDetailsCreated:
+                  )
+                 )
+               
+              )
+              #handles: #(#Any 0.287433 1.0)
+            )
+           )
+         
+        )
+      )
+! !
+
+!PackageBrowser class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageBrowser andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+!
+
+menu
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageBrowser andSelector:#menu
+     (Menu new fromLiteralArrayEncoding:(Packages::PackageBrowser menu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(#Menu
+        #(
+         #(#MenuItem
+            #label: 'Reset Smalltalk Manager'
+            #itemValue: #resetSmalltalkManager
+            #translateLabel: true
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #idea16x16Icon)
+          )
+         #(#MenuItem
+            #label: 'Action'
+            #itemValue: #inspectSmalltalkManager
+            #translateLabel: true
+            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #inspectLocals20x20Icon)
+          )
+         )
+        nil
+        nil
+      )
+! !
+
+!PackageBrowser class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+        #packageDetailsApplicationHolder
+        #packageSelectorApplicationHolder
+        #packageSelectorSelectionHolder
+      ).
+
+! !
+
+!PackageBrowser methodsFor:'accessing'!
+
+packageDetailsApplication
+    ^ packageDetailsApplicationHolder value
+! !
+
+!PackageBrowser methodsFor:'actions'!
+
+inspectSmalltalkManager
+    "This is temporary for when the manager goes a bit bonkers!!"
+    self packageManager inspect
+!
+
+resetSmalltalkManager
+    "This is temporary for when the manager goes a bit bonkers!!"
+    | aPackageManager |
+    self withWaitCursorDo:[
+        Packages::PackageManager smalltalkPackageManager becomeNil.
+        aPackageManager := Packages::PackageManager smalltalkPackageManager.
+        self packageManager:aPackageManager
+    ].
+! !
+
+!PackageBrowser methodsFor:'aspects'!
+
+packageDetailsApplicationHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    packageDetailsApplicationHolder isNil ifTrue:[
+        packageDetailsApplicationHolder := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       packageDetailsApplicationHolder addDependent:self.
+"/       packageDetailsApplicationHolder onChangeSend:#packageDetailsApplicationHolderChanged to:self.
+    ].
+    ^ packageDetailsApplicationHolder.
+!
+
+packageSelectorApplicationHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    packageSelectorApplicationHolder isNil ifTrue:[
+        packageSelectorApplicationHolder := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       packageSelectorApplicationHolder addDependent:self.
+"/       packageSelectorApplicationHolder onChangeSend:#packageSelectorApplicationHolderChanged to:self.
+    ].
+    ^ packageSelectorApplicationHolder.
+!
+
+packagesSelectedHolder
+    packageSelectorSelectionHolder isNil ifTrue:[
+        self applicationAspectsAt:#packagesSelectedHolder put:ValueHolder new.
+    ].
+    ^ packageSelectorSelectionHolder.
+! !
+
+!PackageBrowser methodsFor:'callbacks'!
+
+packageDetailsCreated:aSubCanvas
+    "do nothing...for now"
+
+    self packageDetailsApplicationHolder value:aSubCanvas client.
+!
+
+packageSelectorCreated:aSubCanvas
+    "do nothing...for now"
+    self packageSelectorApplicationHolder value:aSubCanvas client.
+! !
+
+!PackageBrowser methodsFor:'constants'!
+
+smalltalkPackageManager
+    ^ PackageManager smalltalkPackageManager
+! !
+
+!PackageBrowser methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+initialize
+    self packageManager:self smalltalkPackageManager.
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageBrowser methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageBrowser class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageBrowser.st,v 1.4 2006/01/10 09:25:17 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageDetails.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,1983 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageNotebookApplication subclass:#PackageDetails
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+AbstractPackageDetails subclass:#Class
+	instanceVariableNames:'classList selectedClassHolder categoryList selectedCategoryHolder
+		nonCriticalPrivateProcesses'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails
+!
+
+LabelAndIcon subclass:#ClassLabelAndIcon
+	instanceVariableNames:'class'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails::Class
+!
+
+AbstractPackageDetails subclass:#Comment
+	instanceVariableNames:'commentTextHolder commentTextModifiedChannel
+		commentTextAcceptChannel editTextView'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails
+!
+
+AbstractPackageDetails subclass:#LooseMethod
+	instanceVariableNames:'methodSelectedHolder currentMethodSourceHolder methodList
+		tableColumns'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails
+!
+
+Object subclass:#PackageDetailsRow
+	instanceVariableNames:'model'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails::LooseMethod
+!
+
+AbstractPackageDetails subclass:#Prerequisites
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails
+!
+
+AbstractPackageDetails subclass:#Scripts
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageDetails
+!
+
+!PackageDetails class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageDetails::Class class methodsFor:'constant values'!
+
+applicationName
+    ^ 'Classes' asSymbol
+! !
+
+!PackageDetails::Class class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageDetails::Class andSelector:#windowSpec
+     Packages::PackageDetails::Class new openInterface:#windowSpec
+     Packages::PackageDetails::Class open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageDetails::Class'
+          #name: 'Packages::PackageDetails::Class'
+          #visibilityChannel: #isVisible
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 329 359)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#VariableHorizontalPanelSpec
+              #name: 'VariableHorizontalPanel1'
+              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+              #component: 
+             #(#SpecCollection
+                #collection: #(
+                 #(#SequenceViewSpec
+                    #name: 'SelectionInListModelView2'
+                    #model: #selectedCategoryHolder
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                    #isMultiSelect: true
+                    #useIndex: false
+                    #sequenceList: #categoryList
+                  )
+                 #(#SequenceViewSpec
+                    #name: 'SelectedClassView1'
+                    #model: #selectedClassHolder
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                    #isMultiSelect: true
+                    #doubleClickSelector: #browseClassWithIndexes:
+                    #useIndex: true
+                    #sequenceList: #classList
+                  )
+                 )
+               
+              )
+              #handles: #(#Any 0.5 1.0)
+            )
+           )
+         
+        )
+      )
+! !
+
+!PackageDetails::Class class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageDetails::Class andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageDetails::Class class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+        #classList
+        #selectedClassHolder
+      ).
+
+! !
+
+!PackageDetails::Class methodsFor:'accessing'!
+
+classListAt:idx 
+    ^ self classList at:idx
+!
+
+declareDependents
+    super declareDependents
+!
+
+privateProcessesAt:aSymbol 
+    ^ (nonCriticalPrivateProcesses at:aSymbol ifAbsentPut:[[nil]fork]).
+!
+
+privateProcessesAt:aSymbol put:aProcess
+    ^ (nonCriticalPrivateProcesses at:aSymbol put:aProcess).
+! !
+
+!PackageDetails::Class methodsFor:'adding'!
+
+addPrivateClassLabelAndIconForClass:aClass toClassList:aClassList level:aNumber
+    aClass privateClasses do:[:aPrivateClass |
+        aClassList add:(self newClassLabelAndIconWithClass:aPrivateClass).
+        self addPrivateClassLabelAndIconForClass:aPrivateClass toClassList:aClassList level:(aNumber + 1).
+    ].
+!
+
+putClassesNamesIn:aClassList fromPackages:collectionOfPackages inCategories:collectionOfCategoryNames 
+    | classesWithoutPrivateClasses|
+    classesWithoutPrivateClasses := OrderedCollection new.
+    collectionOfCategoryNames do:[:aCategoryName |
+        collectionOfPackages do:[:aPackage |
+            (aPackage classesInCategory:aCategoryName) 
+                do:[:aClass |  aClass isPrivate ifFalse:[
+                                        classesWithoutPrivateClasses add:(self newClassLabelAndIconWithClass:aClass).
+                                ].
+            ].
+        ].
+    ].
+    classesWithoutPrivateClasses sort:[:x :y |
+        x asString < y asString
+    ].
+    classesWithoutPrivateClasses do:[:aLableAndIcon | | aClass |
+        aClass := aLableAndIcon classModel.
+        aClassList add:aLableAndIcon.
+        self addPrivateClassLabelAndIconForClass:aClass toClassList:aClassList level:1
+    ].
+! !
+
+!PackageDetails::Class methodsFor:'aspects'!
+
+categoryList
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    categoryList isNil ifTrue:[
+        categoryList := List new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       categoryList addDependent:self.
+"/       categoryList onChangeSend:#categoryListChanged to:self.
+    ].
+    ^ categoryList.
+!
+
+classList
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    classList isNil ifTrue:[
+        classList := List new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       classList addDependent:self.
+"/       classList onChangeSend:#classListChanged to:self.
+    ].
+    ^ classList.
+!
+
+selectedCategoryHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    selectedCategoryHolder isNil ifTrue:[
+        selectedCategoryHolder := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+       selectedCategoryHolder addDependent:self.
+"/       selectedCategoryHolder onChangeSend:#selectedCategoryHolderChanged to:self.
+    ].
+    ^ selectedCategoryHolder.
+!
+
+selectedClassHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    selectedClassHolder isNil ifTrue:[
+        selectedClassHolder := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       selectedClassHolder addDependent:self.
+"/       selectedClassHolder onChangeSend:#selectedClassHolderChanged to:self.
+    ].
+    ^ selectedClassHolder.
+! !
+
+!PackageDetails::Class methodsFor:'aspects - exported'!
+
+classList:something
+    "automatically generated by UIPainter ..."
+
+    "This method is used when I am embedded as subApplication,"
+    "and the mainApp wants to connect its aspects to mine."
+
+"/     classList notNil ifTrue:[
+"/        classList removeDependent:self.
+"/     ].
+    classList := something.
+"/     classList notNil ifTrue:[
+"/        classList addDependent:self.
+"/     ].
+    ^ self.
+!
+
+selectedClassHolder:something
+    "automatically generated by UIPainter ..."
+
+    "This method is used when I am embedded as subApplication,"
+    "and the mainApp wants to connect its aspects to mine."
+
+"/     selectedClassHolder notNil ifTrue:[
+"/        selectedClassHolder removeDependent:self.
+"/     ].
+    selectedClassHolder := something.
+"/     selectedClassHolder notNil ifTrue:[
+"/        selectedClassHolder addDependent:self.
+"/     ].
+    ^ self.
+! !
+
+!PackageDetails::Class methodsFor:'browsing'!
+
+browseClassWithIndexes:aCollectionOfIndexes
+    "An 'adapter method'. Calls #browserClass:. Is only used as there can be
+    private classes with the same name and the selectionList cannot tell the difference
+    otherwise."
+    | classItems |
+    classItems := aCollectionOfIndexes collect:[:idx |
+        self classListAt:idx
+    ].
+
+    ^ self browseClasses:classItems
+!
+
+browseClasses:aCollection
+    | theClass |
+    theClass := aCollection first classModel.
+    (Smalltalk classNamed:(theClass name)) browse
+! !
+
+!PackageDetails::Class methodsFor:'change & update'!
+
+selectedCategoryChanged:aCollectionOfCategories 
+
+    self withProcessNamed:#selectedCategoryChanged: do:[
+        classList removeAll.
+        self 
+            putClassesNamesIn:classList 
+            fromPackages:self packagesSelected 
+            inCategories:aCollectionOfCategories.
+
+    ].
+!
+
+update:something with:aParameter from:changedObject
+
+    changedObject == selectedCategoryHolder ifTrue:[
+        self selectedCategoryChanged:aParameter        
+    ].
+
+    super update:something with:aParameter from:changedObject
+!
+
+updateWithPackages:packages
+    | classCategoryNames |
+    packages size = 1 ifTrue:[
+        packages first ifNil:[
+            ^ self.
+        ]
+    ].
+
+    self withProcessNamed:#updateWithPackages: do:[ 
+        classList removeAll.
+        categoryList removeAll.
+        classCategoryNames := Set new.
+        packages do:[:aPackage |
+            classCategoryNames addAll:aPackage classCategories   
+        ].
+
+        categoryList addAll:classCategoryNames.
+        categoryList sort:[:x :y |
+            x < y
+        ]. 
+    ].
+"/    packages do:[:aPackage |
+"/        categoryList addAll:aPackage classCategories   
+"/    ].
+! !
+
+!PackageDetails::Class methodsFor:'factory'!
+
+labelAndIconClass
+    ^ ClassLabelAndIcon
+!
+
+newClassLabelAndIconWithClass:aClass
+"/    aClass isPrivate ifTrue:[self halt.].
+    ^ self labelAndIconClass class:aClass
+! !
+
+!PackageDetails::Class methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+initialize
+    nonCriticalPrivateProcesses := Dictionary new
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageDetails::Class methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageDetails::Class methodsFor:'process'!
+
+withProcessNamed:aName do:aBlock 
+    "stop unconditionally the process and replace with aBlock"
+    (self privateProcessesAt:aName) terminate.
+    self privateProcessesAt:aName put:aBlock fork.
+! !
+
+!PackageDetails::Class methodsFor:'queries'!
+
+validateCanChange:arg 
+! !
+
+!PackageDetails::Class::ClassLabelAndIcon class methodsFor:'instance'!
+
+class:aClass
+    ^ (self basicNew) classModel:aClass; initialize
+! !
+
+!PackageDetails::Class::ClassLabelAndIcon methodsFor:'accessing'!
+
+asString
+
+    | aString |
+    aString := String new.
+    class isPrivate ifTrue:[
+        aString := '    '.
+        self privateClassDepth timesRepeat:[
+            aString := aString , '  '.
+        ].
+        aString := aString , '::'. 
+    ].
+
+    aString := aString, class shortName asString. 
+
+    ^ aString
+!
+
+classModel
+    "return the value of the instance variable 'class' (automatically generated)"
+
+    ^ class
+!
+
+classModel:something
+    "set the value of the instance variable 'class' (automatically generated)"
+
+    class := something.
+    self string: self asString.
+!
+
+privateClassDepth
+    | thisClass counter |
+    thisClass := class.
+    counter := 0.
+    [thisClass isNameSpace] whileFalse:[
+        thisClass := thisClass owningClass.
+        thisClass ifNil:[thisClass := Smalltalk].
+        counter := counter + 1.
+    ].
+
+    ^ counter - 1
+! !
+
+!PackageDetails::Comment class methodsFor:'constant values'!
+
+applicationName
+    ^ 'Comment' asSymbol
+! !
+
+!PackageDetails::Comment class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageDetails::Comment andSelector:#windowSpec
+     Packages::PackageDetails::Comment new openInterface:#windowSpec
+     Packages::PackageDetails::Comment open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageDetails::Comment'
+          #name: 'Packages::PackageDetails::Comment'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 329 359)
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#TextEditorSpec
+              #name: 'TextEditor1'
+              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+              #model: #commentTextHolder
+              #hasHorizontalScrollBar: true
+              #hasVerticalScrollBar: true
+              #modifiedChannel: #commentTextModifiedChannel
+              #acceptCallBack: #commentAccepted:
+              #postBuildCallback: #commentTextEditorCreated:
+            )
+           )
+         
+        )
+      )
+! !
+
+!PackageDetails::Comment methodsFor:'accessing'!
+
+declareDependents
+    super declareDependents
+! !
+
+!PackageDetails::Comment methodsFor:'aspects'!
+
+commentTextAcceptChannel
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    commentTextAcceptChannel isNil ifTrue:[
+        commentTextAcceptChannel := TriggerValue new.
+    ].
+    ^ commentTextAcceptChannel.
+!
+
+commentTextHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    commentTextHolder isNil ifTrue:[
+        commentTextHolder := '' asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       commentTextHolder addDependent:self.
+"/       commentTextHolder onChangeSend:#commentTextHolderChanged to:self.
+    ].
+    ^ commentTextHolder.
+!
+
+commentTextModifiedChannel
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    commentTextModifiedChannel isNil ifTrue:[
+        commentTextModifiedChannel := TriggerValue new.
+    ].
+    ^ commentTextModifiedChannel.
+! !
+
+!PackageDetails::Comment methodsFor:'callbacks'!
+
+commentAccepted:aStringCollection 
+    |packagesSelected|
+    (packagesSelected := self packagesSelected) size > 1 ifTrue:[
+        Smalltalk beep.
+        ^ self.
+    ].
+
+    (self packagesNamed:self packagesSelected) first packageComment:aStringCollection asString.
+!
+
+commentTextEditorCreated:aScrolledViewWithTextEditor 
+    "do with the text editor widget as you will...."
+    editTextView := aScrolledViewWithTextEditor scrolledView.
+
+! !
+
+!PackageDetails::Comment methodsFor:'change & update'!
+
+packagesSelectedHolderChanged:selectedPackages 
+    |packagesSelected selectedSinglePackage |
+
+    packagesSelected := self packagesSelected.
+
+    selectedPackages size == 1 ifTrue:[
+        selectedSinglePackage := selectedPackages first.
+        ^ commentTextHolder value: selectedSinglePackage packageComment.
+    ].
+    selectedPackages size == 0 ifTrue:[
+        ^ commentTextHolder value:'No package selected' 
+    ].   
+    "selectedPackages size > 1 ifTrue:["
+        ^ commentTextHolder value:'Cannot show more than one comment!!'  
+    "]."
+!
+
+validateCanChange:arg 
+! !
+
+!PackageDetails::Comment methodsFor:'defaults'!
+
+commentForMultiplePackageSelect
+    ^ String new
+! !
+
+!PackageDetails::Comment methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageDetails::LooseMethod class methodsFor:'constant values'!
+
+applicationName
+    ^ 'Loose Method' asSymbol
+! !
+
+!PackageDetails::LooseMethod class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageDetails::LooseMethod andSelector:#windowSpec
+     Packages::PackageDetails::LooseMethod new openInterface:#windowSpec
+     Packages::PackageDetails::LooseMethod open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: 'Packages::PackageDetails::LooseMethod'
+          #name: 'Packages::PackageDetails::LooseMethod'
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 329 359)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #(
+           #(#VariableVerticalPanelSpec
+              #name: 'VariableVerticalPanel1'
+              #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+              #component: 
+             #(#SpecCollection
+                #collection: #(
+                 #(#DataSetSpec
+                    #name: 'Table1'
+                    #model: #methodSelectedHolder
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                    #dataList: #methodList
+                    #has3Dsepartors: false
+                    #columnHolder: #tableColumns
+                    #multipleSelectOk: true
+                    #verticalSpacing: 0
+                  )
+                 #(#TextEditorSpec
+                    #name: 'SourceEditor'
+                    #model: #currentMethodSourceHolder
+                    #hasHorizontalScrollBar: true
+                    #hasVerticalScrollBar: true
+                  )
+                 )
+               
+              )
+              #handles: #(#Any 0.5 1.0)
+            )
+           )
+         
+        )
+      )
+! !
+
+!PackageDetails::LooseMethod class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageDetails::LooseMethod andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageDetails::LooseMethod class methodsFor:'tableColumns specs'!
+
+tableColumns
+    "This resource specification was automatically generated
+     by the DataSetBuilder of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the DataSetBuilder may not be able to read the specification."
+
+    "
+     DataSetBuilder new openOnClass:Packages::PackageDetails::LooseMethod andSelector:#tableColumns
+    "
+
+    <resource: #tableColumns>
+
+    ^#(
+      #(#DataSetColumnSpec
+         #label: ''
+         #id: 'Icon'
+         #labelButtonType: #Button
+         #model: #icon
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Selector'
+         #id: 'Selector'
+         #labelAlignment: #left
+         #labelButtonType: #Button
+         #model: #selector
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Class'
+         #id: 'Class'
+         #labelAlignment: #left
+         #labelButtonType: #Button
+         #model: #myClass
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Package'
+         #id: 'Package'
+         #labelButtonType: #Button
+         #model: #myPackage
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      )
+!
+
+tableColumnsOld
+    "This resource specification was automatically generated
+     by the DataSetBuilder of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the DataSetBuilder may not be able to read the specification."
+
+    "
+     DataSetBuilder new openOnClass:Packages::PackageDetails::LooseMethod andSelector:#tableColumns
+    "
+
+    <resource: #tableColumns>
+
+    ^#(
+      #(#DataSetColumnSpec
+         #label: ''
+         #id: 'Icon'
+         #labelButtonType: #Button
+         #model: #icon
+         #canSelect: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Selector'
+         #id: 'Selector'
+         #labelAlignment: #left
+         #labelButtonType: #Button
+         #model: #selector
+         #canSelect: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Class'
+         #id: 'Class'
+         #labelAlignment: #left
+         #labelButtonType: #Button
+         #model: #myClass
+         #canSelect: false
+       )
+      #(#DataSetColumnSpec
+         #label: 'Package'
+         #id: 'Package'
+         #labelButtonType: #Button
+         #model: #myPackage
+         #canSelect: false
+       )
+      )
+! !
+
+!PackageDetails::LooseMethod methodsFor:'accessing'!
+
+currentMethodSource:aString 
+    self currentMethodSourceHolder value:aString
+!
+
+declareDependents
+    super declareDependents
+! !
+
+!PackageDetails::LooseMethod methodsFor:'aspects'!
+
+currentMethodSourceHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    currentMethodSourceHolder isNil ifTrue:[
+        currentMethodSourceHolder := '' asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       currentMethodSourceHolder addDependent:self.
+"/       currentMethodSourceHolder onChangeSend:#currentMethodSourceHolderChanged to:self.
+    ].
+    ^ currentMethodSourceHolder.
+!
+
+methodList
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    methodList isNil ifTrue:[
+        methodList := List new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       methodList addDependent:self.
+"/       methodList onChangeSend:#methodListChanged to:self.
+    ].
+    ^ methodList.
+!
+
+methodSelectedHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    methodSelectedHolder isNil ifTrue:[
+        methodSelectedHolder := ValueHolder new.
+        methodSelectedHolder onChangeEvaluate:[| methodSelectedHolderValue|
+            (methodSelectedHolderValue := methodSelectedHolder value) ifNotNil:[
+                self currentMethodSourceChangedToIndex:methodSelectedHolderValue
+            ].
+
+        ]
+    ].
+    ^ methodSelectedHolder.
+!
+
+tableColumns
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    tableColumns isNil ifTrue:[
+        tableColumns := self class tableColumns asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       tableColumns addDependent:self.
+"/       tableColumns onChangeSend:#tableColumnsChanged to:self.
+    ].
+    ^ tableColumns.
+! !
+
+!PackageDetails::LooseMethod methodsFor:'change & update'!
+
+currentMethodSourceChangedToIndex:aCollection
+    | currentPackageDetailsRow |
+    aCollection size > 1 ifTrue:[
+        self currentMethodSource: self moreThanOneMethodCode.
+        ^ self.
+    ].
+    currentPackageDetailsRow := (self methodList at:aCollection first).
+    self currentMethodSourceHolder value:(currentPackageDetailsRow model source).
+!
+
+updateWithPackages:packages
+    | methodNames |
+    methodList removeAll.
+    currentMethodSourceHolder value:String new.
+    methodNames := OrderedCollection new.
+
+    packages do:[:aPackage | 
+        methodNames addAll:(aPackage looseMethods collect:[:aMethod| self newPackageDetailsRowWithModel:aMethod]).   
+    ].
+
+    methodList addAll:methodNames.
+!
+
+validateCanChange:arg 
+! !
+
+!PackageDetails::LooseMethod methodsFor:'defaults'!
+
+moreThanOneMethodCode
+    ^ String new
+! !
+
+!PackageDetails::LooseMethod methodsFor:'factory'!
+
+newPackageDetailsRowWithModel:aModel 
+    ^ PackageDetailsRow new model: aModel
+! !
+
+!PackageDetails::LooseMethod methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageDetails::LooseMethod methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageDetails::LooseMethod::PackageDetailsRow methodsFor:'accessing'!
+
+icon
+    "automatically generated by DataSetBuilder ..."
+
+    "get value"
+
+    ^ ''
+!
+
+model
+    "return the value of the instance variable 'model' (automatically generated)"
+
+    ^ model
+!
+
+model:arg 
+    model:= arg.
+!
+
+myClass
+    "automatically generated by DataSetBuilder ..."
+
+    "get value"
+
+    ^ model mclass
+!
+
+myPackage
+    "automatically generated by DataSetBuilder ..."
+
+    "get value"
+
+    ^ model package
+!
+
+selector
+    "automatically generated by DataSetBuilder ..."
+
+    "get value"
+
+    ^ model selector
+! !
+
+!PackageDetails::Prerequisites class methodsFor:'constant values'!
+
+applicationName
+    ^ 'Prerequisites' asSymbol
+! !
+
+!PackageDetails::Prerequisites class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageDetails::Prerequisites andSelector:#windowSpec
+    "
+
+    <resource: #canvas>
+
+    ^ #(#FullSpec
+          #window: 
+           #(#WindowSpec
+              #name: 'Packages::PackageDetails::Prerequisites'
+              #layout: #(#LayoutFrame 204 0 162 0 503 0 461 0)
+              #label: 'Packages::PackageDetails::Prerequisites'
+              #min: #(#Point 10 10)
+              #max: #(#Point 1024 768)
+              #bounds: #(#Rectangle 204 162 504 462)
+              #menu: #mainMenu
+              #usePreferredExtent: false
+          )
+          #component: 
+           #(#SpecCollection
+              #collection: #()
+          )
+      )
+! !
+
+!PackageDetails::Prerequisites class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageDetails::Prerequisites andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageDetails::Prerequisites methodsFor:'accessing'!
+
+declareDependents
+    super declareDependents
+! !
+
+!PackageDetails::Prerequisites methodsFor:'change & update'!
+
+packagesSelectedHolderChanged:aCollection 
+!
+
+validateCanChange:arg 
+! !
+
+!PackageDetails::Prerequisites methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageDetails::Prerequisites methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageDetails::Scripts class methodsFor:'constant values'!
+
+applicationName
+    ^ 'Scripts' asSymbol
+! !
+
+!PackageDetails::Scripts class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageDetails::Scripts andSelector:#windowSpec
+    "
+
+    <resource: #canvas>
+
+    ^ #(#FullSpec
+          #window: 
+           #(#WindowSpec
+              #name: 'Packages::PackageDetails::Scripts'
+              #layout: #(#LayoutFrame 204 0 162 0 503 0 461 0)
+              #label: 'Packages::PackageDetails::Scripts'
+              #min: #(#Point 10 10)
+              #max: #(#Point 1024 768)
+              #bounds: #(#Rectangle 204 162 504 462)
+              #menu: #mainMenu
+              #usePreferredExtent: false
+          )
+          #component: 
+           #(#SpecCollection
+              #collection: #()
+          )
+      )
+! !
+
+!PackageDetails::Scripts class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageDetails::Scripts andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageDetails::Scripts methodsFor:'accessing'!
+
+declareDependents
+    super declareDependents
+! !
+
+!PackageDetails::Scripts methodsFor:'change & update'!
+
+packagesSelectedHolderChanged:aCollection 
+    self breakPoint:''.
+!
+
+validateCanChange:arg 
+! !
+
+!PackageDetails::Scripts methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageDetails::Scripts methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageDetails class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageDetails.st,v 1.4 2006/01/10 09:25:03 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageError.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,115 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Error subclass:#PackageError
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Exception-Errors'
+!
+
+!PackageError class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageError class methodsFor:'factory'!
+
+invalidClassMoveError
+    "dummy method     "
+!
+
+overrideClassError
+    "dummy method"
+!
+
+removeClassError
+    "return another error class am returning self here!!"
+! !
+
+!PackageError class methodsFor:'raising'!
+
+raiseAddedClassFailedNamed:aClassName toPackage:newPackage
+    ^ (self new) 
+            errorString:'Cannot add ', aClassName, ' to package named: ',newPackage name, ' as it includes
+            a class with the same name!!';
+            raise.
+!
+
+raiseCannotAddAsPackageManagerAlreadyIncludesPackageNamed:aString
+    ^ (self new) 
+            errorString:'Cannot add as packageManager already includes package named ', aString;
+            raise.
+!
+
+raiseCannotMoveClassNamed:aClassName toPackage:newOwnerPackage
+    ^ (self new) 
+            errorString:'Cannot move class named ', aClassName asString, ' from package ', newOwnerPackage name;
+            raise.
+!
+
+raiseCannotRemoveClassNamed:aSymbol fromPackage:aPackage
+    ^ (self new) 
+            errorString:'Cannot removeClassNamed ', aSymbol asString, ' from package ', aPackage name;
+            raise.
+!
+
+raiseCannotRemoveClassNamed:aClassName fromPackage:aPackage inContext:aContext
+
+    ^ (self removeClassError new) 
+            errorString:'Cannot remove packagedClass ', aClassName asString,
+                ' from package: ';
+"/            fromPackage:aPackage;
+"/            context:aContext;
+            raise.
+!
+
+raiseInvalidClassMove:aClass fromPackage:oldOwnerPackage toPackage:newOwnerPackage
+
+    ^ (self invalidClassMoveError new) 
+            errorString:'Cannot move packagedClass ', aClass name asString;
+            raise.
+!
+
+raiseWithOverrideClassErrorClassNotFound:classBeingOverriddenName fromPackage:aPackage
+    ^ (self removeClassError new) 
+            errorString:'Class not found  ', classBeingOverriddenName  asString,
+                ' from package: ' , aPackage name;
+"/            fromPackage:aPackage;
+"/            context:aContext;
+            raise.
+!
+
+raiseWithOverrideMethodErrorMethodNotFound:methodBeingOverridden fromPackage:aPackage
+    ^ (self new) raise.
+! !
+
+!PackageError class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageError.st,v 1.4 2006/01/10 09:29:56 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageHandler.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,84 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#PackageHandler
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Handlers'
+!
+
+!PackageHandler class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageHandler class methodsFor:'instance creation'!
+
+forFilename:aFilename
+    (self isStxFile:aFilename) ifTrue:[
+        ^ StxPackageFileHandler forFilename:aFilename
+    ].
+
+
+    self error:'Unknown file format'
+!
+
+forPackage:aPackage
+
+    (self isStxPackage:aPackage) ifTrue:[
+        ^ StxPackageFileHandler forPackage:aPackage
+    ].
+
+    self error:'Package not known...'
+!
+
+openStxPackageFormat:aFormat
+    ^ (StxPackageFileHandler) openStxPackageFormat:aFormat
+! !
+
+!PackageHandler class methodsFor:'globals'!
+
+smalltalkPackageManager
+    ^ PackageManager smalltalkPackageManager  
+! !
+
+!PackageHandler class methodsFor:'queries'!
+
+isStxFile:aFilename
+    ^ true
+!
+
+isStxPackage:aPackage
+    ^ true
+! !
+
+!PackageHandler class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageHandler.st,v 1.3 2006/01/10 09:32:12 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageManager.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,1099 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageManager subclass:#PackageManager
+	instanceVariableNames:'workingPackage defaultPackage'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Managers'
+!
+
+PackageManager class instanceVariableNames:'currentPackage currentManager imageChanges'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
+!PackageManager class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    PackageManager smalltalkPackageManager
+
+    [author:]
+	 (james@miraculix)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+documentation_exceptions
+"
+
+    ClassDescription fileOutErrorSignal
+	    can occur when a class within a package is autoloaded. Handle in application
+
+    [author:]
+	 (james@miraculix)
+
+"
+!
+
+examples
+"
+
+  more examples to be added:
+								[exBegin]
+    ... add code fragment for
+    ... executable example here ...
+								[exEnd]
+"
+!
+
+history
+    "Created: / 27.1.2003 / 13:57:50 / james"
+! !
+
+!PackageManager class methodsFor:'instance creation'!
+
+initialize
+    "Uninitialize Singleton"
+    currentManager ifNotNil:[
+	currentManager uninitialize.
+	currentManager := nil.
+	currentPackage := nil.
+    ]
+
+"
+    self initialize
+"
+!
+
+newManagerOfCurrentImage
+    | anInstance |
+    anInstance := self new.
+
+    self basicPackagesInImage do:[:aPackage |
+	package isInstalled:true.
+	anInstance addPackage:aPackage
+    ].
+    ^ anInstance
+
+"
+currentManager := self newManagerOfCurrentImage.
+"
+! !
+
+!PackageManager class methodsFor:'* As yet uncategorized *'!
+
+basePackageNames
+    ^ (Array with:(Project noProjectID)) ,
+	#(
+	    #'stx:clients/AddrBook'
+	    #'stx:clients/Animation'
+	    #'stx:clients/Clock'
+	    #'stx:clients/Demos'
+	    #'stx:clients/DirView'
+	    #'stx:clients/DocTool'
+	    #'stx:clients/DrawTool'
+	    #'stx:clients/GLdemos'
+	    #'stx:clients/GuessingGame'
+	    #'stx:clients/LogicTool'
+	    #'stx:clients/MailTool'
+	    #'stx:clients/NewsTool'
+	    #'stx:clients/PingPong'
+	    #'stx:clients/Tetris'
+	    #'stx:clients/TicTacToe'
+	    #'stx:clients/TicTacToe3D'
+	    #'stx:clients/Tools'
+	    #'stx:goodies'
+	    #'stx:goodies/benchmarks'
+	    #'stx:goodies/benchmarks/deltaBlue'
+	    #'stx:goodies/benchmarks/dhrystones'
+	    #'stx:goodies/benchmarks/misc'
+	    #'stx:goodies/benchmarks/richards'
+	    #'stx:goodies/benchmarks/self'
+	    #'stx:goodies/communication'
+	    #'stx:goodies/dhbNumeric'
+	    #'stx:goodies/distributions'
+	    #'stx:goodies/glorp'
+	    #'stx:goodies/lisp'
+	    #'stx:goodies/math/fibonacci'
+	    #'stx:goodies/measurement'
+	    #'stx:goodies/minneStore'
+	    #'stx:goodies/obsolete'
+	    #'stx:goodies/persistency'
+	    #'stx:goodies/postscript'
+	    #'stx:goodies/prolog'
+	    #'stx:goodies/rdoit'
+	    #'stx:goodies/refactoryBrowser'
+	    #'stx:goodies/regex'
+	    #'stx:goodies/remoteObjects'
+	    #'stx:goodies/screenSavers'
+	    #'stx:goodies/sif'
+	    #'stx:goodies/smaCC'
+	    #'stx:goodies/soap'
+	    #'stx:goodies/soap/examples'
+	    #'stx:goodies/soap/opera'
+	    #'stx:goodies/soap/splash'
+	    #'stx:goodies/soap/spray'
+	    #'stx:goodies/soap/wsdl'
+	    #'stx:goodies/soap/xe'
+	    #'stx:goodies/soap/xmlsig'
+	    #'stx:goodies/sound'
+	    #'stx:goodies/stmath'
+	    #'stx:goodies/stxInExternalWindow'
+	    #'stx:goodies/sunit'
+	    #'stx:goodies/swazoo'
+	    #'stx:goodies/tgen'
+	    #'stx:goodies/webServer'
+	    #'stx:goodies/webServer/pwsSwiki'
+	    #'stx:goodies/xml-indelv'
+	    #'stx:goodies/xml-vw'
+	    #'stx:goodies/xml-yaxo'
+	    #'stx:libbasic'
+	    #'stx:libbasic2'
+	    #'stx:libbasic3'
+	    #'stx:libboss'
+	    #'stx:libcomp'
+	    #'stx:libcompat'
+	    #'stx:libhtml'
+	    #'stx:libjava'
+	    #'stx:libjava/examples'
+	    #'stx:libjavascript'
+	    #'stx:libodbc'
+	    #'stx:libopengl'
+	    #'stx:libsnmp'
+	    #'stx:libtable'
+	    #'stx:libtool'
+	    #'stx:libtool2'
+	    #'stx:libui'
+	    #'stx:libview'
+	    #'stx:libview2'
+	    #'stx:libwidg'
+	    #'stx:libwidg2'
+	    #'stx:libwidg3'
+    )
+! !
+
+!PackageManager class methodsFor:'accessing'!
+
+changes
+    imageChanges ifNil:[
+	imageChanges := OrderedCollection new.
+    ].
+    ^ imageChanges
+!
+
+smalltalkPackageManager
+    "/ to clear the singleton for the moment
+     | workingPackage packagesInImage|
+
+    "/    self initialize.
+    currentManager
+	ifNil:[
+	    currentManager := self new.
+
+	    packagesInImage := self basicPackagesInImage.
+	    workingPackage := packagesInImage removeKey:(Project noProjectID).
+
+	    currentManager addPackages:(packagesInImage).
+	    currentManager defaultPackage:workingPackage.
+	].
+    ^ currentManager
+! !
+
+!PackageManager class methodsFor:'defaults'!
+
+defaultPackages
+    ^ DictionaryStack new.
+! !
+
+!PackageManager class methodsFor:'factory'!
+
+defaultPackage
+    ^ (Packages::Package named:#'__NoProject__')
+!
+
+packageClass
+    ^ Package
+! !
+
+!PackageManager class methodsFor:'temporary'!
+
+basicPackagesInImage
+    "builds up dictionary of the packages in the system taking the information of the classes and
+    methods so we have a complete picture but without the prerequisite information.
+    returns the dictionary"
+    | packagesInImage extentions clsPkg |
+
+    packagesInImage := Dictionary new.
+    extentions := Dictionary new.
+
+    "collect the classes and mark where the extentions are"
+    Smalltalk allClasses do:[:aClass |
+	    aClass isNameSpace ifFalse:[
+		clsPkg := aClass package.
+		((packagesInImage at: clsPkg
+				 ifAbsentPut:[clsPkg == #'__NoProject__' ifTrue:[
+				    (Package named:clsPkg)
+				 ] ifFalse:[(Package named:clsPkg)
+				 ].         ])
+		    addedClass:aClass).
+
+"/                aClass hasExtensions ifTrue:[
+		    aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+			|mthdPkg|
+			mthdPkg := mthd package.
+			mthdPkg ~= clsPkg ifTrue:[| methodPackage |
+			    "this is found out when you add a class!!"
+"/                            (packagesInImage at: clsPkg) removeMethod:mthd. "does not belong to the package"
+			    methodPackage :=
+				    (packagesInImage at: mthdPkg ifAbsentPut:[
+					mthdPkg == #'__NoProject__' ifTrue:[
+					    (Package named:mthdPkg)
+					 ] ifFalse:[(Package named:mthdPkg)
+					 ].
+				     ]).
+			     methodPackage  addedMethod:mthd
+
+			].
+"/                    ].
+		]
+	    ]
+    ].
+"/    packagesInImage removeKey:#''.    "remove namespaces"
+    packagesInImage do:[:aPackage |
+	aPackage initializeInstalled.
+    ].
+    "the following is needed in a fresh image!!"
+    packagesInImage at:#'__NoProject__' ifAbsentPut:[(Package named:#'__NoProject__')].
+    ^ packagesInImage
+! !
+
+!PackageManager methodsFor:'accessing'!
+
+allClassCategories
+    | allClassCategories |
+    allClassCategories := SortedCollection new.
+
+    self packagesDo:[:aPackage |
+	allClassCategories addAll:aPackage classCategories
+    ].
+
+    ^ allClassCategories
+!
+
+allPackageCategories
+    ^ (self packages collect:[:aPackage | aPackage category]) asSet.
+!
+
+changes
+    ^ self class changes
+!
+
+defaultPackage
+    "return the value of the instance variable 'defaultPackage' (automatically generated)"
+
+    ^ defaultPackage
+!
+
+defaultPackage:something
+    "set the value of the instance variable 'defaultPackage' if the current default package
+    is also the working package. Change the working package "
+
+    workingPackage == defaultPackage ifTrue:[
+	workingPackage := something.
+    ].
+
+    defaultPackage := something.
+!
+
+packageNamed:anIdentifier
+    ^ self packageNamed:anIdentifier ifAbsent:[nil]
+!
+
+packageNamed:anIdentifier ifAbsent:aBlock
+    anIdentifier ifNil:[
+	^ aBlock value
+    ].
+    defaultPackage name == anIdentifier ifTrue:[
+	^ defaultPackage
+    ].
+    ^ packages atKey:anIdentifier ifAbsent:aBlock
+!
+
+packagesAtCategoryName:aCategoryName
+    ^ self packages select:[:aPackage |
+	(aPackage isInCategoryNamed:aCategoryName)
+    ].
+!
+
+packagesNamed:aCollectionOfPackageNames
+
+    ^ (aCollectionOfPackageNames collect:[:aName |
+	self packageNamed:aName
+    ]).
+!
+
+smalltalkChanges
+    ^ self class changes
+!
+
+workingPackage
+    "return the value of the instance variable 'workingPackage' (automatically generated)"
+
+    ^ workingPackage
+!
+
+workingPackage:aPackage
+    ((aPackage == defaultPackage) or:[self includesPackage:aPackage]) ifFalse:[
+	self error:'Trying to make a package that i do not know about the workingPackage!!'
+    ].
+
+    workingPackage removeDependent:self.
+    workingPackage:= aPackage.
+    workingPackage addDependent:self.
+! !
+
+!PackageManager methodsFor:'adding & removing'!
+
+addChange:aChange
+    ^ self class changes add:aChange.
+!
+
+addPackage:aPackage
+    "the reciever needs to be dependent on the packages just in case they change"
+    aPackage addDependent:self.
+    self basicAddPackage:aPackage.
+    self changed:#addPackage: with:aPackage
+!
+
+addPackages:aPackages
+    "the reciever needs to be dependent on the packages just in case they change"
+    aPackages do:[:aPackage |
+	self basicAddPackage:aPackage.
+    ].
+    self changed:#addPackages: with:aPackages
+!
+
+basicAddPackage:aPackage
+    "the reciever needs to be dependent on the packages just in case they change"
+    packages push:aPackage.
+!
+
+basicRemovePackage:aPackage
+    ^ packages removeKey:aPackage name
+!
+
+removeChange:aChange
+    ^ self class changes remove:aChange.
+!
+
+removePackage:aPackage
+    "the reciever needs to be dependent on the packages just in case they change"
+    aPackage removeDependent:self.
+    self basicRemovePackage:aPackage.
+    self changed:#removePackage: with:aPackage
+!
+
+removePackageNamed:aPackageName
+    | aPackage |
+    aPackage := (packages removeKey:aPackageName).
+    aPackage removeDependent:self.
+    self changed:#removePackage: with:aPackage
+! !
+
+!PackageManager methodsFor:'api'!
+
+addClass:aClass toPackage:newPackage
+    "A manager type of the method which should not be called from Smalltalk changes"
+    | oldPackageName oldPackage |
+
+    (self includesPackage:newPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', newPackage name.
+    ].
+    oldPackageName := aClass package.
+    oldPackage := self packageNamed:oldPackageName.
+
+    (oldPackageName == newPackage name) ifTrue:["error??"
+	newPackage addedClass:aClass.
+	^ self
+    ].
+
+    self setClass:aClass toPackage:newPackage.
+    PackageError handle:[:ex |
+	self setClass:aClass toPackage:oldPackage.
+	ex raise.
+    ] do:[
+	newPackage addedClass:aClass.
+	oldPackage overrideClassNamed:aClass name byPackageNamed:newPackage name.
+    ].
+!
+
+addMethod:aMethod toPackage:newPackage
+    | oldPackageName oldPackage|
+
+    (self includesPackage:newPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', newPackage name.
+    ].
+"/    self moveClass:aClass toPackage:newPackage.
+    oldPackageName := aMethod package.
+    oldPackage := self packageNamed:oldPackageName.
+
+    (oldPackageName == newPackage name) ifTrue:[
+	newPackage addedMethod:aMethod.
+	^ self  "error??"
+    ].
+
+    aMethod setPackage:newPackage name.
+
+    newPackage addedMethod:aMethod.
+    oldPackage overrideMethod:aMethod byPackageNamed:newPackage name.
+!
+
+installPackage:aPackage
+    "installs a package that the receiver is aware of into the image if not raise an error
+    for the sender to catch so it is able to handle it"
+    (self includesPackage:aPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', aPackage name,' so it cannot be installed!!'
+    ].
+    ^ (self getPackageHandlerForPackage:aPackage) installPackageIn:self
+!
+
+loadPackageFromFile:aFilename
+    "install a starter package which comes from a file. This is the
+    a state where the package has not yet entered the image but it
+    is a package that the receiver is aware of and has some initial
+    information about. Return the installed Package"
+
+    ^ (self getPackageReaderForFile:aFilename) loadPackageIn:self .
+!
+
+moveClass:aClass toPackage:newOwnerPackage
+    "i have the responsibilty to set aClasses new variable (newOwnerPackage name) and
+    all the methods in aClass with the same package name!!
+    "
+    | oldOwnerPackage|
+
+    oldOwnerPackage := self packageNamed:aClass package.
+
+    oldOwnerPackage ifNil:[
+	"error handling - if a package has accidentially been removed
+	and i do not know about it. Fake it and put it in the default package"
+       oldOwnerPackage := defaultPackage.
+       self setClass:aClass toPackage:defaultPackage.
+       (defaultPackage includesPackagedClassNamed:aClass name) ifTrue:[
+	   defaultPackage removedClassNamed:aClass name.
+       ].
+       defaultPackage addedClass:aClass.
+    ].
+
+    oldOwnerPackage == newOwnerPackage ifTrue:[
+	(oldOwnerPackage includesPackagedClassNamed:aClass name) ifFalse:[
+	    self setClass:aClass toPackage:newOwnerPackage.
+	    oldOwnerPackage addedClass:aClass.
+	].
+	^ self.
+    ].
+    "change the value of package to the new name... not sure if this is the correct place for this"
+    (oldOwnerPackage notNil
+	and:[aClass package == oldOwnerPackage name]) ifTrue:[
+	    self setClass:aClass toPackage:newOwnerPackage.
+    ].
+
+    self moveClassNamed:aClass name fromPackage:oldOwnerPackage toPackage:newOwnerPackage.
+!
+
+moveClassNamed:aClassName fromPackage:fromPackage toPackage:newOwnerPackage
+    "i have the responsibilty to set aClasses new variable (newOwnerPackage name) and
+    all the methods in aClass with the same package name!!
+    "
+    | oldOwnerPackage oldOwnerPackageIncludesMovingClass oldPackageMovingClass newPackagedClass |
+
+    oldOwnerPackage := fromPackage.
+    oldPackageMovingClass := (oldOwnerPackage packagedClassNamed:aClassName).
+    oldOwnerPackageIncludesMovingClass := oldPackageMovingClass notNil.
+
+    oldOwnerPackageIncludesMovingClass ifFalse:[
+	self error:'Error ', fromPackage name, ' does not know this class!!'.
+	^ self.
+    ].
+
+    (oldOwnerPackage == newOwnerPackage) ifTrue:[
+	"Mmm interesting. There is not much to do here. oldOwnerPackage knows the class already"
+	^ self
+    ].
+    (newPackagedClass := newOwnerPackage packagedClassNamed:aClassName) ifNotNil:[
+	PackageError raiseErrorString:newOwnerPackage name,  ' already knows a class with this name. Remove this class from here first!!'.
+	^ self.
+    ].
+    oldOwnerPackage movedClassNamed:aClassName toPackage:newOwnerPackage
+!
+
+moveMethod:aMethod toPackage:newOwnerPackage
+    |oldOwnerPackage|
+
+    aMethod mclass ifNil:[
+	self error:'Cannot move a method without an owning class!!'
+    ].
+
+    oldOwnerPackage := self packageNamed:aMethod package ifAbsent:[defaultPackage].
+
+    self setMethod:aMethod toPackage:newOwnerPackage.
+    (oldOwnerPackage definesSelector:aMethod name forClassNamed:(aMethod mclass name asSymbol)) ifFalse:[
+	newOwnerPackage addedMethod:aMethod.
+	^ self
+    ].
+    oldOwnerPackage movedMethod:aMethod toPackage:newOwnerPackage
+!
+
+removeClassNamed:aClass fromPackage:fromPackage
+    ^ self removeClassNamed:aClass fromPackage:fromPackage moveToDefaultPackage:true.
+!
+
+removeClassNamed:removeClassName fromPackage:fromPackage moveToDefaultPackage:moveToDefaultPackage
+    "this is different from removing a class from a system. If you want to do that do
+    aClass removeFromSystem and the package manager will react!!
+
+    This is an administration remove on the packages and just moves aClass to the responsibility
+    of the package manager's default class and removes all responsibilites from fromPackage.
+
+    "
+    | overriddingPackage overriddingPackageName removingPackagedClass |
+    removingPackagedClass :=  (fromPackage packagedClassNamed:removeClassName).
+    (self includesPackage:fromPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', fromPackage name.
+    ].
+
+    fromPackage == defaultPackage ifTrue:[
+	"when the packaged class is in the defaultClass it is removed from the system!!!!"
+	^ removingPackagedClass removeFromSystem.
+    ].
+    "if the fromPackage has been overridden all that needs to be done is that the
+    packages that the fromPackage has overridden needs to be swapped to the package that
+    the fromPackage has been overridden by. Then it can be removed from the fromPackage"
+    removingPackagedClass isInSmalltalk ifFalse:[
+	overriddingPackageName := (fromPackage overriddingPackageNameAtClassName:removeClassName).
+	overriddingPackage := self packageNamed:overriddingPackageName.
+	overriddingPackage ifNotNil:[
+	    self packagesDo:[:aPackage |
+		(fromPackage ~= aPackage and:[aPackage ~= defaultPackage]) ifTrue:[
+		    ((aPackage overriddenClassNamesByPackage:fromPackage) includes:removeClassName) ifTrue:[
+			"to keep class in smalltalk"
+
+			aPackage changePackageOverrideFromPackage:fromPackage toPackage:overriddingPackage
+			    forClassNamed:removeClassName.
+		    ].
+		].
+	    ].
+	    ^ removingPackagedClass removeFromPackage.
+	].
+    ].
+
+    "when we are here the fromPackage holds the currentRepresentation of the class in Smalltalk"
+    moveToDefaultPackage ifTrue:[ | return |
+	self setClass:removingPackagedClass classInSmalltalk toPackage:defaultPackage.
+	self packagesDo:[:aPackage |
+	    ((aPackage overriddenClassNamesByPackage:fromPackage) includes:removeClassName) ifTrue:[
+		"to keep class in smalltalk"
+		aPackage changePackageOverrideFromPackage:fromPackage toPackage:defaultPackage
+		    forClassNamed:removeClassName.
+	    ].
+	].
+	return := removingPackagedClass removeFromPackage.
+	removingPackagedClass package:defaultPackage.
+	defaultPackage addedPackagedClass:removingPackagedClass.
+	^ return
+    ].
+
+    ^ removingPackagedClass removeFromSystem.
+!
+
+removeMethod:aMethod fromPackage:aPackage
+    "add method to a package. At this point it is determined to be a loose method or not"
+    (self includesPackage:aPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', aPackage name.
+    ].
+    aPackage removedMethod:aMethod
+!
+
+savePackage:aPackage
+    self savePackage:aPackage as:aPackage filename.
+!
+
+savePackage:aPackage as:aFilename
+    "saves a package that the receiver is aware of if not raise an error
+    for the sender to catch so it is able to handle it"
+    (self includesPackage:aPackage) ifFalse:[
+	self error:'This package manager is not responsible of the package ', aPackage name,' so it cannot be saved!!'
+    ].
+
+    (self getPackageHandlerForPackage:aPackage) savePackageAs:aFilename.
+    ^ aPackage.
+!
+
+uninstallPackage:aPackage
+    "need to include the restoration of packages aPackage has overridden!!!!!!!!"
+    (self includesPackage:aPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', aPackage name,' so it cannot be uninstalled!!'
+    ].
+
+    (self isBasePackage:aPackage) ifTrue:[
+	self error:aPackage name asString, ' is a base package and cannot be uninstalled!!'.
+    ].
+
+    aPackage uninstallFromManager:self.
+!
+
+unloadPackage:aPackage
+    "unloads the package from the receiver.Does not need to
+     make any checks here as it is not installed."
+
+    (self includesPackage:aPackage) ifFalse:[
+	self error:'The package manager does not know of the package ', aPackage name.
+    ].
+
+    (self isBasePackage:aPackage) ifTrue:[
+	self error:aPackage name asString, ' is a base package and cannot be unloaded!!'.
+    ].
+
+    aPackage isInstalled ifTrue:[
+	self uninstallPackage:aPackage.
+    ].
+    self removePackage:aPackage.
+    aPackage removeFromSystem.
+    self changed:#unloadPackage: with:aPackage.
+    ^ aPackage.
+!
+
+unloadPackageNamed:aPackageName
+    "unloads the package from the receiver.Does not need to
+     make any checks here as it is not installed."
+    | aPackage |
+    (self includesPackageNamed:aPackageName) ifFalse:[
+	self error:'The package manager does not know of the package ', aPackageName.
+    ].
+    aPackage := self packageNamed:aPackageName.
+    aPackage == workingPackage ifTrue:[
+	PackageNotification raiseUnloadingWorkingPackage:aPackageName.
+	workingPackage := defaultPackage.
+    ].
+
+    self unloadPackage:aPackage.
+! !
+
+!PackageManager methodsFor:'basic admin'!
+
+setClass:aClass toPackage:newOwnerPackage
+    "sets the variable package in both class and methods belonging to the class
+     but only with the same name as the classes old package"
+    |oldOwnerPackageName newOwnerPackageName|
+    newOwnerPackageName := newOwnerPackage name.
+    oldOwnerPackageName := aClass package.
+    aClass setPackage:newOwnerPackageName.
+    aClass methodDictionary copy keysAndValuesDo:[:aMethodName :aMethod |
+	aMethod package == oldOwnerPackageName ifTrue:[
+	    aMethod setPackage:newOwnerPackageName
+	].
+    ].
+
+    aClass class methodDictionary copy keysAndValuesDo:[:aMethodName :aMethod |
+	aMethod package == oldOwnerPackageName ifTrue:[
+	    aMethod setPackage:newOwnerPackageName
+	].
+    ].
+!
+
+setMethod:aMethod toPackage:newOwnerPackage
+    "sets the variable package"
+    aMethod setPackage:newOwnerPackage name.
+! !
+
+!PackageManager methodsFor:'change & update'!
+
+changeSetChanged:something with:aChange from:changedObject
+    "find out what type of change it is and send the packages the corresponding
+     message to is if they are affected. If they are they should (if they are behaving)
+    send me a change notification to inform me about it(see packageChanged:with:from:)!!
+    "
+    | classNameOfChange packageName changeClass changeMethod |
+    aChange isCollection ifTrue:[
+	something == #removeAll: ifTrue:[
+	    "happens after checking in"
+"/            self smalltalkChanges removeAll:aChange
+	].
+	^ self "do i need to do anything???"
+    ].
+    (aChange isClassChange) ifFalse:[
+	self error:' What is this???'.
+    ].
+
+    (aChange isKindOf:self methodPackageChangeClass) ifTrue:[| aMethod methodOwnedClass oldPackageName |
+	aMethod := aChange previousVersion.
+	methodOwnedClass := aChange changeClass.
+	oldPackageName := aChange oldPackageName.
+	self methodPackageChange:aMethod class:methodOwnedClass oldPackageName:oldPackageName.
+	^ self
+    ].
+    (aChange isKindOf:self classPackageChangeClass) ifTrue:[| classToMove oldPackageName |
+	classToMove := aChange changeClass.
+	oldPackageName := aChange oldPackageName.
+	self classPackageChange:classToMove oldPackageName:oldPackageName.
+	^ self
+    ].
+
+    (aChange isMethodCategoryChange) ifTrue:[
+	self packagesDo:[:aPackage |
+	     "(aPackage isDependentOnMethodNamed:aChange selector forClassNamed:aChange className)" false ifTrue:[
+		aPackage methodCategoryChange:aChange.
+	    ].
+	].
+	^ self
+    ].
+
+    "the following is similar to the one above"
+    (aChange isMethodCategoryRenameChange) ifTrue:[
+	self packagesDo:[:aPackage |
+	    "(aPackage isDependentOnMethodNamed:aChange selector forClassNamed:aChange className)"  false ifTrue:[
+		aPackage methodCategoryRenameChange:aChange.
+	    ].
+	].
+	^ self
+    ].
+
+    (aChange isMethodRemoveChange) ifTrue:[
+	self packagesDo:[:aPackage |
+	    (aPackage isDependentOnMethodNamed:aChange selector forClassNamed:aChange className) ifTrue:[
+		aChange previousVersion ifNotNil:[
+		    aPackage methodRemoveChange:aChange.
+		].
+	    ].
+	].
+	^ self
+    ].
+
+    (aChange isMethodChange) ifTrue:[
+	"A new created method or a modified method"
+	changeMethod := aChange changeMethod.
+	packageName := changeMethod package.
+
+	self packagesDo:[:aPackage |
+	    (Switch new)
+		if:[(aPackage name == packageName)] then:[
+		    self addMethod:changeMethod toPackage:aPackage];
+		if:[(aPackage isDependentOnMethodNamed:aChange selector forClassNamed:aChange className)] then:[
+		    aPackage methodChanged:aChange];
+		value.
+	].
+	^ self
+    ].
+
+    aChange isClassChange ifTrue:[
+	(aChange isClassRemoveChange) ifTrue:[
+	    "results in one package being overridden by Smalltalk"
+	    classNameOfChange := aChange className asSymbol.
+	    self packagesDo:[:aPackage |
+		(Switch new)
+		    if:[(aPackage isDependentOnClassNamed:classNameOfChange)] then:[
+			aPackage classRemoveChange:aChange];
+		    value.
+		].
+	    ^ self
+	].
+
+	(aChange isClassDefinitionChange) ifTrue:[
+	    "This change is not added to the working class"
+	    "changes to instance variables, classVariableNames, poolDictionaries, category"
+
+	    classNameOfChange := aChange className asSymbol.
+	    changeClass := aChange changeClass.
+	    packageName := changeClass package.
+
+	    self packagesDo:[:aPackage |
+		(Switch new)
+		    if:[(aPackage name == packageName)] then:[
+			(aPackage includesPackagedClassNamed:classNameOfChange) ifTrue:[
+			     aPackage removedClassNamed:classNameOfChange.
+			].
+			aPackage addedClass:changeClass];
+		    if:[(aPackage isDependentOnClassNamed:classNameOfChange)] then:[
+			aPackage classDefinitionChange:aChange];
+		    value.
+
+	    ].
+	    ^ self
+
+	].
+	(aChange isClassInstVarDefinitionChange)  ifTrue:[
+	    "This change is not added to the working class"
+	    "changes to instance variables, classVariableNames, poolDictionaries, category"
+
+	    classNameOfChange := aChange className.
+	    changeClass := aChange changeClass.
+	    packageName := changeClass package.
+
+	    self packagesDo:[:aPackage |
+		(Switch new)
+		    if:[(aPackage name == packageName) ] then:[
+			aPackage addedClass:changeClass];
+		    if:[(aPackage isDependentOnClassNamed:classNameOfChange) ] then:[
+			aPackage classInstVarDefinitionChange:aChange].
+	    ].
+	    ^ self
+	].
+	(aChange isClassRenameChange) ifTrue:[
+	    "This change is not added to the working class"
+	    classNameOfChange := aChange className.
+	    changeClass := aChange changeClass.
+	    packageName := changeClass package.
+
+	    self packagesDo:[:aPackage |
+		(Switch new)
+		    if:[(aPackage name == packageName) ] then:[
+			aPackage addedClass:changeClass];
+		    if:[(aPackage isDependentOnClassNamed:classNameOfChange) ] then:[
+			aPackage classRenameChange:aChange];
+		    value.
+	    ].
+	    ^ self
+	].
+
+	self breakPoint:''.
+    ].
+    self breakPoint:''.
+!
+
+classPackageChange:classToOverride oldPackageName:oldPackageName
+    "reacts to a class package change
+    Assertion:
+	aClass package ~= oldPackageName
+    "
+
+    self setClass:classToOverride toPackage:(self packageNamed:oldPackageName).
+    self error:'Sorry, this function is no longer available other than within the packageBrowser. ', Character cr asString,
+	Character cr asString, ' This action has done nothing!!'.
+
+"/    | newPackageName newOwnerPackage|
+"/    newPackageName := classToOverride package.
+"/    newOwnerPackage := self packageNamed:newPackageName ifAbsent:[self newPackageNamed:newPackageName].
+"/
+"/    "fake this... maybe this is a kludge..."
+"/    self setClass:classToOverride toPackage:(self packageNamed:oldPackageName).
+"/
+"/    self addClass:classToOverride toPackage:newOwnerPackage.
+!
+
+methodPackageChange:aMethod class:methodOwnedClass oldPackageName:oldPackageName
+
+    self setMethod:aMethod toPackage:(self packageNamed:oldPackageName).
+    Transcript nextPutAll:'Sorry, this function is no longer available other than within the packageBrowser. ', Character cr asString,
+	Character cr asString, ' This action has done nothing!! >>methodPackageChange:aMethod class:methodOwnedClass oldPackageName:oldPackageName'.
+
+
+"/    | newPackageName oldOwnerPackage newOwnerPackage|
+"/
+"/    newPackageName := aMethod package.
+"/    oldOwnerPackage :=(self packageNamed:oldPackageName).
+"/    newOwnerPackage := (self packageNamed:newPackageName).
+"/
+"/    newOwnerPackage ifNil:[
+"/        PackageError raiseErrorString:'The package ', newPackageName, ' is not known',
+"/            ' to this packageManager', ' and so cannot realise this methodPackageChange'
+"/
+"/    ].
+"/
+"/    oldOwnerPackage ifNil:[
+"/        PackageError raiseErrorString:'The package ', oldPackageName, ' is not known',
+"/            ' to this packageManager', ' and so cannot realise this methodPackageChange'
+"/    ].
+"/
+"/    oldOwnerPackage movedMethod:aMethod toPackage:newOwnerPackage
+!
+
+packageChanged:something with:aParameter from:changedObject
+   "maybe send a change notification for views here???"
+"/    self halt.
+    self addChange:aParameter.
+    self changed:#packagedChanged with:changedObject
+!
+
+update:something with:aParameter from:changedObject
+
+    (self includesPackage:changedObject) ifTrue:[
+	self packageChanged:something with:aParameter from:changedObject.
+	^ self.
+    ].
+    (changedObject == ChangeSet current) ifTrue:[
+	self changeSetChanged:something with:aParameter from:changedObject.
+	^ self.
+    ].
+! !
+
+!PackageManager methodsFor:'checks'!
+
+canLoadPackage:aPackage
+    ""
+    (self includesPackage:aPackage) ifTrue:[
+	Notification raise.
+    ].
+! !
+
+!PackageManager methodsFor:'enumarating'!
+
+packagesDo:aOneArgBlock
+    "should this or should this not include the defaultPackage??? should it
+    be treated seperately?"
+    aOneArgBlock value:defaultPackage.
+    super packagesDo:aOneArgBlock.
+!
+
+packagesSelect:aOneArgBlock
+    "should this or should this not include the defaultPackage??? should it
+    be treated seperately?"
+    | selectedPackages |
+    selectedPackages := (self packages select:aOneArgBlock).
+
+    (aOneArgBlock value:defaultPackage) ifTrue:[
+	selectedPackages add:defaultPackage.
+    ].
+    ^ selectedPackages
+! !
+
+!PackageManager methodsFor:'errors'!
+
+recoveryHandlerDo:aBlock forException:packageErrorClass
+    "an atomic action is about to happen. This should succeed or
+    fail and return to the previous state."
+
+    "to do - this could be done by an extra class.
+    could save the state of the receiver before this action is done
+    along with a 'transaction number' held in the receivers class to make
+    sure we are consistant. The hard copy could then be the backup. This
+    all depends on how long it takes to make the backup and how often
+    we are going to do this.
+    "
+    packageErrorClass handle:[:ex |
+	Transcript show:ex errorString.
+    ] do:[
+	aBlock value
+    ]
+! !
+
+!PackageManager methodsFor:'factory'!
+
+classPackageChangeClass
+    ^ Smalltalk classNamed:#'Packages::ChangeFaker::ClassPackageChange'
+!
+
+getPackageSaverForPackage:aPackage
+    ^ StxPackageFileWriter forPackage:aPackage
+!
+
+methodPackageChangeClass
+    ^ Smalltalk classNamed:#'Packages::ChangeFaker::MethodPackageChange'
+!
+
+newPackageNamed:aString
+    | newPackage |
+
+    (self includesPackageNamed:aString) ifTrue:[
+	PackageError raiseCannotAddAsPackageManagerAlreadyIncludesPackageNamed:aString
+    ].
+
+    newPackage := self packageClass named:aString addToManager:self.
+    newPackage initializeInstalled.
+    ^ newPackage
+!
+
+packageClass
+    ^ Package
+! !
+
+!PackageManager methodsFor:'initialization'!
+
+initialize
+    defaultPackage := self class defaultPackage.
+    workingPackage := defaultPackage.
+    super initialize.
+!
+
+uninitialize
+
+    self packagesDo:[:aPackage |
+	self removeDependent:aPackage.
+    ].
+    defaultPackage removeDependent:self.
+
+    packages := nil.
+    super uninitialize.
+! !
+
+!PackageManager methodsFor:'private-opening'!
+
+getPackageHandlerForPackage:aPackage
+
+    | aPackageHandler |
+
+    (aPackageHandler := aPackage packageHandler) ifNil:[
+	aPackageHandler := PackageHandler forPackage:aPackage.
+    ].
+
+    ^ aPackageHandler
+!
+
+getPackageReaderForFile:aFilename
+    ^ StxPackageFileReader forFilename:aFilename
+! !
+
+!PackageManager methodsFor:'queries'!
+
+includesPackage:anObject
+    ^ ((packages includes:anObject)or:[defaultPackage == anObject])
+!
+
+isBasePackage:aPackage
+
+    ^ self class basePackageNames includes:aPackage name.
+! !
+
+!PackageManager class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageManager.st,v 1.9 2006/08/24 08:38:42 cg Exp $'
+! !
+
+PackageManager initialize!
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageManagerTests.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,730 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractTestCases subclass:#PackageManagerTests
+	instanceVariableNames:'packageManager defaultPackage'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Managers'
+!
+
+!PackageManagerTests class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+         (james@miraculix)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+history
+    "Created: / 24.1.2003 / 16:15:21 / james"
+! !
+
+!PackageManagerTests methodsFor:'initialize / release'!
+
+initialize
+
+    packageManager ifNil:[
+        packageManager := self packageManager.
+    ].
+
+    defaultPackage ifNil:[
+        defaultPackage := packageManager defaultPackage.
+    ].
+!
+
+setUp
+    "common setup - invoked before testing"
+    super setUp.
+    self setUpUsedClasses.
+!
+
+setUpAllForQWERTY
+    | class copyQWERTYDic|
+    
+    (class := Smalltalk at:#QWERTY) ifNil:[
+        self createClassNamed:#QWERTY. 
+        (class := Smalltalk at:#QWERTY).
+    ].
+    copyQWERTYDic := QWERTY methodDictionary copy.
+    copyQWERTYDic removeKey:#aDummyMethod ifAbsent:[].
+    copyQWERTYDic removeKey:#aDummyMethod2 ifAbsent:[].
+    copyQWERTYDic removeKey:#aDummyMethod3 ifAbsent:[].
+    copyQWERTYDic keysAndValuesDo:[:key :value |
+       QWERTY methodDictionary removeKey:key.
+    ].
+
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod3 1 + 1.'.
+    ].
+    packageManager moveClass:QWERTY toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:defaultPackage.
+!
+
+setUpAllForQWERTZ
+    | class copyQWERTZDic|
+    (class := Smalltalk at:#QWERTZ) ifNil:[
+        self createClassNamed:#QWERTZ.
+        (class := Smalltalk at:#QWERTZ)
+    ].
+
+    copyQWERTZDic := QWERTZ methodDictionary copy.
+    copyQWERTZDic removeKey:#aDummyMethod ifAbsent:[].
+    copyQWERTZDic removeKey:#aDummyMethod2 ifAbsent:[].
+    copyQWERTZDic removeKey:#aDummyMethod3 ifAbsent:[].
+    copyQWERTZDic keysAndValuesDo:[:key :value |
+       QWERTZ methodDictionary removeKey:key.
+    ].
+
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod3 1 + 1.'.
+    ].
+
+    packageManager moveClass:QWERTZ toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:defaultPackage.
+!
+
+setUpUsedClasses
+    "common setup - invoked before testing"
+    |  |
+    self setUpAllForQWERTZ.
+    self setUpAllForQWERTY.                
+!
+
+tearDown
+    "common cleanup - invoked after testing"
+
+    "move class package to where it was"
+    super tearDown
+! !
+
+!PackageManagerTests methodsFor:'test - adding and removing'!
+
+test_addClass_toPackage
+    | packageTestCases oldPackage|
+    "prerequisites to test"
+    "QWERTZ is in workingPackage"
+    self assert:(packageManager packageNamed:(QWERTZ package)) == defaultPackage.
+    [
+        "set up"
+        oldPackage := packageManager newPackageNamed:#'oldPackage'.       
+        packageManager moveClass:QWERTZ toPackage:oldPackage.
+
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        oldPackage :=  packageManager packageNamed:(QWERTZ package).
+        packageManager addClass:QWERTZ toPackage:packageTestCases.
+
+        self assert: (packageTestCases isDirty).
+        self assert: (packageTestCases isInstalled).
+        self assert: (packageTestCases packagedClassNamed:#QWERTZ) notNil.
+        self assert: (packageTestCases packagedClassNamed:#QWERTZ) isInSmalltalk.    
+        self assert: (oldPackage packagedClassNamed:#QWERTZ) notNil.         
+        self shouldnt: (oldPackage packagedClassNamed:#QWERTZ) isInSmalltalk.           
+
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+       ].
+        oldPackage ifNotNil:[
+            packageManager removePackage:oldPackage.
+       ].
+    ]
+!
+
+test_addMethod_toPackage
+    |method1 method2 packageTestCases|
+    "prerequisites to test"
+    "none at the moment"
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        method1 := (QWERTZ compiledMethodAt:#aDummyMethod).
+        method2 := (QWERTZ compiledMethodAt:#aDummyMethod2).
+
+        packageManager addMethod:method1 toPackage:packageTestCases.
+        packageManager addMethod:method2 toPackage:packageTestCases.
+
+        self assert:(packageTestCases isDirty).
+        self assert:(packageTestCases isInstalled).
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_moveMethod_toPackage
+    | packageTestCases method1 method2|
+    "prerequisites to test"
+
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        method1 := (QWERTZ compiledMethodAt:#aDummyMethod).
+        method2 := (QWERTZ compiledMethodAt:#aDummyMethod2).
+        packageManager moveMethod:method1 toPackage:packageTestCases.
+        packageManager moveMethod:method2 toPackage:packageTestCases.
+
+        self assert:(packageTestCases isDirty).
+        self assert:(packageTestCases isInstalled).
+
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_removeClassNamed_fromPackage
+    | packageTestCases |
+    "prerequisites to test"
+
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager moveClass:QWERTZ toPackage:packageTestCases. 
+        packageManager removeClassNamed:#QWERTZ fromPackage:packageTestCases.
+
+        "test the class was completely removed!!"
+        self assert:(Smalltalk at:#QWERTZ) notNil.
+
+        "test that the package was changed"
+        self assert:(packageTestCases isDirty).
+        "test that the package still is installed"
+        self assert:(packageTestCases isInstalled).
+        "test that the class was removed from packageTestCases"
+        self shouldnt:(packageTestCases includesPackagedClassNamed:#QWERTZ).
+
+        "the class was moved where. Check it is here"
+        self assert:(packageManager defaultPackage includesPackagedClassNamed:#QWERTZ).
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_removeClass_fromPackage
+    "to test that when a "
+    | oldPackage |
+    [
+        "pre-setup"
+            "i expect setUp should do this!!"
+        self assert:(packageManager defaultPackage includesPackagedClassNamed:#QWERTZ).
+        oldPackage := Package packageManager newPackageNamed:#'oldPackage'.
+        packageManager moveClassNamed:#QWERTZ fromPackage:defaultPackage toPackage:oldPackage.
+
+        "prerequisites"
+        self shouldnt: (packageManager defaultPackage includesPackagedClassNamed:#QWERTZ).
+        self assert: (oldPackage includesPackagedClassNamed:#QWERTZ).
+        self shouldnt: (defaultPackage includesPackagedClassNamed:#QWERTZ).
+
+        "check that the added class in oldPackage is in smalltalk
+         and that that oldPackage has a packaged class representing it."
+        self assert: (oldPackage packagedClassNamed:#QWERTZ) notNil.
+        self assert: (oldPackage packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        packageManager removeClassNamed:#QWERTZ fromPackage:oldPackage.
+
+        "check that oldPackage has NOT got a packaged class representing it."
+        self assert: (oldPackage packagedClassNamed:#QWERTZ) isNil.
+        "check that the deleted class is then stored in workingClass"
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) notNil.
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) isInSmalltalk.        
+
+    ] ensure:
+    [
+        oldPackage ifNotNil:[
+            packageManager removePackage:oldPackage.
+        ].
+    ].
+!
+
+test_removeClass_fromPackage2
+    "Test:
+    When the manager removes the responsibility of a class from a package via:
+        PackageManager>>removeClass:fromPackage:
+
+    If a package overid another package with a class, and this package was
+    deleted, the overriden information has to be updated.
+
+    Sequence of events
+        package1 owns class1
+        package2 overrides class1
+            package2 owns class1
+            package1 stores class1 as overriddenBy: package2
+        packageManager remove:class1 from:package2
+            'at the moment'
+            package2 no longer owns class1
+            package stores class1 as overriddenBy:package2 'WRONG!!!!'
+
+    There are two ways of going from here:
+
+        1)  package1 brings its version forward redefining the smalltalk version
+        2)  defaultPackage now owns this definition of class1 and package1 must update
+            this change.
+
+    I choose (2) as (1) may confuse the user. (2) has the advanatage that the Smalltalk
+    dictionary does not change - and is what i would expect...
+    "
+    | package1 package2 |
+    "i expect setUp should do this!!"
+    self assert:(defaultPackage includesPackagedClassNamed:#QWERTZ).
+    [
+        "pre-setup"
+        package1 := Package packageManager newPackageNamed:#'package1'.
+        package2 := Package packageManager newPackageNamed:#'package2'. 
+        packageManager moveClassNamed:#QWERTZ fromPackage:defaultPackage toPackage:package1.
+
+        "prerequisites"
+        self shouldnt: (defaultPackage includesPackagedClassNamed:#QWERTZ).
+        self assert: (package1 includesPackagedClassNamed:#QWERTZ).
+
+        "check that the added class in package1 is in smalltalk
+         and that that package1 has a packaged class representing it."
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        "package2 overrides the responsibility of QWERTZ"
+        packageManager addClass:QWERTZ toPackage:package2.
+        "package2 should be responsible for QWERTZ and package1 should store that
+        it was package2 that overrid the change"
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert: (package2 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package2 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert:(package1 overriddenClassNamesByPackage:package2) size == 1.
+        self assert:(package1 overriddenClassNamesByPackage:package2) first == #QWERTZ. 
+
+        "remove the class from the package2. This should make all the responsibilities
+        go to defaultPackage in packageManager."  
+        packageManager removeClassNamed:#QWERTZ fromPackage:package2.
+
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.    
+
+        self assert: (package2 packagedClassNamed:#QWERTZ) isNil.
+        self assert:(package1 overriddenClassNamesByPackage:package2) size == 0.
+
+        self assert:(package1 overriddenClassNamesByPackage:defaultPackage) size == 1.
+        self assert:(package1 overriddenClassNamesByPackage:defaultPackage) first == #QWERTZ. 
+
+        "check that the deleted class is then stored in workingClass"
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) notNil.
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) isInSmalltalk.        
+
+    ] ensure:
+    [
+        package1 ifNotNil:[
+            packageManager removePackage:package1.
+        ].
+        package2 ifNotNil:[
+            packageManager removePackage:package2.
+        ].
+    ].
+!
+
+test_removeClass_fromPackage3
+    "to test that when a "
+    | package1 |
+    [
+        "pre-setup"
+            "i expect setUp should do this!!"
+        self assert:(packageManager defaultPackage includesPackagedClassNamed:#QWERTZ).
+        package1 := Package packageManager newPackageNamed:#'package1'.
+        packageManager moveClassNamed:#QWERTZ fromPackage:defaultPackage toPackage:package1.
+
+        "prerequisites"
+        self shouldnt: (packageManager defaultPackage includesPackagedClassNamed:#QWERTZ).
+        self assert: (package1 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt: (defaultPackage includesPackagedClassNamed:#QWERTZ).
+
+        "check that the added class in package1 is in smalltalk
+         and that that package1 has a packaged class representing it."
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        packageManager removeClassNamed:#QWERTZ fromPackage:package1.
+
+        "check that package1 has NOT got a packaged class representing it."
+        self assert: (package1 packagedClassNamed:#QWERTZ) isNil.
+        "check that the deleted class is then stored in workingClass"
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) notNil.
+        self assert: (defaultPackage packagedClassNamed:#QWERTZ) isInSmalltalk.  
+        self assert:((defaultPackage packagedClassNamed:#QWERTZ) packagedMethods size == 3).
+        self assert: (package1 packagedMethods at:#QWERTZ ifAbsent:[nil]) isNil.
+    ] ensure:
+    [
+        package1 ifNotNil:[
+            packageManager removePackage:package1.
+        ].
+    ].
+!
+
+test_removeMethod_fromPackage
+    |method1 method2 packageTestCases|
+    "prerequisites to test"
+
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        method1 := (QWERTZ compiledMethodAt:#aDummyMethod).
+        method2 := (QWERTZ compiledMethodAt:#aDummyMethod2).
+
+        packageManager moveClass:QWERTZ toPackage:packageTestCases.
+
+        packageManager moveMethod:method1 toPackage:packageTestCases.
+        packageManager moveMethod:method2 toPackage:packageTestCases.
+
+        self packageManager removeMethod:method2 fromPackage:packageTestCases.
+
+        self assert:(packageTestCases includesPackagedClassNamed:#QWERTZ).
+        self assert:(Smalltalk at:#QWERTZ) notNil.
+        self assert:(packageTestCases isDirty).
+        self assert:(packageTestCases isInstalled).
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_removePackage
+    "Test:
+    When the manager removes the responsibility of a class from a package via:
+        PackageManager>>removeClass:fromPackage:
+
+    If a package overid another package with a class, and this package was
+    deleted, the overriden information has to be updated.
+
+    Sequence of events
+        package1 owns class1
+        package2 overrides class1
+        package3 overrides class1
+            package3 owns class1
+            package2 stores class1 as overriddenBy: package3
+            package1 stores class1 as overriddenBy: package2
+
+        packageManager removePackage:package2
+            'at the moment '
+            package stores class1 as overriddenBy:package2 'WRONG!!!!'
+            package3 owns class1
+
+    "
+    | package1 package2 package3 |
+    "i expect setUp should do this!!"
+    self assert:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ).
+    [
+        "pre-setup"
+        package1 := Package packageManager newPackageNamed:#'package1'.
+        package2 := Package packageManager newPackageNamed:#'package2'.
+        package3 := Package packageManager newPackageNamed:#'package3'.
+        packageManager moveClassNamed:#QWERTZ fromPackage:defaultPackage toPackage:package1.
+
+        "prerequisites"
+        self shouldnt: (packageManager workingPackage includesPackagedClassNamed:#QWERTZ).
+        self assert: (package1 includesPackagedClassNamed:#QWERTZ).
+
+        "check that the added class in oldPackage is in smalltalk
+         and that that oldPackage has a packaged class representing it."
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        "package2 overrides the responsibility of QWERTZ"
+        packageManager addClass:QWERTZ toPackage:package2.
+        "package2 should be responsible for QWERTZ and package1 should store that
+        it was package2 that overrid the change"
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert: (package2 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package2 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert:(package1 overriddenClassNamesByPackage:package2) size == 1.
+        self assert:(package1 overriddenClassNamesByPackage:package2) first == #QWERTZ.
+
+        "package3 overrides the responsibility of QWERTZ"
+        packageManager addClass:QWERTZ toPackage:package3.
+        "package3 should be responsible for QWERTZ and package2 should store that
+        it was package2 that overrid the change and package1 should store that package2
+        overrid its changes"
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert: (package2 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package2 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        self assert: (package3 packagedClassNamed:#QWERTZ) notNil.
+        self assert: (package3 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        self assert:(package1 overriddenClassNamesByPackage:package2) size == 1.
+        self assert:(package1 overriddenClassNamesByPackage:package2) first == #QWERTZ. 
+        self assert:(package2 overriddenClassNamesByPackage:package3) size == 1.
+        self assert:(package2 overriddenClassNamesByPackage:package3) first == #QWERTZ. 
+
+        "remove the package package2. This should make all the responsibilities
+        stay in package3!!"
+        packageManager unloadPackage:package2. 
+        self assert: (package1 packagedClassNamed:#QWERTZ) notNil.
+        self shouldnt: (package1 packagedClassNamed:#QWERTZ) isInSmalltalk.    
+        self assert:(package1 overriddenClassNamesByPackage:package2) size == 0.
+        self assert:(package1 overriddenClassNamesByPackage:defaultPackage) size == 0.
+
+        self shouldnt: (packageManager includesPackage:package2).
+
+        "check that the deleted class is then stored in package3"
+        self assert:(package1 overriddenClassNamesByPackage:package3) size == 1.
+        self assert:(package1 overriddenClassNamesByPackage:package3) first == #QWERTZ. 
+
+    ] ensure:
+    [
+        package1 ifNotNil:[
+            packageManager removePackageNamed:#'package1'.
+        ].
+        (packageManager includesPackage:package2) ifTrue:[
+            packageManager removePackageNamed:#'package2'.
+        ].
+        package3 ifNotNil:[
+            packageManager removePackageNamed:#'package3'.
+        ].
+    ].
+! !
+
+!PackageManagerTests methodsFor:'test - moving'!
+
+test_addClass_PackageError
+    "Move QWERTZ class to the default package that already knows it!! it should complain"
+    [
+        self should:[packageManager addClass:QWERTZ toPackage:defaultPackage] raise:PackageError
+
+    ] ensure:[
+    ].
+!
+
+test_addClass_Packaged_Error2
+    "A class can only be added to a package when it doesnt have a class with the same name.
+    if it does a PackageError occurs!!"
+    | package1 package2|
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self shouldnt:(package1 isDirty).
+        self shouldnt:(package2 isDirty).
+
+        "Add the class to package1 and package2 and then attempt to add it to package1 again"
+        packageManager addClass:QWERTZ toPackage:package1.
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.   
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ).   
+
+        packageManager addClass:QWERTZ toPackage:package2.
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.      
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+
+        "QWERTZ is already in Smalltalk assigned to package2"
+        self should:[packageManager addClass:QWERTZ toPackage:package2] raise:PackageError.
+        "The state should stay the same as before this action was carried out"
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.      
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.  
+
+        "QWERTZ is already in Smalltalk but assigned to package2" 
+        packageManager addClass:QWERTZ toPackage:package1.
+        "QWERTZ is assigned to package 1"
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.      
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.       
+
+        packageManager addClass:QWERTZ toPackage:defaultPackage.
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+    ].
+!
+
+test_moveClass1
+    "Move QWERTZ class to a new package named the same as the old package
+    but with a 1 on the end. Then move the class back."
+    | package1 package2|
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self shouldnt:(package1 isDirty).
+        self shouldnt:(package2 isDirty).
+
+        "Make the representation of QWERTZ is in the default package and
+        have overriddenPackagedClasses in package1 and package2!!"
+        packageManager addClass:QWERTZ toPackage:package1.
+        packageManager addClass:QWERTZ toPackage:package2.      
+        packageManager addClass:QWERTZ toPackage:defaultPackage.
+
+        self assert:(QWERTZ package == defaultPackage name).
+
+        self assert:(package1 overriddenClassChangesIncludesClassNamed:#QWERTZ).
+        self assert:(package2 overriddenClassChangesIncludesClassNamed:#QWERTZ).
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+
+        self assert:(package1 isDirty).
+        self assert:(package2 isDirty).
+
+        "It is in defaultPackage"
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+
+        "<tested method>"
+            self should:[packageManager moveClassNamed:#QWERTZ fromPackage:package1 toPackage:package2] raise:PackageError. 
+            "If a class already owns a preresentation of a class by the same name it must be removed
+             BEFORE the above action can take place. The state should remain the same as before"
+        "</tested method>"
+
+        self assert:(package1 overriddenClassChangesIncludesClassNamed:#QWERTZ).
+        self assert:(package2 overriddenClassChangesIncludesClassNamed:#QWERTZ).
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+
+        self assert:(package1 isDirty).
+        self assert:(package2 isDirty).
+        "It is in defaultPackage"
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+
+        "<tested method with it removed from package2>"
+           packageManager removeClassNamed:#QWERTZ fromPackage:package2.
+           packageManager moveClassNamed:#QWERTZ fromPackage:package1 toPackage:package2. 
+        "</tested method>"
+
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt:(package1 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+        self assert:(QWERTZ package == defaultPackage name).
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+        "<tested method>"
+            packageManager moveClassNamed:#QWERTZ fromPackage:package2 toPackage:package1. 
+        "</tested method>>"
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+        "<tested method>"
+            self should:[packageManager moveClassNamed:#QWERTZ fromPackage:package1 toPackage:defaultPackage] raise:PackageError. 
+        "</tested method>>"
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package2'.
+        packageManager unloadPackageNamed:#'package1'.
+    ].
+!
+
+test_moveClass2
+    "Move QWERTZ class to a new package named the same as the old package
+    but with a 1 on the end. Then move the class back."
+    | package1 package2|
+    [
+        package1 := packageManager packageNamed:#'package1' ifAbsent:[
+            packageManager newPackageNamed:#'package1'
+        ]. 
+        package2 := packageManager packageNamed:#'package2'ifAbsent:[
+            packageManager newPackageNamed:#'package2'
+        ]. 
+        self shouldnt:(package1 isDirty).
+        self shouldnt:(package2 isDirty).
+
+        "Make the representation of QWERTZ is in the default package and
+        have overriddenPackagedClasses in package1 and package2!!"
+        packageManager addClass:QWERTZ toPackage:package1.
+
+        self assert:(QWERTZ package == package1 name).
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        self assert:(package1 isDirty).
+
+        "<tested method>"  "here package1 'owns' the class in smalltalk. After the method has been evaluated
+          package2 should 'own' the class in smalltalk"
+            packageManager moveClassNamed:#QWERTZ fromPackage:package1 toPackage:package2. 
+        "</tested method>"
+
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt:(package1 includesPackagedClassNamed:#QWERTZ).
+
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.    
+
+        self assert:(QWERTZ package == package2 name).
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+
+        "<tested method>"
+            packageManager addClass:QWERTZ toPackage:defaultPackage.
+        "</tested method>"
+
+    ] ensure:[
+        packageManager unloadPackage:package2.
+        packageManager unloadPackage:package1.
+    ].
+! !
+
+!PackageManagerTests class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageManagerTests.st,v 1.4 2006/01/10 09:31:56 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageNotification.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,51 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Notification subclass:#PackageNotification
+	instanceVariableNames:'package'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Exception-Notifications'
+!
+
+!PackageNotification class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageNotification class methodsFor:'raising'!
+
+raiseUnloadingWorkingPackage:aPackageName
+    ^ self raiseErrorString:'Attempting to unload a workingPackage, will by default unload the package /'withCRs,
+        'and set the working package as the default package!!'.
+! !
+
+!PackageNotification class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageNotification.st,v 1.3 2006/01/10 09:32:07 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageOpener.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,44 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#PackageOpener
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+!PackageOpener class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageOpener class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageOpener.st,v 1.2 2006/01/10 09:32:10 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackagePrerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,56 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Prerequisite subclass:#PackagePrerequisite
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Prerequisite'
+!
+
+!PackagePrerequisite class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackagePrerequisite methodsFor:'evaluation'!
+
+testCondition
+    ^ (PackageManager smalltalkPackageManager includesPackageNamed:name)
+! !
+
+!PackagePrerequisite methodsFor:'queries'!
+
+isPackagePrerequisite
+    ^ true
+! !
+
+!PackagePrerequisite class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackagePrerequisite.st,v 1.2 2006/01/10 09:32:00 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageProperties.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,453 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+PackageDetails subclass:#PackageProperties
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+AbstractPackageDetails subclass:#General
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageProperties
+!
+
+!PackageProperties class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageProperties class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageProperties andSelector:#windowSpec
+     Packages::PackageProperties new openInterface:#windowSpec
+     Packages::PackageProperties open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(#FullSpec
+        #name: #windowSpec
+        #window: 
+       #(#WindowSpec
+          #label: ''
+          #name: ''
+          #labelChannel: #labelHolder
+          #min: #(#Point 10 10)
+          #max: #(#Point 1024 768)
+          #bounds: #(#Rectangle 29 59 329 359)
+          #menu: #mainMenu
+        )
+        #component: 
+       #(#SpecCollection
+          #collection: #()
+        )
+      )
+! !
+
+!PackageProperties class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageProperties andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageProperties class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+        #list
+        #selectionHolder
+      ).
+
+! !
+
+!PackageProperties methodsFor:'accessing'!
+
+labelHolder
+    "assuming that there is only one package selected!!"
+    | selectedPackage packagesSelected |
+    packagesSelected := self packagesSelected.
+    selectedPackage :=  packagesSelected first.
+    ^ selectedPackage name asString, ' Properties'
+! !
+
+!PackageProperties::General class methodsFor:'accessing'!
+
+applicationName
+    ^ 'General'
+! !
+
+!PackageProperties::General class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageProperties::General andSelector:#windowSpec
+    "
+
+    <resource: #canvas>
+
+    ^ #(#FullSpec
+          #window: 
+           #(#WindowSpec
+              #name: 'Packages::PackageProperties::General'
+              #layout: #(#LayoutFrame 204 0 162 0 503 0 461 0)
+              #label: 'Packages::PackageProperties::General'
+              #min: #(#Point 10 10)
+              #max: #(#Point 1024 768)
+              #bounds: #(#Rectangle 204 162 504 462)
+              #menu: #mainMenu
+              #usePreferredExtent: false
+          )
+          #component: 
+           #(#SpecCollection
+              #collection: #()
+          )
+      )
+! !
+
+!PackageProperties::General class methodsFor:'menu specs'!
+
+mainMenu
+    "This resource specification was automatically generated by the CodeGeneratorTool."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageProperties::General andSelector:#mainMenu
+    "
+
+    <resource: #menu>
+
+    ^ #(#Menu
+           #(
+             #(#MenuItem
+                #label: 'File'
+                #translateLabel: true
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'New'
+                          #translateLabel: true
+                          #value: #menuNew
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Open...'
+                          #translateLabel: true
+                          #value: #menuOpen
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Save'
+                          #translateLabel: true
+                          #value: #menuSave
+                      )
+                       #(#MenuItem
+                          #label: 'Save As...'
+                          #translateLabel: true
+                          #value: #menuSaveAs
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'Exit'
+                          #translateLabel: true
+                          #value: #closeRequest
+                      )
+                    ) nil
+                    nil
+                )
+            )
+             #(#MenuItem
+                #label: 'Help'
+                #translateLabel: true
+                #startGroup: #right
+                #submenu: 
+                 #(#Menu
+                     #(
+                       #(#MenuItem
+                          #label: 'Documentation'
+                          #translateLabel: true
+                          #value: #openDocumentation
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'About this Application'
+                          #translateLabel: true
+                          #value: #openAboutThisApplication
+                      )
+                    ) nil
+                    nil
+                )
+            )
+          ) nil
+          nil
+      )
+! !
+
+!PackageProperties::General methodsFor:'initialization & release'!
+
+closeDownViews
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is really closed.
+     See also #closeDownViews, which is invoked before and may suppress the close
+     or ask the user for confirmation."
+
+    "/ change the code below as required ...
+    "/ This should cleanup any leftover resources
+    "/ (for example, temporary files)
+    "/ super closeRequest will initiate the closeDown
+
+    "/ add your code here
+
+    "/ do not remove the one below ...
+    ^ super closeDownViews
+!
+
+closeRequest
+    "This is a hook method generated by the Browser.
+     It will be invoked when your app/dialog-window is about to be
+     closed (this method has a chance to suppress the close).
+     See also #closeDownViews, which is invoked when the close is really done."
+
+    "/ change the code below as required ...
+    "/ Closing can be suppressed, by simply returning.
+    "/ The 'super closeRequest' at the end will initiate the real closeDown
+
+    ("self hasUnsavedChanges" true) ifTrue:[
+        (self confirm:(resources string:'Close without saving ?')) ifFalse:[
+            ^ self
+        ]
+    ].
+
+    ^ super closeRequest
+!
+
+postBuildWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked during the initialization of your app/dialog,
+     after all of the visual components have been built, 
+     but BEFORE the top window is made visible.
+     Add any app-specific actions here (reading files, setting up values etc.)
+     See also #postOpenWith:, which is invoked after opening."
+
+    "/ add any code here ...
+     self inspect.
+    ^ super postBuildWith:aBuilder
+!
+
+postOpenWith:aBuilder
+    "This is a hook method generated by the Browser.
+     It will be invoked right after the applications window has been opened.
+     Add any app-specific actions here (starting background processes etc.).
+     See also #postBuildWith:, which is invoked before opening."
+
+    "/ add any code here ...
+
+    ^ super postOpenWith:aBuilder
+! !
+
+!PackageProperties::General methodsFor:'menu actions'!
+
+menuNew
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'new' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''new'' available.'.
+!
+
+menuOpen
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'open' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''open'' available.'.
+!
+
+menuSave
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'save' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''save'' available.'.
+!
+
+menuSaveAs
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'saveAs' is selected."
+
+    "/ change below and add any actions as required here ...
+    self warn:'no action for ''saveAs'' available.'.
+!
+
+openAboutThisApplication
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-about' is selected."
+
+    "/ could open a customized aboutBox here ...
+    super openAboutThisApplication
+!
+
+openDocumentation
+    "This method was generated by the Browser.
+     It will be invoked when the menu-item 'help-documentation' is selected."
+
+    "/ change below as required ...
+
+    "/ to open an HTML viewer on some document (under 'doc/online/<language>/' ):
+    HTMLDocumentView openFullOnDocumentationFile:'TOP.html'.
+
+    "/ add application-specific help files under the 'doc/online/<language>/help/appName'
+    "/ directory, and open a viewer with:
+    "/ HTMLDocumentView openFullOnDocumentationFile:'help/<MyApplication>/TOP.html'.
+! !
+
+!PackageProperties class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageProperties.st,v 1.2 2006/01/10 09:31:58 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageSaver.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,44 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#PackageSaver
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+!PackageSaver class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageSaver class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSaver.st,v 1.2 2006/01/10 09:31:51 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageSelector.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,1816 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractPackageBrowser subclass:#PackageSelector
+	instanceVariableNames:'selectionChangedBlock list'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Application'
+!
+
+AbstractPackageBrowser subclass:#BasicPackageSelector
+	instanceVariableNames:'selectionChangedBlock list'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageSelector
+!
+
+AbstractPackageBrowser subclass:#HierarchicalPackageSelector
+	instanceVariableNames:'selectionChangedBlock tree packagesSelectedIndexHolder'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageSelector
+!
+
+HierarchicalItem subclass:#CategoryItem
+	instanceVariableNames:'name packageManager'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageSelector::HierarchicalPackageSelector
+!
+
+HierarchicalItem subclass:#PackageItem
+	instanceVariableNames:'package'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageSelector::HierarchicalPackageSelector
+!
+
+HierarchicalItem subclass:#RootItem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PackageSelector::HierarchicalPackageSelector
+!
+
+!PackageSelector class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageSelector class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageSelector andSelector:#windowSpec
+     Packages::PackageSelector new openInterface:#windowSpec
+     Packages::PackageSelector open
+    "
+
+    <resource: #canvas>
+
+    ^
+     #(#FullSpec
+	#name: #windowSpec
+	#window:
+       #(#WindowSpec
+	  #label: 'Packages::PackageSelectorApplication'
+	  #name: 'Packages::PackageSelectorApplication'
+	  #min: #(#Point 10 10)
+	  #max: #(#Point 1024 768)
+	  #bounds: #(#Rectangle 29 59 329 359)
+	  #menu: #mainMenu
+	)
+	#component:
+       #(#SpecCollection
+	  #collection: #(
+	   #(#SubCanvasSpec
+	      #name: 'SelectorSubCanvas'
+	      #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+	      #hasHorizontalScrollBar: false
+	      #hasVerticalScrollBar: false
+	      #clientHolder: #applicationHolder
+	    )
+	   )
+
+	)
+      )
+! !
+
+!PackageSelector class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+	#packagesSelectedHolder
+      ).
+
+! !
+
+!PackageSelector methodsFor:'aspects'!
+
+applicationHolder
+    "automatically generated by UIPainter ..."
+
+    |holder|
+    (holder := builder bindingAt:#applicationHolder) isNil ifTrue:[
+"/        builder aspectAt:#applicationHolder put:(holder :=  (BasicPackageSelector new) asValue).
+	builder aspectAt:#applicationHolder put:(holder :=  (HierarchicalPackageSelector new) asValue).
+    ].
+    ^ holder
+!
+
+declareDependents
+    self packageManager addDependent:self.
+!
+
+undeclareDependents
+    self packageManager removeDependent:self.
+! !
+
+!PackageSelector methodsFor:'change & update'!
+
+packagedManagerChangeAddPackage:aPackage
+    self applicationHolder value packagedManagerChangeAddPackage:aPackage.
+!
+
+packagedManagerChangeRemovePackage:aPackage
+    self applicationHolder value packagedManagerChangeRemovePackage:aPackage
+!
+
+update:something with:aParameter from:changedObject
+    something == #packagedChanged ifTrue:[
+	^ super update:something with:aParameter from:changedObject
+    ].
+
+    something == #addPackage: ifTrue:[
+	^ self packagedManagerChangeAddPackage:aParameter.
+    ].
+    something == #removePackage: ifTrue:[
+	^ self packagedManagerChangeRemovePackage:aParameter.
+    ].
+
+    super update:something with:aParameter from:changedObject
+! !
+
+!PackageSelector::BasicPackageSelector class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageSelector::BasicPackageSelector andSelector:#windowSpec
+     Packages::PackageSelector::BasicPackageSelector new openInterface:#windowSpec
+     Packages::PackageSelector::BasicPackageSelector open
+    "
+
+    <resource: #canvas>
+
+    ^
+     #(#FullSpec
+	#name: #windowSpec
+	#window:
+       #(#WindowSpec
+	  #label: 'Packages::PackageSelectorApplication'
+	  #name: 'Packages::PackageSelectorApplication'
+	  #min: #(#Point 10 10)
+	  #max: #(#Point 1024 768)
+	  #bounds: #(#Rectangle 29 59 329 359)
+	  #menu: #mainMenu
+	)
+	#component:
+       #(#SpecCollection
+	  #collection: #(
+	   #(#SelectionInListModelViewSpec
+	      #name: 'SelectionInListModelView'
+	      #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+	      #model: #packagesSelectedHolder
+	      #hasHorizontalScrollBar: true
+	      #hasVerticalScrollBar: true
+	      #listModel: #list
+	      #multipleSelectOk: true
+	      #useIndex: false
+	      #highlightMode: #line
+	      #selectOnButtomMenu: true
+	    )
+	   )
+
+	)
+      )
+! !
+
+!PackageSelector::BasicPackageSelector class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+	#packagesSelectedHolder
+      ).
+
+! !
+
+!PackageSelector::BasicPackageSelector methodsFor:'accessing'!
+
+masterApplication:aMasterApplication
+    "initialization"
+    | aPackageManager myList packageNames|
+    super masterApplication:aMasterApplication.
+
+    aPackageManager := self packageManager.
+    (myList := self list) removeAll.
+    packageNames := (aPackageManager packages collect:[:aPackage | aPackage name]).
+    myList addAll:packageNames.
+
+!
+
+selected
+    ^ self selectionHolder value
+!
+
+selectedPackage
+    ^ self packageManager packageNamed:self selection
+!
+
+selectionChangedBlock
+    "return the value of the instance variable 'selectionChangedBlock' (automatically generated)"
+
+    ^ selectionChangedBlock
+!
+
+selectionChangedBlock:something
+    "set the value of the instance variable 'selectionChangedBlock' (automatically generated)"
+
+    selectionChangedBlock := something.
+! !
+
+!PackageSelector::BasicPackageSelector methodsFor:'aspects'!
+
+list
+
+    list ifNil:[
+	list := List new.
+	list addDependent:self.
+    ].
+    ^ list.
+! !
+
+!PackageSelector::BasicPackageSelector methodsFor:'change & update'!
+
+listUpdate:something with:aParameter
+
+    | copy |
+    copy := list asOrderedCollection.
+
+    copy sort:[:x :y |
+	x < y
+    ].
+
+    list become:copy.
+!
+
+update:something with:aParameter from:changedObject
+
+    (changedObject == list) ifTrue:[
+	^ self listUpdate:something with:aParameter
+    ].
+
+
+    self breakPoint:''.
+! !
+
+!PackageSelector::BasicPackageSelector methodsFor:'initialization'!
+
+initialize
+    | aPackageManager myList packageNames firstOrNil|
+    masterApplication ifNil:[
+	^ super initialize
+    ].
+
+    aPackageManager := masterApplication model.
+    (myList := self list) removeAll.
+    packageNames := (aPackageManager packages collect:[:aPackage | aPackage name]).
+    myList addAll:packageNames.
+
+    self model:masterApplication model.
+
+    self list isEmpty ifFalse:[
+	firstOrNil := self list first
+    ].
+    self selectionHolder value:firstOrNil.
+    ^ super initialize
+!
+
+initializeWithMasterApplication:aMasterApplication
+    | myList packageNames aPackageManager|
+    aPackageManager := aMasterApplication model.
+    (myList := self list) removeAll.
+    packageNames := (aPackageManager packages collect:[:aPackage | aPackage name]).
+    myList addAll:packageNames.
+!
+
+postBuildWith:aBuilder
+    ^ super postBuildWith:aBuilder
+! !
+
+!PackageSelector::HierarchicalPackageSelector class methodsFor:'image specs'!
+
+basePackageIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageSystem inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageSystem
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageSystem'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$IBP$IBP$@BP$IBP$IBP$IBP$IBP$@A@@@BP$IBP$IBP$IBP$@A@HD@0@IBP$IBP$I@@$I@@H@@@DC@@$IBP@I@@ @@@PD@@@D@@$IBP@H@@ GA0@@
+@PLBA@@IBP@HB@ GA0\FA @@A@@IBP$I@@ GA0\FAPT@BP@IBP$I@@ GA0@@@@TEAP@IBP$I@@ GA0X@BP@EAPXF@@$IBP$@A0XF@@@@APXF@@$IBP$IBP@F
+APTEAPXF@@$IBP$IBP@FAPTEAPXFA0\@BP$IBP$I@@T@APXF@@\@BP$IBP$IBP$@BP@G@@$@BP$IBP$IBP$IBP$I@@$IBP$IBP$IBP@a') ; colorMapFromArray:#[0 0 0 255 128 0 255 168 88 192 192 0 255 255 0 160 160 160 195 195 195 220 220 220 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@A@@O@A>@''<W?#?>_?0?:G?0?_!!?<C? _?@?8A]@@ @b') ; yourself); yourself]
+!
+
+defaultPackageIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self defaultPackageIcon inspect
+     ImageEditor openOnClass:self andSelector:#defaultPackageIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class defaultPackageIcon'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPT@@@TEAP@EAPTEAPTEAP@@@0L@@@@C@@@EAPTE@@@C@0@@@PH@@@LC@@@E@@LC@@@A@PDB@ H@@@LC@@@@@@DA@PDA@ HB@ H@@@@E@@L@@@DA@PHB
+@ @@@@TEAP@C@0L@@@DB@@@B@ @EAPT@@0LC@0L@@@HB@ H@APTE@@LC@0LC@0HB@ HB@@TEAP@C@0LC@0LB@ HB@ @EAPT@@0LC@0LC@ HB@ H@APTE@@LC
+@0LC@0HB@ HB@@TEAP@B@0LC@0LB@ HB@@@EAPTE@@@B@0LC@ H@@@TEAPTEAPTE@@@B@0@@APTEAPTEAPTEAPTE@@@EAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 170 0 192 220 0 230 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?<_?1??G?<_?0?<@?@@0@b') ; yourself); yourself]
+!
+
+loadedPackageIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self loadedPackageIcon inspect
+     ImageEditor openOnClass:self andSelector:#loadedPackageIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class loadedPackageIcon'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAP@@@@@@@@@@APTEAPTE@@@@@@@@@@@@@@@EAPT@@@@@@@@@@0L@@@@@@@@E@@@@@@@C@0LC@0L@@@@@@@@@@@LC@0LC@0LC@0L@@@@E@@L@@@LC@0LC
+@0@@@@TEAP@C@0L@@@LC@@@B@ @EAPT@@0LC@0L@@@HB@ H@APTE@@LC@0LC@0HB@ HB@@TEAP@C@0LC@0LB@ HB@ @EAPT@@0LC@0LC@ HB@ H@APTE@@LC
+@0LC@0HB@ HB@@TEAP@B@0LC@0LB@ HB@@@EAPTE@@@B@0LC@ H@@@TEAPTEAPTE@@@B@0@@APTEAPTEAPTEAPTE@@@EAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@A @_ G?!!??G?<_?1??G?<_?1??G?<_?0?<@?@@0@b') ; yourself); yourself]
+!
+
+miniBasePackage
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniBasePackage inspect
+     ImageEditor openOnClass:self andSelector:#miniBasePackage
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniBasePackage'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPT@@@TEAP@EAPTEAPTEAP@@@0L@@@@C@@@EAPTE@@@C@0@@@PH@@@LC@@@E@@LC@@@A@PDB@ H@@@LC@@@@@@DA@PDA@ HB@ H@@@@E@@L@@@DA@PHB
+@ @@@@TEAP@C@0L@@@DB@@@B@ @EAPT@@0LC@0L@A@PDA@PDA@PE@@LC@0LC@0PDA@@@A@PDAP@C@0LC@0LDA@@DA@@DA@T@@0LC@0LCA@@@@@@@@@PE@@LC
+@0LC@0P@@0LB@ @DAP@B@0LC@0LD@@LC@ H@A@TE@@@B@0LCA@@C@0HB@@PEAPTE@@@B@0PD@@@@@@PDAPTEAPTE@@@DA@PDA@PDA@@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??7??_?=??7??_?<??0??@?<b') ; yourself); yourself]
+!
+
+miniPackageApplications
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageApplications inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageApplications
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageApplications'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B (JB (@@@(JB @JB (JB (JB @@B@ @@@@H@@@JB (J@@@HB@@C@0PCB@ H@@@J@@ H@@LC@0LDA@PCB@ H@@@@@0@@@@@@@@@@@@P@@@@J@@ @A0HB@ \A
+A0@H@@(JB @H@@\IBP$IBP\@@@@JB (@B@@GBP$IBP$G@@\@B (J@@ @A0$IBP$IA0@G@@@JB @H@@\GA0\GA0\@A0T@B (@B@@@@@@@@@@@@@\F@@(J@@ H
+B@ @A0\GA0\GA @JB @DB@ H@@@FA XFA X@B (J@@@DB@ H@@@@@@@@@@(JB (J@@@DB@@@B (JB (JB (JB (J@@@JB (JB (JB @a') ; colorMapFromArray:#[0 0 0 88 88 88 0 0 255 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?>_?9??''?>_?8?? ?@@0@b') ; yourself); yourself]
+!
+
+miniPackageEditors
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageEditors inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageEditors
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageEditors'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$@@@$I@@@IBP$IBP$IBP@@A0\@@@\G@@@IBP$I@@@GA0@@@PL@@@\G@@@I@@\G@@@A@PDC@0L@@@\G@@@@@@DA@PDA@0LC@0L@@@@I@@ @@@DA@PLC
+@0@@@@$IBP@HA0\@@@DC@@@C@0@IBP$@B@\GA0\@@@LC@0L@BP$I@@ GA0\GA0LC@0LC@@$IBP@HA0\G@@@@@@LC@0@IBP$@B@\@@@THB@T@@@L@@@$I@@@@
+AP HA XHB@T@@@H@@@THB@ FA  HAP@@A@H@@@@@AP HB@ E@@@D@ @@BP$IBP@@APT@@@ B@@@IBP$IBP$IBP@@BP@@@@$IBP$IBP@a') ; colorMapFromArray:#[0 0 0 128 128 0 255 168 88 192 192 0 255 220 168 195 195 195 192 192 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A&@_>G?>?????7?<_?1??G?<_?1??''???????C?0C\@b') ; yourself); yourself]
+!
+
+miniPackageFavourites
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageFavourites inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageFavourites
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageFavourites'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$@@@$IBP@IBP$IBP$IBP@@B@ @@@@H@@@IBP$I@@@HB@@@A@X@@@ H@@@I@@ H@@@DA@PFA X@@@ H@@@@@@PDA@PDA XFA X@@@@I@@ @@@PDA@XF
+A @@@@$IBP@HB@ @@@PF@@@FA @IBP$@B@ HB@ @@@XFA X@BP$I@@ HB@ HB@X@@@XF@@@IBP@HB@ HB@ @APHA@@LB@@$@B@ HB@ @AP\E@@HC@0@I@@ H
+B@ H@@TGAPHC@0H@BP@FB@ HB@ @APLE@0L@BP$I@@@FB@ HA @E@0H@BP$IBP$I@@@FB@@@@@L@BP$IBP$IBP$I@@@IBP$@BP$IBP@a') ; colorMapFromArray:#[0 0 0 128 0 0 192 0 0 255 0 0 128 128 0 255 128 0 192 192 0 255 192 192 255 255 192 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?>_?=??7??_?8??@?8@1@b') ; yourself); yourself]
+!
+
+miniPackageGames
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageGames inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageGames
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageGames'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B (JB (@@@(JB @JB (JB (JB @@B@ @@@@H@@@JB (J@@@HB@@@@0P@B@ H@@@J@@ H@@@C@0LDA@@@B@ @B @@@@LC@0LCA@PDA@@@@@@J@@ @@@LC@0PD
+@@H@@@(JB @HB@ @@@LD@@@G@@PJB (@B@ HB@ @@@@@A0@DB (J@@ HB@ HB@PD@@\@A@(JB @HB@ HB@ D@@@G@@PJB (@B@ HB@ @@PD@A0@@B (J@@ H
+B@ H@@\IA @FA @@B @DB@ HB@@GA0\IA \E@@(J@@@DB@ H@@XGA0TEAP@JB (J@@@DB@@@@@XE@@@JB (JB (J@@@JB (@@@(JB @a') ; colorMapFromArray:#[0 0 0 192 0 0 255 0 0 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>??;??7?<_?1??G?<_?1??G??_?<??0?>@1 b') ; yourself); yourself]
+!
+
+miniPackageGraphics
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageGraphics inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageGraphics
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageGraphics'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+G1<_G1<@@A<_G0@_G1<_G1<_G0@@GQ4@@@@]@@@_G1<_@@@]GP@@DQP@GQ4]@@@_@A4]@@@QDQDTE@@@GQ4]@@@@@ADQDQDQEAPTE@@@@@@_@A4@@ADQDQPT
+E@@]@A<_G0@]GQ4@@ADT@@@TE@@_G1<@GQ4]GQ4@@@@@@@@@@@@_@A4]GQ4]@A AE!!XAFA @@@@@@@@@@@@JA@HGC!!DM@@@SD1LSD1L@B0TBB@<TD @@D!!HR
+D!!HR@@0F@0$PEQL@@@@@@@@@@@@[F!!$^GA4W@A<_@@@TGQ4@@@@@@@@@@@@_G1<_@@@TGP@@G1<_G1<_G1<_G1<_@@@_G1<_G1<_G0@a') ; colorMapFromArray:#[0 0 0 88 88 88 0 0 128 0 0 255 0 128 0 0 192 0 0 128 0 0 128 128 0 192 192 0 255 255 128 0 0 192 0 0 255 0 0 192 88 0 128 0 128 192 0 192 255 0 255 128 128 0 255 128 0 255 168 88 192 192 0 255 255 0 128 128 128 255 220 168 195 195 195 192 192 255 192 255 192 255 192 192 255 192 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??7????????????<??0?@@0@b') ; yourself); yourself]
+!
+
+miniPackageMultimedia
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageMultimedia inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageMultimedia
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageMultimedia'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$@@@$IBP@IBP$IBP$IBP@@A0\@@@@G@@@IBP$I@@@GA0@@@PH@@@\G@@@I@@\G@@@A@PDB@ H@@@\G@@@@@@DA@PDA@ HB@ @@@@@I@@\@@@DA@PHB
+@@@B@@$IBP@GA0\@@@D@@@HB@ @IBP$@A0\GA0\@@ H@@@@@BP$I@@\GA0\GA0H@A@PD@@$IBP@GA0\GA0\@A PDA@ @BP$@A0\GA0\@A@PC@@LDA@@I@@\G
+A0\G@@PD@@\@A@P@BP@BA0\GA0@DA@L@APPD@@$I@@@BA0\G@@ DA@PE@@$IBP$I@@@BA0@@A@PD@@$IBP$IBP$I@@@IBP@@@@$IBP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 160 160 160 195 195 195 192 192 255 192 255 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?<_?9??7??_?<?? ?<@3 b') ; yourself); yourself]
+!
+
+miniPackageNetwork
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageNetwork inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageNetwork
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageNetwork'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B (JB (@@@(JB @JB (JB (JB @@B@ @@@@H@@@JB (J@@@HB@@@@0P@@@ H@@@J@@ H@@@C@0LDA@P@@@ H@@@@@@LC@0LCA@PDA@P@@@@J@@ @@@LC@@@@
+@@PD@@(JB @HB@ @@@$IBP$@A@@JB (@B@ HB@@GA XG@@@@@@(J@@ HB@ @A0HB@@$IBP$@B @HB@ H@@$IBP@G@ HE@@(@B@ HB@ EAPT@A0DAAP@J@@ H
+B@ @A0\G@@$IBP@JB @DB@ H@@@@@@T@@@@E@@(J@@@DB@ HA@P@APTEAP@JB (J@@@DB@@@@@\GA0@JB (JB (J@@@JB (@@@@JB @a') ; colorMapFromArray:#[0 0 0 0 0 128 0 0 255 128 128 0 192 192 0 128 128 128 128 128 255 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??''??_?=??7?>_?<??0?>@10b') ; yourself); yourself]
+!
+
+miniPackageSettings
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageSettings inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageSettings
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageSettings'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B@ HB@ @@@ HB@@HB@ HB@ HB@@@A X@@@@F@@@HB@ H@@@FA @@@PH@@@XF@@@H@@XF@@@A@PDB@ H@@@XF@@@@@@DA@PDA@ HB@ H@@@@H@@X@@@DA@PHB
+@ @@@@ HB@@FA X@@@DB@@@@@ @HB@ @A XFA X@@@@@@@H@B@ H@@XFA XF@@P@A0T@A0@HB@@FA XFA X@APTEAP@HB@ @A XFA X@A0TC@@TE@@ H@@XF
+A XF@@TE@@HGAP@HB@@BA XFA X@APTGAP@HB@ H@@@BA X@A0@EAP@E@@ HB@ H@@@BA @@@@@H@@ HB@ HB@ H@@@HB@ HB@ HB@@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?>_?1??''?>_?0?? ?4@0@b') ; yourself); yourself]
+!
+
+miniPackageSystem
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageSystem inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageSystem
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageSystem'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$IBP$IBP$@BP$IBP$IBP$IBP$IBP$@A@@@BP$IBP$IBP$IBP$@A@HD@0@IBP$IBP$I@@$I@@H@@@DC@@$IBP@I@@ @@@PD@@@D@@$IBP@H@@ GA0@@
+@PLBA@@IBP@HB@ GA0\FA @@A@@IBP$I@@ GA0\FAPT@BP@IBP$I@@ GA0@@@@TEAP@IBP$I@@ GA0X@BP@EAPXF@@$IBP$@A0XF@@@@APXF@@$IBP$IBP@F
+APTEAPXF@@$IBP$IBP@FAPTEAPXFA0\@BP$IBP$I@@T@APXF@@\@BP$IBP$IBP$@BP@G@@$@BP$IBP$IBP$IBP$I@@$IBP$IBP$IBP@a') ; colorMapFromArray:#[0 0 0 255 128 0 255 168 88 192 192 0 255 255 0 160 160 160 195 195 195 220 220 220 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@A@@O@A>@''<W?#?>_?0?:G?0?_!!?<C? _?@?8A]@@ @b') ; yourself); yourself]
+!
+
+miniPackageUtilities
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self miniPackageUtilities inspect
+     ImageEditor openOnClass:self andSelector:#miniPackageUtilities
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class miniPackageUtilities'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+BP$IBP$@@@$IBP@IBP$IBP$IBP@@A0\@@@@G@@@IBP$I@@@GA0@@@0T@@@\G@@@I@@\G@@@C@0LEAPT@@@\G@@@@@@LC@0LCAPTEAPT@@@@I@@\@@@LC@0L@
+@@@@@@$IBP@GA0\@@@L@@@@@AP@IBP$@A0\GA0\@A X@AP@B@@$I@@\GA0\@A XA@@TB@@H@BP@GA0\@A XAA@@@@ HB@@$@A0\GA0@A@@@D@@H@@@$I@@\G
+A0\G@@T@@@P@@@$IBP@EA0\GA0\@@ H@A@@IBP$I@@@EA0\@@ H@@@@D@@$IBP$I@@@E@@H@BP$I@@P@BP$IBP$I@@@@BP$IBP$@BP@a') ; colorMapFromArray:#[0 0 0 88 88 88 0 192 192 128 128 0 255 168 88 192 192 0 160 160 160 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??''??_?=??''?<_?0?? ?G@8Hb') ; yourself); yourself]
+!
+
+noramlPackage
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self noramlPackage inspect
+     ImageEditor openOnClass:self andSelector:#noramlPackage
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class noramlPackage'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPTEAPTEAPTE@@@EAPTEAP@EAPTEAPTEAPTEAPTEAPTEAPTEAPTE@@@DA@@EAPT@A@@@APTEAPTEAPTEAPTEAPTEAPTE@@@DA@LCA@@E@@PCA@P@@@TE
+APTEAPTEAPTEAPTE@@@DA@LC@0LC@@@D@0LC@0PD@@@EAPTEAPTEAPTE@@@DA@LC@0LC@@@A@ @@@0LC@0LDA@@@APTEAPTE@@@DA@LC@0LC@@@A@PDA@ D@
+@@LC@0LCA@P@@@TE@@@DA@LC@0LC@@@A@PDA@PHA@ DB@@@C@0LC@0PD@@@E@@PC@0LC@@@A@PDA@PDA@PHA@ DB@P@@@0LC@0L@APTE@@PC@@@A@PDA@PDA
+@PDB@PHA@ DB@PH@@@LC@@TE@@@@@@@A@PDA@PDA@PDA@PDB@PHA@ DB@PHA@@@@@@@E@@@C@0@@@PDA@PDA@PDA@ DB@PHA@ DB@@@C@0@@APTEAP@@@0L@
+@@DA@PDA@PDA@ DB@PHA@@@C@0@@APTEAPTE@@P@@@LC@@@A@PDA@PHA@ DB@@@C@0@@@ @EAPTEAPT@A@LC@@@C@0@@@PDA@PHA@@@C@0@@@ HB@@TEAPTE
+AP@D@0LC@0@@@0L@@@DB@@@C@0@@@ HB@ H@APTEAPTE@@PC@0LC@0L@@@LC@@@C@0@@@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@@@C@ @@@ HB@ HB@ HB
+@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC@ HB@ HB
+@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC
+@ HB@ HB@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@HC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@P@EAPTEAPT@@@HB@0LC
+@0LC@0LC@ HB@ HB@ HB@PD@@@TEAPTEAPTE@@@B@ LC@0LC@0LB@ HB@ HB@PD@@@TEAPTEAPTEAPTEAP@@@ HC@0LC@0HB@ HB@PD@@@TEAPTEAPTEAPTE
+APTEAPT@@@HB@0LC@ HB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTE@@@B@ LB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTEAPTEAP@@@ D@@@TEAPTEAPTEAPTE
+APTEAPTEAPTEAPTEAPTEAPT@@@TEAPTEAPTEAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G???>A???? _???8G???>A??
+?? _???8G???>A???? G??? @_?? @A?? @@G? @@@_ @@@A @@b') ; yourself); yourself]
+!
+
+normalApplications
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalApplications inspect
+     ImageEditor openOnClass:self andSelector:#normalApplications
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalApplications'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B (JB (JB (JB (J@@@JB (JB @JB (JB (JB (JB (JB (JB (JB (J@@@IBP@JB (@BP@@B (JB (JB (JB (JB (JB (J@@@IBP HBP@J@@$HBP$@@@(J
+B (JB (JB (JB (J@@@IBP HB@ H@@@IB@ HB@$I@@@JB (JB (JB (J@@@IBP HB@ H@@@CA@@@B@ HB@ IBP@@B (JB (J@@@IBP HB@ H@@@C@0LCA@L@
+@@ HB@ HBP$@@@(J@@@IBP HB@ H@@@C@0LC@0PCA@LD@@@HB@ HB@$I@@@J@@$HB@ H@@@C@0LC@0LC@0PCA@LD@0@@B@ HB@ @B (J@@$H@@@C@0LC@0LC
+@0LD@0PCA@LD@0P@@@ H@@(J@@@@@@@C@0L@@@@@@@@@@@@@@@@@@@@D@0PC@@@@@@@J@@@HB@@@@0@GA0HB@ HB@ \G@P\G@@LD@@@HB@@@B (JB @@B@ @
+@@\G@ HB@ HBA0\AA0\@@@@HB@@@B (JB (J@@$@@@ @@PDA@PDA@PDA@PDA@P@HB@@@A@@JB (JB (@BP H@@@GBP$IBP$IBP$IBP$G@@@@@@@D@@(JB (J
+B @IB@ H@@\IBP$IBP$IBP$IBP\@AP\G@@P@B (JB (J@@$HB@ @A0$IBP$IBP$IBP$IA0@EA0\@A@@JB (JB (@BP HB@@GBP$IBP$IBP$IBP$G@@TEAP@D
+@@(JB (JB @IB@ H@@\IBP$IBP$IBP$IBP\@A $G@@@@@@@JB (J@@$HB@ @A0$IBP$IBP$IBP$IA0@FBP\@AP\G@@(JB (@BP HB@@GA0\GA0\GA0\GA0\G
+@@XIA0@EA0\@B (JB @IB@ H@@@@@@@@@@@@@@@@@@@@A $G@@TEAP@JB (J@@$HB@ HB@ H@@XFA XFA XFA XFBP\@A $G@@(JB (@BP HB@ HB@ @A0$I
+BP$IBP$IBP$IA0@FBP\@B (JB @IB@ HB@ HB@@GA0\GA0\GA0\GA0\G@@XIA0@JB (J@@PHB@ HB@ H@@@@@@@@@@@@@@@@@@@@A $G@@(JB (@@@PDB@ H
+B@ HB@ H@@XFA XFA XFA XFBP\@B (JB (J@@@DA@ HB@ HB@ @A0$IBP$IBP$IBP$IA0@JB (JB (JB @@A@PHB@ HB@@GA0\GA0\GA0\GA0\G@@(JB (J
+B (JB (@@@PDB@ H@@@@@@@@@@@@@@@@@@@@B (JB (JB (JB (J@@@DA@ D@0L@@@(JB (JB (JB (JB (JB (JB (JB (JB @@A@L@@@(JB (JB (JB (J
+B (JB (JB (JB (JB (JB (@@@(JB (JB (JB (JB (JB @a') ; colorMapFromArray:#[0 0 0 88 88 88 0 0 255 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???>G????!!????8_???>G????!!??
+??8_???>G????!!????8G???>@_??? A???8@G? @@@_ @@@A @@b') ; yourself); yourself]
+!
+
+normalEditors
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalEditors inspect
+     ImageEditor openOnClass:self andSelector:#normalEditors
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalEditors'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B0,KB0,KB0,KB0,K@@@KB0,KB0@KB0,KB0,KB0,KB0,KB0,KB0,KB0,K@@@JB @KB0,@B @@B0,KB0,KB0,KB0,KB0,KB0,K@@@JB $IB @K@@(IB (@@@,K
+B0,KB0,KB0,KB0,K@@@JB $IBP$I@@@JBP$IBP(J@@@KB0,KB0,KB0,K@@@JB $IBP$I@@@AA@@@BP$IBP$JB @@B0,KB0,K@@@JB $IBP$I@@@A@PDAA@D@
+@@$IBP$IB (@@@,K@@@JB $IBP$I@@@A@PDA@PPAA@DD@@@IBP$IBP(J@@@K@@(IBP$I@@@A@PDA@PDA@PPAA@DD@P@@BP$IBP$@B0,K@@(I@@@A@PDA@PDA
+@PDD@PPAA@DD@PP@@@$I@@,K@@@@@@@A@PDA@PDA@PDA@PDD@PPAA@DD@PPA@@@@@@@K@@@IBP@@@PDA@PDA@PDAA@DD@PPAA@DD@@@IBP@@B0,KB0@@BP$@
+@@DA@PDA@PDAA@DD@PPA@@@IBP@@B0,KB0,K@@(@@@$I@@@A@PDA@PPAA@DD@@@IBP@@A@@KB0,KB0,@B $I@@@IBP@@@PDA@PPA@@@IBP@@A@PD@@,KB0,K
+B0@JBP$IBP@@BP$@@@DD@@@IBP@@A@PDA@P@B0,KB0,K@@(IBP$IBP$@@@$I@@@IBP@@A@PDA@PDA@@KB0,KB0,@B $IBP$IBP$I@@@IA@@@A@PDA@PDA@PD
+@@,KB0,KB0@JBP$IBP$IBP$IBP$DA@PDA@PDA@PDA@P@B0,KB0,K@@(IBP$IBP$IBP$I@@@DA@PDA@PDA@PDA@@KB0,KB0,@B $IBP$IBP$I@@@FB @@A@PD
+A@PDA@PD@@,KB0,KB0@JBP$IBP$I@@@FB (JB X@@@PDA@PDA@P@B0,KB0,K@@(IBP$I@@@FB (JA0\JB (F@@@DA@PDA@@@@@,KB0,@B $I@@@FB (JA0(J
+B \GB (JA @@A@P@@@TE@@,KB0@J@@@FB (JB (GA0\JB \GB (JB X@@@TE@0L@B0,K@@@FB (JA0\GB (JB \JB (JB X@@@TEAPLC@ @K@@@FB (JB (J
+B \GA0(JB (JB X@@@TEAPLC@ @@B0@FB (JB (JB (JB (JA0(JB X@@@TEAPLC@ @@B0,KB0@@A (JB (JB (JB (JB X@@@TEAPLC@ @@B0,KB0,KB0,@
+@@XJB (JB (JB X@@@TEAPLC@ @@B0,KB0,KB0,KB0,K@@@FB (JB X@@@@HB@LC@ @@B0,KB0,KB0,KB0,KB0,KB0@@B X@@@,K@@(J@ @@B0,KB0,KB0,K
+B0,KB0,KB0,KB0,@@@,KB0,@@@@@B0,KB0,KB0,KB0,KB0@a') ; colorMapFromArray:#[0 0 0 128 128 0 255 128 0 255 168 88 192 192 0 255 220 168 195 195 195 192 192 255 192 255 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G???>A???? _???8G????!!??
+??<_????G????7????;????8_???8A???8@G??8@@_''8@@A!!8@@b') ; yourself); yourself]
+!
+
+normalInspectPackage
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalInspectPackage inspect
+     ImageEditor openOnClass:self andSelector:#normalInspectPackage
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalInspectPackage'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPTEAPTEAPTE@@@EAPTEAP@EAPTEAPTEAPTEAPTEAPTEAPTEAPTE@@@DA@@EAPT@A@@@APTEAPTEAPTEAPTEAPTEAPTE@@@DA@LCA@@E@@PCA@P@@@TE
+APTEAPTEAPTEAPTE@@@DA@LC@0LC@@@D@0LC@0PD@@@EAPTEAPTEAPTE@@@DA@LC@0LC@@@A@ @@@0LC@0LDA@@@APTEAPTE@@@DA@LC@0LC@@@A@PDA@ D@
+@@LC@0LCA@P@@@TE@@@DA@LC@0LC@@@A@PDA@PHA@ DB@@@C@0LC@0PD@@@E@@PC@0LC@@@A@PDA@PDA@PHA@ DB@P@@@0LC@0L@APTE@@PC@@@A@PDA@PDA
+@PDB@PHA@ DB@PH@@@LC@@TE@@@@@@@A@PDA@PDA@PDA@PDB@PHA@ DB@PHA@@@@@@@E@@@C@0@@@PDA@PDA@PDA@ DB@PHA@ DB@@@C@0@@APTEAP@@@0L@
+@@DA@PDA@PDA@ DB@PHA@@@C@0@@APTEAPTE@@P@@@LC@@@A@PDA@PHA@ DB@@@C@0@@@ @EAPTEAPT@A@LC@@@C@0@@@PDA@PHA@@@C@0@@@ HB@@TEAPTE
+AP@D@0LC@0@@@0L@@@DB@@@C@0@@@ HB@ H@APTEAPTE@@PC@0LC@0L@@@LC@@@C@0@@@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@@@C@ @@@ HB@ HB@ HB
+@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC@ HB@ HB
+@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC
+@ HB@ HB@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@HC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@P@EAPTEAPT@@@HB@0LC
+@0LC@0LC@ HB@ HB@ HB@PD@@@TEAPTEAPTE@@@B@ LC@0LC@0LB@ HB@ HB@PD@@@TEAPTEAPTEAPTEAP@@@ HC@0LC@0HB@ HB@PD@@@TEAPTEAPTEAPTE
+APTEAPT@@@HB@0LC@ HB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTE@@@B@ LB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTEAPTEAP@@@ D@@@TEAPTEAPTEAPTE
+APTEAPTEAPTEAPTEAPTEAPT@@@TEAPTEAPTEAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G???>A???? _???8G???>A??
+?? _???8G???>A???? G??? @_?? @A?? @@G? @@@_ @@@A @@b') ; yourself); yourself]
+!
+
+normalPackage
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackage inspect
+     ImageEditor openOnClass:self andSelector:#normalPackage
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackage'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPTEAPTEAPTE@@@EAPTEAP@EAPTEAPTEAPTEAPTEAPTEAPTEAPTE@@@DA@@EAPT@A@@@APTEAPTEAPTEAPTEAPTEAPTE@@@DA@LCA@@E@@PCA@P@@@TE
+APTEAPTEAPTEAPTE@@@DA@LC@0LC@@@D@0LC@0PD@@@EAPTEAPTEAPTE@@@DA@LC@0LC@@@A@ @@@0LC@0LDA@@@APTEAPTE@@@DA@LC@0LC@@@A@PDA@ D@
+@@LC@0LCA@P@@@TE@@@DA@LC@0LC@@@A@PDA@PHA@ DB@@@C@0LC@0PD@@@E@@PC@0LC@@@A@PDA@PDA@PHA@ DB@P@@@0LC@0L@APTE@@PC@@@A@PDA@PDA
+@PDB@PHA@ DB@PH@@@LC@@TE@@@@@@@A@PDA@PDA@PDA@PDB@PHA@ DB@PHA@@@@@@@E@@@C@0@@@PDA@PDA@PDA@ DB@PHA@ DB@@@C@0@@APTEAP@@@0L@
+@@DA@PDA@PDA@ DB@PHA@@@C@0@@APTEAPTE@@P@@@LC@@@A@PDA@PHA@ DB@@@C@0@@@ @EAPTEAPT@A@LC@@@C@0@@@PDA@PHA@@@C@0@@@ HB@@TEAPTE
+AP@D@0LC@0@@@0L@@@DB@@@C@0@@@ HB@ H@APTEAPTE@@PC@0LC@0L@@@LC@@@C@0@@@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@@@C@ @@@ HB@ HB@ HB
+@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC@ HB@ HB
+@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@PC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@ @EAPTEAPT@A@LC@0LC@0LC@0LC
+@ HB@ HB@ HB@ HB@@TEAPTEAP@D@0LC@0LC@0LC@0LB@ HB@ HB@ HB@ H@APTEAPTE@@HC@0LC@0LC@0LC@0HB@ HB@ HB@ HB@P@EAPTEAPT@@@HB@0LC
+@0LC@0LC@ HB@ HB@ HB@PD@@@TEAPTEAPTE@@@B@ LC@0LC@0LB@ HB@ HB@PD@@@TEAPTEAPTEAPTEAP@@@ HC@0LC@0HB@ HB@PD@@@TEAPTEAPTEAPTE
+APTEAPT@@@HB@0LC@ HB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTE@@@B@ LB@PD@@@TEAPTEAPTEAPTEAPTEAPTEAPTEAPTEAP@@@ D@@@TEAPTEAPTEAPTE
+APTEAPTEAPTEAPTEAPTEAPT@@@TEAPTEAPTEAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G???>A???? _???8G???>A??
+?? _???8G???>A???? G??? @_?? @A?? @@G? @@@_ @@@A @@b') ; yourself); yourself]
+!
+
+normalPackageFavourite
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageFavourite inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageFavourite
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageFavourite'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B (JB (JB (JB (J@@@JB (JB @JB (JB (JB (JB (JB (JB (JB (J@@@IBP@JB (@BP@@B (JB (JB (JB (JB (JB (J@@@IBP HBP@J@@$HBP$@@@(J
+B (JB (JB (JB (J@@@IBP HB@ H@@@IB@ HB@$I@@@JB (JB (JB (J@@@IBP HB@ H@@@DA @@B@ HB@ IBP@@B (JB (J@@@IBP HB@ H@@@DA@PDA P@
+@@ HB@ HBP$@@@(J@@@IBP HB@ H@@@DA@PDA@XDA PF@@@HB@ HB@$I@@@J@@$HB@ H@@@DA@PDA@PDA@XDA PFA@@@B@ HB@ @B (J@@$H@@@DA@PDA@PD
+A@PFA@XDA PFA@X@@@ H@@(J@@@@@@@DA@PDA@PDA@PDA@PFA@XDA PFA@XD@@@@@@@J@@@HB@@@A@PDA@PDA@PDA PFA@XDA PF@@@HB@@@B (JB @@B@ @
+@@PDA@PDA@PDA PFA@XD@@@HB@@@B (JB (J@@$@@@ H@@@DA@PDA@XDA PF@@@HB@@@A @JB (JB (@BP H@@@HB@@@A@PDA@XD@@@HB@@@A XF@@(JB (J
+B @IB@ HB@@@B@ @@@PF@@@HB@@@A XFA X@B (JB (J@@$HB@ HB@ @@@ H@@@HB@@@A XFA XFA @JB (JB (@BP HB@ HB@ H@@@HA @@A XFA XFA XF
+@@(JB (JB @IB@ HB@ HB@ HB@ FA XFA XFA XFA X@B (JB (J@@$HB@ HB@ HB@ HB@XFA @@@@@FA X@@@@@B (JB (@BP HB@ HB@ HB@ HA X@@0TC
+AP@F@@LB@0H@B (JB @IB@ HB@ HB@ HB@ F@@TEA0TE@0H@@0HC@ H@B (J@@$HB@ HB@ HB@ HB@X@AP\EA0TE@@LC@0HC@ @JB (@BP HB@ HB@ HB@ H
+A @EA0\EAPLA@0LC@0HB@@(JB @IB@ HB@ HB@ HB@ F@@TGAPTC@0HC@0LB@0H@B (J@@XHB@ HB@ HB@ HB@XF@@LGAPTC@0LC@0LB@@(JB (@@@XFB@ H
+B@ HB@ HA X@APTE@0TC@0LB@0H@B (JB (J@@@FA  HB@ HB@ FA X@@0LE@0LC@ LB@@(JB (JB (JB @@A XHB@ HB@XFA X@APLE@0HC@ @JB (JB (J
+B (JB (@@@XFB@ HA XFA@P@@0LC@0H@B (JB (JB (JB (JB (J@@@FA  FA@P@@@(@@0LB@@(JB (JB (JB (JB (JB (JB @@A P@@@(JB (@@0@JB (J
+B (JB (JB (JB (JB (JB (@@@(JB (JB (@B (JB (JB @a') ; colorMapFromArray:#[0 0 0 128 0 0 192 0 0 255 0 0 128 128 0 255 128 0 192 192 0 255 192 192 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G????A????8_????G????1??
+??<_????G????!!????8G???<@_??>@A???@@G?/ @@_!!0@@A H@b') ; yourself); yourself]
+!
+
+normalPackageGames
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageGames inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageGames
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageGames'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B0,KB0,KB0,KB0,K@@@KB0,KB0@KB0,KB0,KB0,KB0,KB0,KB0,KB0,K@@@JB @KB0,@B @@B0,KB0,KB0,KB0,KB0,KB0,K@@@JB $IB @K@@(IB (@@@,K
+B0,KB0,KB0,KB0,K@@@JB $IBP$I@@@JBP$IBP(J@@@KB0,KB0,KB0,K@@@JB $IBP$I@@@DAP@@BP$IBP$JB @@B0,KB0,K@@@JB $IBP$I@@@DA@PDAPP@
+@@$IBP$IB (@@@,K@@@JB $IBP$I@@@DA@PDA@TDAPPE@@@IBP$IBP(J@@@K@@(IBP$I@@@DA@PDA@PDA@TDAPPEA@@@BP$IBP$@B0,K@@(I@@@DA@PDA@PD
+A@PEA@TDAPPEA@T@@@$I@@,K@@@@@@@DA@PDA@PDA@PDA@PEA@TDAPPEA@TD@@@@@@@K@@@IBP@@A@PDA@PDA@PDAPPEA@TD@@@@A@@IBP@@B0,KB0@@BP$@
+@@PDA@PDA@PDAPPEA@@C@0L@BP@@B0,KB0,K@@(@@@$I@@@DA@PDA@TDAPPE@@@@@@@@AP@KB0,KB0,@B $I@@@IBP@@A@PDA@TD@@@@B  F@@TE@@,KB0,K
+B0@JBP$IBP@@BP$@@@PE@@@IBP@JB@X@APT@B0,KB0,K@@(IBP$IBP$@@@$I@@@IBP@@@@(HA @EAP@KB0,KB0,@B $IBP$IBP$I@@@IAP@@APT@B  F@@TE
+@@,KB0,KB0@JBP$IBP$IBP$IBP$EAPTEAP@JB@X@APT@B0,KB0,K@@(IBP$IBP$IBP$IBPTEAPT@@@(HA @EAP@KB0,KB0,@B $IBP$IBP$IBP$IAPT@@@\@
+B  F@@TE@@,KB0,KB0@JBP$IBP$IBP$IBP$@@@HBA0@JB@X@@@T@B0,KB0,K@@(IBP$IBP$IBP$I@@DB@0HG@@(HA @@@@@KB0,KB0,@B $IBP$IBP$IBP@H
+B (A@P\@B  F@@\G@@@KB0,KB0@JBP$IBP$IBP$I@@ HB@(JA0\@@@@GA0\GA0@KB0,K@@TIBP$IBP$IBP$@B@ HB@ JB \GA0\GA0 HA @KB0,@@@TEBP$I
+BP$IBP@GB@ HB@ HB (GA0 HA XF@@,KB0,K@@@EAP$IBP$IBP@GA0 HB@ HB@(HA XFA X@B0,KB0,KB0@@APTIBP$IBP@@A0\HB@ HB@XFA XFA @KB0,K
+B0,KB0,@@@TEBP$IAPT@@@\GB@ HA XFA X@B0,KB0,KB0,KB0,K@@@EAP$EA@P@@@@GA0 FA X@@@,KB0,KB0,KB0,KB0,KB0@@APP@@@,KB0@@A0X@@@,K
+B0,KB0,KB0,KB0,KB0,KB0,@@@,KB0,KB0,@@@,KB0,KB0@a') ; colorMapFromArray:#[0 0 0 128 0 0 192 0 0 255 0 0 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???8G???>A???? _???8G???>A??
+??0_???>G????1????<G????@_???0A???8@G??<@@_#<@@A L@b') ; yourself); yourself]
+!
+
+normalPackageGraphics
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageGraphics inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageGraphics
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageGraphics'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+HB@ HB@ HB@ HB@ @@@ HB@ H@@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ @@@_G0@ HB@@G0@@HB@ HB@ HB@ HB@ HB@ HB@ @@@_G18^G0@ @A<^G1<@@B@
+HB@ HB@ HB@ HB@ @@@_G18^G!!8^@@@_G!!8^G!!<_@@@ HB@ HB@ HB@ @@@_G18^G!!8^@@@QE@@@G!!8^G!!8_G0@@HB@ HB@ @@@_G18^G!!8^@@@QDQDQEAD@
+@A8^G!!8^G1<@@B@ @@@_G18^G!!8^@@@QDQDQDQPQEADT@@@^G!!8^G!!<_@@@ @A<^G!!8^@@@QDQDQDQDQDQPQEADTDP@@G!!8^G!!8@HB@ @A<^@@@QDQDQDQDQ
+DQDTDQPQEADTDQP@@A8^@B@ @@@@@@@QDQDQDQDQDQDQDQDTDQPQEADTDQPQ@@@@@@@ @@@^G @@DQDQDQDQDQDQEADTDQPQEADT@@@^G @@HB@ H@@@G!!8@
+@ADQDQDQDQDQEADTDQPQ@@@^G @@HB@ HB@ @A<@@A8^@@@QDQDQDQPQEADT@@@^G @@E@@ HB@ HB@@G18^@@@^G @@DQDQDQPQ@@@^G @@EAPT@B@ HB@
+H@@_G!!8^G @@G!!8@@ADT@@@^G @@EAPTEAP@HB@ HB@ @A<^G!!8^G!!8@@A8^@@@@@@@@@@@@@@@@@@@@@@@ HB@@G18^G!!8^G!!8^@@@^@A$Y@QXVE!!XV@Q$Y
+@Q$Y@B@ H@@_G!!8^G!!8^G!!8^G!!8@FQ$AE!!XVE!!XAFQ$AFQ$@HB@ @A<^G!!8^G!!8^G!!8^G @@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@^@@(JA@PB
+@ \GC 8QDP4M@@@XFA XFA XFA XFA XF@@@B (DA@HBA0\NC!!DQCP4@@ALSD1LSD1LSD1LSD1L^G @KB0TE@0LHB@<OEAPRD @@CP4MCP4MCP4MCP4MCQ8^
+FP@KAPTC@0 HC0<TEAHR@@@RD!!HRD!!HRD!!HRD!!HRG!!8@C@0FA!!\WBP$PDATUD1L@@@4MCP4MCP4MCP4MCP4M@@@LC@XFE1\IBQ@PEQTSD0@ @@@@@@@@@@@@
+@@@@@@@^@A0\F1,ZF!!<_GQ4^G!! X@B@ HB@ @@@TEA8^G!!8^G!!8@GA0[F1(ZG1<]GQ8^FA @HB@ HB@ H@@@EAP^G!!8^G @@@@@@@@@@@@@@@@@@@@@ HB@
+HB@ HB@@@APTG!!8^EAPTDQD@@B@ HB@ HB@ HB@ HB@ HB@ HB@ @@@TEA8TDQD@@B@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ H@@@EAD@@B@ HB@ HB@ HB@
+HB@ HB@ HB@ HB@ HB@ HB@@@B@ HB@ HB@ HB@ HB@ H@@a') ; colorMapFromArray:#[0 0 0 88 88 88 0 0 128 0 0 255 0 128 0 0 192 0 0 128 0 0 128 128 0 192 192 0 255 255 128 0 0 192 0 0 255 0 0 192 88 0 128 0 128 192 0 192 255 0 255 128 128 0 255 128 0 255 168 88 192 192 0 255 255 0 128 128 128 128 128 255 255 220 168 195 195 195 192 192 255 192 255 192 255 192 192 255 192 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G????1????<_????G????7??????????????????
+?????????????7????<G????@_???0A?? @@G? @@@_ @@@A @@b') ; yourself); yourself]
+!
+
+normalPackageMutimedia
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageMutimedia inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageMutimedia
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageMutimedia'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+DA@PDA@PDA@PDA@P@@@PDA@PD@@PDA@PDA@PDA@PDA@PDA@PDA@PDA@P@@@OC0@PDA@@C0@@DA@PDA@PDA@PDA@PDA@PDA@P@@@OC08NC0@P@@<NC0<@@A@P
+DA@PDA@PDA@PDA@P@@@OC08NC 8N@@@OC 8NC <O@@@PDA@PDA@PDA@P@@@OC08NC 8N@@@DAP@@C 8NC 8OC0@@DA@PDA@P@@@OC08NC 8N@@@DA@PDAPP@
+@@8NC 8NC0<@@A@P@@@OC08NC 8N@@@DA@PDA@TDAPPE@@@NC 8NC <O@@@P@@<NC 8N@@@DA@PDA@PDA@TDAPPEA@@@C 8NC 8@DA@P@@<N@@@DA@PDA@PD
+A@PEA@TDAPPEA@T@@@8N@A@P@@@@@@@DA@PDA@PDA@PDA@PEA@TDAPPEA@TD@@@@@@@P@@@NC @@A@PDA@PDA@PDAPPEA@TDAPPE@@@NC @@DA@PD@@@C 8@
+@@PDA@PDA@PDAPPEA@TD@@@NC @@DA@PDA@P@@<@@@8N@@@DA@PDA@TDAPPE@@@NC @@AP@PDA@PDA@@C08N@@@NC @@A@PDA@TD@@@NC @@APTE@A@PDA@P
+D@@OC 8NC @@C 8@@@PE@@@N@@@@@@@@APT@DA@PDA@P@@<NC 8NC 8@@@8N@@@N@@@HB@ HB@ @@@@PDA@PDA@@C08NC 8NC 8N@@@NAP@MB@ HB@ HB@ H
+@A@PDA@PD@@OC 8NC 8NC 8NC 8@B0LMB@ HB@ HB@<O@A@PDA@P@@<NC 8NC 8NC 8N@@DAB0LHB@ HB@ OC0<H@A@PDA@@C08NC 8NC 8NC 8@B@(AB0LH
+B@ HB@<OB@ @DA@PD@@OC 8NC 8NC 8N@@ HB@ AB0\FA \OB@ HB@ @DA@P@@<NC 8NC 8NC 8@B@ HB@ GA @@A \HB@ HB@@PDA@@C08NC 8NC 8NC @H
+B@ HB@X@APT@A  HB@ H@A@PD@@OC 8NC 8NC 8N@@ HB@ HA @EC @FB@ HB@ @DA@P@@TNC 8NC 8NC 8@B@ HB@ GA @@A \HB@ HB@@PDA@@@@TEC 8N
+C 8NC @HB@ HB@<GA XGBPHHB@ H@A@PDA@P@@@EAP8NC 8NC @HB@<OB@ HB@ CBPHKB@@PDA@PDA@PD@@@APTNC 8N@@ OC0<HB@ HB@ CBPHB@A@PDA@P
+DA@PDA@@@@TEC 8N@@<OB@ HB@ HB@0CBP@PDA@PDA@PDA@PDA@P@@@EAP8E@@ HB@ HB@ HB@0@DA@PDA@PDA@PDA@PDA@PD@@@APP@@@@HB@ HB@ @@A@P
+DA@PDA@PDA@PDA@PDA@PDA@@@A@PD@@@@@@@@A@PDA@PD@@a') ; colorMapFromArray:#[0 0 0 0 128 0 0 255 255 255 0 255 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 192 192 255 192 255 192 192 255 255 255 192 192 255 192 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???<G????!!????8_????G????1??
+??<_????G????1????<G???>@_??? A???0@G??8@@_?<@@A#<@b') ; yourself); yourself]
+!
+
+normalPackageNetwork
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageNetwork inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageNetwork
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageNetwork'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+C@0LC@0LC@0LC@0L@@@LC@0LC@@LC@0LC@0LC@0LC@0LC@0LC@0LC@0L@@@KB0@LC@0@B0@@C@0LC@0LC@0LC@0LC@0LC@0L@@@KB0(JB0@L@@,JB0,@@@0L
+C@0LC@0LC@0LC@0L@@@KB0(JB (J@@@KB (JB ,K@@@LC@0LC@0LC@0L@@@KB0(JB (J@@@FA0@@B (JB (KB0@@C@0LC@0L@@@KB0(JB (J@@@FA XFA0X@
+@@(JB (JB0,@@@0L@@@KB0(JB (J@@@FA XFA \FA0XG@@@JB (JB ,K@@@L@@,JB (J@@@FA XFA XFA \FA0XGA @@B (JB (@C@0L@@,J@@@FA XFA XF
+A XGA \FA0XGA \@@@(J@@0L@@@@@@@FA XFA XFA XFA XGA \FA0XGA \F@@@@@@@L@@@JB @@A XFA XFA X@@@@@@@@@@@@G@@@JB @@C@0LC@@@B (@
+@@XFA XF@@$IBP$IBP$IBP@JB @@C@0LC@0L@@,@@@(J@@@FA @IBP$IBP$IBP$H@@@@A0@LC@0LC@0@B0(J@@@JB @@@@,KB0,KB0,KB@ @A0\G@@0LC@0L
+C@@KB (JB @@B (@BP HB@ HB@$HB@@GA0\@C@0LC@0L@@,JB (JB (@@@@I@ HB@ HBB0 @@@@@@@@@@@0LC@0@B0(JB (JB (J@@$AA@DB@PHK@@$IBP$I
+BP$I@@0LC@@KB (JB (JB (@BPDA@PDA@P@IBP$IBP$IBP @C@0L@@,JB (JB (JB @I@PDA@PD@B0,KB0,KB0,HB@@LC@0@B0(JB (JB (J@@,KB0,KB0@I
+B@ HB@ HBP H@@0LC@@KB (JB (JB (J@@@@@@@@@@$B@ HB@ HKB@ @C@0L@@,JB (JB (JB (@B@ HB@ @BPHD@ DB@P,HB@@LC@0@B0(JB (JB (J@@,K
+B0,KB0@I@PDA@PDAB0 H@@0LC@@KB (JB (JB (@BP$IBP$I@@$A@PDA@PDKB@@LC@0L@@\JB (JB (JB @I@0$@@@@@B0,KB0,KB0,@B@@LC@0@@@\GB (J
+B (J@@$IBP$IBP$@@@@@@@@@@@ I@@0LC@0L@@@GA0(JB (J@@@@@@@@@@@HB@ HB@ HBP @C@0LC@0LC@@@A0\JB (JB \GA0\@B0,KB0,KB0,HB@@LC@0L
+C@0LC@0@@@\GB (JA0\GA @IBP$IBP$IBP H@@0LC@0LC@0LC@0L@@@GA0(GA X@@@$EBP@@@@@IB@@LC@0LC@0LC@0LC@0LC@@@A0X@@@0@BP$IBP$IBP$@
+C@0LC@0LC@0LC@0LC@0LC@0@@@0LC@0@@@@@@@@@@@0LC@@a') ; colorMapFromArray:#[0 0 0 0 0 128 0 0 255 0 128 0 0 255 255 255 0 0 128 128 0 192 192 0 128 128 128 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G????!!????<_????G????1????<_????G????1??
+??<_???>G????1????<G????@_???0A???<@G??>@@_/?@@A!!? b') ; yourself); yourself]
+!
+
+normalPackageSettings
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageSettings inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageSettings
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageSettings'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B@ HB@ HB@ HB@ H@@@HB@ HB@@HB@ HB@ HB@ HB@ HB@ HB@ HB@ H@@@GA0@HB@ @A0@@B@ HB@ HB@ HB@ HB@ HB@ H@@@GA0XFA0@H@@\FA0\@@@ H
+B@ HB@ HB@ HB@ H@@@GA0XFA XF@@@GA XFA \G@@@HB@ HB@ HB@ H@@@GA0XFA XF@@@A@ @@A XFA XGA0@@B@ HB@ H@@@GA0XFA XF@@@A@PDA@ D@
+@@XFA XFA0\@@@ H@@@GA0XFA XF@@@A@PDA@PHA@ DB@@@FA XFA \G@@@H@@\FA XF@@@A@PDA@PDA@PHA@ DB@P@@A XFA X@B@ H@@\F@@@A@PDA@PDA
+@PDB@PHA@ DB@PH@@@XF@@ H@@@@@@@A@PDA@PDA@PDA@PDB@PHA@ DB@PHA@@@@@@@H@@@FA @@@PDA@PDA@PDA@ DB@PHA@ DB@@@FA @@B@ HB@@@A X@
+@@DA@PDA@PDA@ DB@PHA@@@FA @@B@ HB@ H@@\@@@XF@@@A@PDA@PHA@ DB@@@FA @@@ @HB@ HB@ @A0XF@@@FA @@@PDA@PHA@@@FA @@@ HB@@ HB@ H
+B@@GA XFA @@A X@@@DA@@@FA @@@@HB@ H@B@ HB@ H@@\FA XFA X@@@XF@@@FA @@@@\D@@HB@ @HB@ HB@ @A0XFA XFA XF@@@F@ @@@ H@A0P@@ H@
+@@ HB@ HB@@GA XFA XFA XFA X@A@\@@@\EAPL@@@\D@@ HB@ H@@\FA XFA XFA XFA @CAP\GAPTEAP\GAPL@B@ HB@ @A0XFA XFA XFA XF@ @DAPTE
+APTEAPTC@@ HB@ HB@@GA XFA XFA XFA XB@@\EAPPCA@TEAPP@B@ HB@ H@@\FA XFA XFA XF@@@GAPTD@0@@A0TEAPP@@@ HB@ @A0XFA XFA XFA @G
+A0TEAPL@@ H@A0TEAP\D@@ HB@@GA XFA XFA XF@@LCAPTEA@@B@ @GAPTE@0L@B@ H@@HFA XFA XFA XF@@@DA@TEA0@@A0TEAPL@@@ HB@ @@@HBA XF
+A XFA XF@ @DAPTEA0\EAPTC@@ HB@ HB@ H@@@B@ XFA XFA XB@@\EAPTEAPTEAPL@B@ HB@ HB@ HB@@@@ HFA XFA @GAPLDAPTEAPTGAPL@B@ HB@ H
+B@ HB@ @@@HBA XF@@PC@@@GAPTC@@@D@0@HB@ HB@ HB@ HB@ H@@@B@ XB@@@@@@@G@0@HB@@@B@ HB@ HB@ HB@ HB@ HB@@@@ H@@@ H@@\C@@ HB@ H
+B@ HB@ HB@ HB@ HB@ HB@ @@@ HB@ H@@@HB@ HB@ HB@@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 128 128 128 160 160 160 195 195 195 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???<G????A???? _???8G????!!??
+??<_????G????!!???? G???8@_???@A???0@G?>X@@_'' @@A 0@b') ; yourself); yourself]
+!
+
+normalPackageSystem
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageSystem inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageSystem
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageSystem'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+B@ HB@ HB@ HB@ H@@@HB@ HB@@HB@ HB@ HB@ HB@ HB@ HB@ HB@ H@@@GA0@HB@ @A0@@B@ HB@ HB@ HB@ HB@ HB@ H@@@GA0XFA0@H@@\FA0\@@@ H
+B@ HB@ HB@ HB@ H@@@GA0XFA XF@@@GA XFA \G@@@HB@ HB@ HB@ H@@@GA0XFA XF@@@BA@@@A XFA XGA0@@B@ HB@ H@@@GA0XFA XF@@@B@ HBA@H@
+@@XFA XFA0\@@@ H@@@GA0XFA XF@@@B@ HB@ PBA@HD@@@FA XFA \G@@@H@@\FA XF@@@B@ HB@ HB@ PBA@HD@ @@A XFA X@B@ H@@\F@@@B@ HB@ HB
+@ HD@ PBA@HD@ P@@@XF@@ H@@@@@@@B@ HB@ HB@ HB@ HD@ PBA@HD@ PB@@@@@@@H@@@FA @@@ HB@ HB@ HBA@HD@ @@@@@D@@@FA @@B@ HB@@@A X@
+@@HB@ HB@ HBA@H@@@@@@@@FA @@B@ HB@ H@@\@@@XF@@@B@ HB@ PBA@@G@@@G@@@@@ @HB@ HB@ @A0XF@@@FA @@@ HB@ P@@@@@@@@@@ HB@@ HB@ H
+B@@GA XFA @@A X@@@H@@@X@@@DC@0D@@ H@B@ HB@ H@@\FA XFA X@@@XF@@@@@@@@@0LC@0L@@ @HB@ HB@ @A0XFA XFA XF@@@F@ HB@@@@@PDC@0@B
+@@ HB@ HB@@GA XFA XFA XF@@@B@ H@@@@@@@@@@ H@@@ HB@ H@@\FA XFA XFA @G@@HB@@@@@@@@@@@B@ @G@@ HB@ @A0XFA XFA X@A0\@@@@@@@@G
+A0@@@@@@@@\G@@ HB@@GA XFA XFA @GA0\@@@@@@@\G@@@@@@@GA0\@B@ H@@\FA XFA XFA @@@@@@@@@@A0\@@@@@@@@@@@ HB@ @A0XFA XFA XFA XF
+@ @@@@@GA0@@@@@B@@ HB@ HB@@GA XFA XFA XFA XB@@@@AP\GAP@@@@H@B@ HB@ H@@PFA XFA XFA XFA H@@@\GA0\GA0@@@ @HB@ HB@ @@@PDA XF
+A XFA XF@ @GA0\GA0\GA0@@@@ HB@ HB@ H@@@DA@XFA XFA XB@@\GA0\GA0\G@@ HB@ HB@ HB@ HB@@@A@PFA XFA H@A0\GA0\GA0\@B@ HB@ HB@ H
+B@ HB@ @@@PDA XF@ H@@@\GA0\@@@ HB@ HB@ HB@ HB@ HB@ H@@@DA@XB@@LC@@@@@@LC@@ HB@ HB@ HB@ HB@ HB@ HB@@@A@@C@0L@B@ @@0LC@@ H
+B@ HB@ HB@ HB@ HB@ HB@ @B@@@@@ HB@ @@@@HB@ HB@@a') ; colorMapFromArray:#[0 0 0 192 88 0 128 128 0 255 128 0 192 192 0 128 128 128 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???8G???>A???? _???<G????!!????<_????G????!!??
+?? _???8G???>A???? G??? @_??8@A??<@@G?? @@_9<@@A\N@b') ; yourself); yourself]
+!
+
+normalPackageUtilities
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self normalPackageUtilities inspect
+     ImageEditor openOnClass:self andSelector:#normalPackageUtilities
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class normalPackageUtilities'
+	ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+C 8NC 8NC 8NC 8N@@@NC 8NC @NC 8NC 8NC 8NC 8NC 8NC 8NC 8N@@@MCP@NC 8@CP@@C 8NC 8NC 8NC 8NC 8NC 8N@@@MCP0LCP@N@@4LCP4@@@8N
+C 8NC 8NC 8NC 8N@@@MCP0LC@0L@@@MC@0LC@4M@@@NC 8NC 8NC 8N@@@MCP0LC@0L@@@CA @@C@0LC@0MCP@@C 8NC 8N@@@MCP0LC@0L@@@C@0LCA L@
+@@0LC@0LCP4@@@8N@@@MCP0LC@0L@@@C@0LC@0XCA LF@@@LC@0LC@4M@@@N@@4LC@0L@@@C@0LC@0LC@0XCA LF@0@@C@0LC@0@C 8N@@4L@@@C@0LC@0LC
+@0LF@0XCA LF@0X@@@0L@@8N@@@@@@@C@0LC@0LC@0LC@0LF@0XCA LF@0XC@@@@@@@N@@@LC@@@@0LC@0LC@0LCA LF@0XCA LF@@@LC@@@C 8NC @@C@0@
+@@LC@0LC@0LF@0@@@@@@@@@LC@@@C 8NC 8N@@4@@@0L@@@C@0LC@0L@A0DA@P@LC@@@A @NC 8NC 8@CP0L@@@LC@@@@0LC@@\GA0\G@@@@A XF@@8NC 8N
+C @MC@0LC@@@C@0@@@@GA0 A@PD@A XF@@@@@@8NC 8N@@4LC@0LC@0@@@0@A0\H@PDA@P@FA @KB @NC 8NC 8@CP0LC@0LC@0L@@\GB@DA@PDA@@X@B0(@
+C 8N@@8NC @MC@0LC@0LC@@GA0 A@PDA@P@FA @KB @NC @@C 8N@@4LC@0LC@0L@@\H@PDA@PD@A XF@@,JB0@@B @NC 8@CP0LC@0LC@0@B@DA@PDA@@$@
+A @KB HJB0,B@@8NC @MC@0LC@0LC@@A@PDA@P@DAP$@B0(BB HB@ @NC 8N@@4LC@0LC@0LC@@A@PD@A @D@@,J@ (B@@@@C 8NC 8@CP0LC@0LC@0LC@@A
+@@XFA @KB HJ@ @F@@8NC 8NC @MC@0LC@0LC@0LC@@FA X@B0(BB H@A X@C 8NC 8N@@XLC@0LC@0LC@0LC@XF@@,J@ (B@@$@A @NC 8NC 8@@@XFC@0L
+C@0LC@0LA @KB HJ@ @DAP$@@@8NC 8NC 8N@@@FA 0LC@0LC@0@B0(BB H@A @DAP$@C 8NC 8NC 8NC @@A XLC@0L@@,J@ (B@@X@@@@DAP$@C 8NC 8N
+C 8NC 8@@@XFC@@KB HJ@ @@@@8NC @DAP$@C 8NC 8NC 8NC 8N@@@F@@,BB H@@@8NC 8NC @DAP$@C 8NC 8NC 8NC 8NC @@@ HB@@8NC 8NC 8NC @D
+AP@NC 8NC 8NC 8NC 8NC 8@@@@NC 8NC 8NC 8NC @@C @a') ; colorMapFromArray:#[0 0 0 88 88 88 0 192 192 128 128 0 255 128 0 255 168 88 192 192 0 128 128 128 160 160 160 255 220 168 195 195 195 192 255 255 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@0P@@@>O@@@?7<@@???0@????@????<?????7????8????<?????7????8_???8G???>A???? _???<G???>A????D_???3G????1????<_???>G????A??
+?? _???8G???>A???? G???8@_???@A??#8@G? _@@_ C0@A0@Xb') ; yourself); yourself]
+!
+
+notInstalledpackageIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self notInstalledpackageIcon inspect
+     ImageEditor openOnClass:self andSelector:#notInstalledpackageIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class notInstalledpackageIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@ATET@AUEE@APQAP@TDQT@A]5_@@UUU\@O5?G@@E@M0C=_3\@?W<7@O5?M0C=_3\@?W<4@O5?M@C=_0@@@T@@@@a') ; colorMapFromArray:#[0 0 0 132 0 132 255 255 0 152 156 152]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A30O[A%LF?<O?0??G?<??3??O?<??3??O?8??C?8O?@b') ; yourself); yourself]
+!
+
+packageDirtyIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self packageDirtyIcon inspect
+     ImageEditor openOnClass:self andSelector:#packageDirtyIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class packageDirtyIcon'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPT@@@TEAP@EAPTEAPTEAP@@@0L@@@@C@@@EAPTE@@@C@0@@@PH@@@LC@@@E@@LC@@@A@PDB@ H@@@LC@@@@@@DA@PDA@ HB@ H@@@@E@@L@@@DA@PHB
+@ @@@@TEAP@C@0L@@@DB@@@B@ @EAPT@@0@C@@L@@@HB@@H@APTE@@LC@0LC@0H@@ H@@@TEAP@C@@L@@0@B@ @B@ @EAPT@@0LC@0LC@@HB@ @@APTE@@L@
+@0@C@@HB@@HB@@TEAP@B@0LC@0L@@ HB@@@EAPTE@@@B@0@C@ H@@@TEAPTEAPTE@@@B@0@@APTEAPTEAPTEAPTE@@@EAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 200 200 200 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?<_?1??G?<_?0?<@?@@0@b') ; yourself); yourself]
+!
+
+packageIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self packageIcon inspect
+     ImageEditor openOnClass:self andSelector:#packageIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class packageIcon'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPT@@@TEAP@EAPTEAPTEAP@@@0L@@@@C@@@EAPTE@@@C@0@@@PH@@@LC@@@E@@LC@@@A@PDB@ H@@@LC@@@@@@DA@PDA@ HB@ H@@@@E@@L@@@DA@PHB
+@ @@@@TEAP@C@0L@@@DB@@@B@ @EAPT@@0LC@0L@@@HB@ H@APTE@@LC@0LC@0HB@ HB@@TEAP@C@0LC@0LB@ HB@ @EAPT@@0LC@0LC@ HB@ H@APTE@@LC
+@0LC@0HB@ HB@@TEAP@B@0LC@0LB@ HB@@@EAPTE@@@B@0LC@ H@@@TEAPTEAPTE@@@B@0@@APTEAPTEAPTEAPTE@@@EAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 128 128 0 192 192 0 255 255 192 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?<_?1??G?<_?0?<@?@@0@b') ; yourself); yourself]
+!
+
+packageOverriddenIcon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self packageOverriddenIcon inspect
+     ImageEditor openOnClass:self andSelector:#packageOverriddenIcon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:#'Packages::PackageSelector::HierarchicalPackageSelector class packageOverriddenIcon'
+	ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(nil )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+APTEAPT@@@TEAP@EAPTEAPTEAP@@@0L@@@@C@@@EAPTE@@@C@0@@@PH@@@LC@@@E@@LC@@@A@PDB@ H@@@LC@@@@@@DA@PDA@ HB@ H@@@@E@@L@@@DA@PHB
+@ @@@@TEAP@C@0L@@@DB@@@B@ @EAPT@@0LC@0L@@@HB@ H@APTE@@LC@0LC@0HB@ HB@@TEAP@C@0LC@0LB@ HB@ @EAPT@@0LC@0LC@ HB@ H@APTE@@LC
+@0LC@0HB@ HB@@TEAP@B@0LC@0LB@ HB@@@EAPTE@@@B@0LC@ H@@@TEAPTEAPTE@@@B@0@@APTEAPTEAPTEAPTE@@@EAPTEAPTEAP@a') ; colorMapFromArray:#[0 0 0 192 0 0 250 0 0 255 150 150 255 255 255 0 0 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A"@_>G?>?????7?<_?1??G?<_?1??G?<_?0?<@?@@0@b') ; yourself); yourself]
+! !
+
+!PackageSelector::HierarchicalPackageSelector class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:Packages::PackageSelector::HierarchicalPackageSelector andSelector:#windowSpec
+     Packages::PackageSelector::HierarchicalPackageSelector new openInterface:#windowSpec
+     Packages::PackageSelector::HierarchicalPackageSelector open
+    "
+
+    <resource: #canvas>
+
+    ^
+     #(#FullSpec
+	#name: #windowSpec
+	#window:
+       #(#WindowSpec
+	  #label: 'Packages::PackageSelectorApplication'
+	  #name: 'Packages::PackageSelectorApplication'
+	  #min: #(#Point 10 10)
+	  #max: #(#Point 1024 768)
+	  #bounds: #(#Rectangle 29 59 329 359)
+	  #menu: #mainMenu
+	)
+	#component:
+       #(#SpecCollection
+	  #collection: #(
+	   #(#HierarchicalListViewSpec
+	      #name: 'SelectionInListModelView2'
+	      #layout: #(#LayoutFrame 0 0 0 0 0 1 0 1)
+	      #model: #packagesSelectedIndexHolder
+	      #menu: #popUpMenu
+	      #hasHorizontalScrollBar: true
+	      #hasVerticalScrollBar: true
+	      #listModel: #tree
+	      #multipleSelectOk: true
+	      #highlightMode: #line
+	      #valueChangeSelector: #newSelectedIndexes:
+	    )
+	   )
+
+	)
+      )
+! !
+
+!PackageSelector::HierarchicalPackageSelector class methodsFor:'menu specs'!
+
+popUpMenu
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Packages::PackageSelector::HierarchicalPackageSelector andSelector:#popUpMenu
+     (Menu new fromLiteralArrayEncoding:(Packages::PackageSelector::HierarchicalPackageSelector popUpMenu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^
+     #(#Menu
+	#(
+	 #(#MenuItem
+	    #label: 'New category'
+	    #itemValue: #kjj
+	    #translateLabel: true
+	  )
+	 #(#MenuItem
+	    #label: 'Properties'
+	    #itemValue: #showProperties
+	    #translateLabel: true
+	  )
+	 #(#MenuItem
+	    #label: 'Inspect'
+	    #itemValue: #inspectPackage
+	    #translateLabel: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Save Package'
+	    #itemValue: #savePackage
+	    #translateLabel: true
+	  )
+	 #(#MenuItem
+	    #label: 'Unload Package'
+	    #itemValue: #unloadPackage
+	    #translateLabel: true
+	  )
+	 #(#MenuItem
+	    #label: 'Uninstall Package'
+	    #itemValue: #uninstallPackage
+	    #translateLabel: true
+	  )
+	 )
+	nil
+	nil
+      )
+! !
+
+!PackageSelector::HierarchicalPackageSelector class methodsFor:'plugIn spec'!
+
+aspectSelectors
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this. If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "Return a description of exported aspects;
+     these can be connected to aspects of an embedding application
+     (if this app is embedded in a subCanvas)."
+
+    ^ #(
+	#packagesSelectedHolder
+      ).
+
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'* As yet uncategorized *'!
+
+categoryItemNamed:aName
+    tree root children do:[:anItem |
+	anItem isCategoryItem ifTrue:[
+	    anItem label = aName ifTrue:[
+		^ anItem
+	    ].
+	].
+    ].
+
+    ^ nil
+!
+
+packagedManagerChangeAddPackage:aPackage
+    | categoryItem |
+    categoryItem := (self categoryItemNamed:aPackage category) ifNil:[
+	categoryItem := tree root add: (CategoryItem name:aPackage category packageManager:self packageManager)
+    ].
+
+    categoryItem add:(categoryItem newItemPackageWithPackage:aPackage).
+    ^ self
+!
+
+packagedManagerChangeRemovePackage:aPackage
+
+    tree copy do:[:anItem |
+	anItem isPackageItem ifTrue:[
+	    anItem package == aPackage ifTrue:[
+		anItem remove.
+	    ].
+	].
+    ].
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'accessing'!
+
+masterApplication:aMasterApplication
+    "initialization"
+    | aPackageManager newRootItem tree categories |
+    super masterApplication:aMasterApplication.
+    tree := self tree.
+    tree showRoot:false.
+    aPackageManager := self packageManager.
+
+    newRootItem := RootItem new.
+    tree root:newRootItem.
+    categories := aPackageManager allPackageCategories collect:[:aCategory |
+	self newItemPackageWithCategory:aCategory packageManager:aPackageManager
+    ].
+
+"/    packageItems := (aPackageManager packages collect:[:aPackage |  self newItemPackageWithPackage:aPackage]).
+    newRootItem addAll:categories.
+    newRootItem add:(self newItemPackageWithPackage:aPackageManager defaultPackage) .
+
+    newRootItem expand.
+    newRootItem sort.
+!
+
+selected
+    ^ self selectionHolder value
+!
+
+selectedPackage
+    ^ self packageManager packageNamed:self selection
+!
+
+selectionChangedBlock
+    "return the value of the instance variable 'selectionChangedBlock' (automatically generated)"
+
+    ^ selectionChangedBlock
+!
+
+selectionChangedBlock:something
+    "set the value of the instance variable 'selectionChangedBlock' (automatically generated)"
+
+    selectionChangedBlock := something.
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'actions'!
+
+inspectPackage
+    | packagesSelected selectedSinglePackage|
+    packagesSelected := self  packagesSelected.
+    (packagesSelected size > 1) ifTrue:[
+	self warn:'Only one package can be selected!!'.
+	^ self
+    ].
+    (packagesSelected size = 0) ifTrue:[
+	self warn:'You need to select a package'.
+	^ self
+    ].
+
+    selectedSinglePackage := packagesSelected first.
+    selectedSinglePackage inspect.
+!
+
+savePackage
+    "assumes that there is only one package is selected"
+    | filename repeat |
+    repeat := true.
+    [repeat] whileTrue:[
+	filename := FileDialog
+			requestFileName:'enter a fileName:'
+			default:''
+			version:nil
+			ifFail:[nil]
+			pattern:'*.*'
+			fromDirectory:nil
+			whenBoxCreatedEvaluate:nil.
+	(Switch new)
+	    if:[filename isNil] then:[^ self "do nothing!!"];
+	    if:[filename asFilename isDirectory] then:[
+		repeat := (self confirm:'Directory selected!! Do you want to try this again?')
+	    ];
+	    if:[filename asFilename exists] then:[
+		repeat := (self confirm:'This file already exists!! Do you want to override this file?') not
+	    ];
+	    otherwise:[repeat := false];
+	    value
+
+    ].
+    self halt.
+    self packageManager savePackage:(self packagesSelected first) as:filename asFilename
+!
+
+showProperties
+
+    "size should only be one as this action should be disabled if there is more than
+    one package selected."
+
+    self showPropertiesOfPackage:self packagesSelected first
+!
+
+showPropertiesOfPackage:aPackage
+
+    ((PackageProperties new) masterApplication:self)openAsSlave
+!
+
+uninstallPackage
+    "assumes that there is only one package is selected"
+    | aPackage |
+    aPackage := self packagesSelected first.
+    (self packageManager isBasePackage:aPackage) ifTrue:[
+	self warn:'Package is registered as a ''Base Package'' and cannot be uninstalled'.
+	^ self
+    ].
+
+    (self confirm:'Are you sure you want to uninstall the package named: ', aPackage name, '?\\' withCRs
+		    , 'This will remove all classes currently under this package''s control!!') ifFalse:[
+	^ self
+    ].
+
+    self packageManager uninstallPackage:aPackage
+!
+
+unloadPackage
+    "assumes that there is only one package is selected"
+    | aPackage |
+    aPackage := self packagesSelected first.
+    (self packageManager isBasePackage:aPackage) ifTrue:[
+	self warn:'Package is registered as a ''Base Package'' and cannot be unload'.
+	^ self
+    ].
+
+    (self confirm:'Are you sure you want to unload the package named: ', aPackage name) ifFalse:[
+	^ self
+    ].
+    self packageManager unloadPackage:aPackage
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'aspects'!
+
+packagesSelectedIndexHolder
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    packagesSelectedIndexHolder isNil ifTrue:[
+	packagesSelectedIndexHolder := ValueHolder new.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       packagesSelectedIndexHolder addDependent:self.
+"/       packagesSelectedIndexHolder onChangeSend:#packagesSelectedIndexHolderChanged to:self.
+    ].
+    ^ packagesSelectedIndexHolder.
+!
+
+tree
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    tree isNil ifTrue:[
+	tree := HierarchicalList new.
+	tree application:self.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       tree addDependent:self.
+"/       tree onChangeSend:#treeChanged to:self.
+    ].
+    ^ tree.
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'change & update'!
+
+newSelectedIndexes:collectionOfIndexes
+    | newSelectionItems|
+    newSelectionItems := collectionOfIndexes collect:[:idx |
+	self tree at:idx
+    ].
+
+    self newSelectedItems:newSelectionItems
+!
+
+newSelectedItems:aCollectionOfPackageItems
+    | packageNames packagesSelected |
+    packageNames := aCollectionOfPackageItems collect:[:anItem |
+	(anItem isRootItem) ifFalse:[
+	    anItem isPackageItem ifTrue:[
+		anItem package name.
+	    ] ifFalse:[
+		nil.
+	    ].
+	] ifTrue:[
+	    nil. "no package is selected."
+	].
+    ].
+    packagesSelected := (self packagesNamed: packageNames).
+    (packagesSelected includes:nil) ifTrue:[| minimumIndex |
+	"error handling in a case that should not really happen"
+
+	self warn:'Error - Packages selected include a name which the package manager does not know!!'.
+	minimumIndex := self packagesSelectedIndexHolder value first.
+	self packagesSelectedIndexHolder value do:[:anIndex | | item |
+	    minimumIndex := minimumIndex min:anIndex.
+	    item := (tree at:anIndex).
+	    (self packageManager includesPackage:item package) ifFalse:[
+		item remove.
+	    ].
+	].
+
+	self packagesSelectedIndexHolder value:(Array with:((minimumIndex - 1) max:1)).
+    ].
+    self packagesSelectedHolder value:packagesSelected
+!
+
+update:something with:aParameter from:changedObject
+
+    self breakPoint:''.
+! !
+
+!PackageSelector::HierarchicalPackageSelector methodsFor:'factory'!
+
+newItemPackageWithCategory:name packageManager:manager
+    ^ CategoryItem name:name packageManager:manager
+!
+
+newItemPackageWithPackage:aPackage
+    ^ PackageItem package:aPackage
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem class methodsFor:'accessing'!
+
+iconFor:aCategoryItem
+    "roundabout ;-) "
+    ^ aCategoryItem model iconFor:aCategoryItem
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem class methodsFor:'instance creation'!
+
+name:aName packageManager:aPackageManager
+    ^(self new)
+	    name:aName;
+	    packageManager:aPackageManager
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem methodsFor:'accessing'!
+
+children
+    children ifNil:[
+	children :=  self createPackageItemsFrom:(packageManager packagesAtCategoryName:self name).
+	self sort:[:x :y |
+	    x label < y label
+	].
+    ].
+    ^ children
+!
+
+icon
+    ^ self class iconFor:self.
+!
+
+label
+
+    ^ name
+!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+    ^ name
+!
+
+name:something
+    "set the value of the instance variable 'name' (automatically generated)"
+
+    name := something.
+!
+
+packageManager
+    "return the value of the instance variable 'packageManager' (automatically generated)"
+
+    ^ packageManager
+!
+
+packageManager:something
+    "set the value of the instance variable 'packageManager' (automatically generated)"
+
+    packageManager := something.
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem methodsFor:'factory'!
+
+createPackageItemsFrom:aCollectionOfPackages
+    ^ aCollectionOfPackages collect:[:aPackage |
+	self newItemPackageWithPackage:aPackage
+    ].
+
+
+
+
+
+!
+
+newItemPackageWithPackage:aPackage
+    ^ ((Packages::PackageSelector::HierarchicalPackageSelector::PackageItem) parent:self)  package:aPackage
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem methodsFor:'printing'!
+
+printOn:aStream
+    aStream nextPutAll:'CategoryItem named: ''',
+	self name, ''''.
+! !
+
+!PackageSelector::HierarchicalPackageSelector::CategoryItem methodsFor:'queries'!
+
+isCategoryItem
+    ^ true
+!
+
+isPackageItem
+    ^ false.
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem class methodsFor:'accessing'!
+
+iconFor:aPackageItem
+    | package |
+    package := aPackageItem package.
+    (package name == (Project noProjectID)) ifTrue:[
+	^ self iconsClass defaultPackageIcon
+    ].
+
+    (aPackageItem packageManager isBasePackage:package) ifTrue:[
+	^ self iconsClass basePackageIcon
+    ].
+
+    (package isInstalled not) ifTrue:[
+	^ self iconsClass loadedPackageIcon
+    ].
+
+    ^ self iconsClass packageIcon
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem class methodsFor:'constants'!
+
+iconsClass
+    ^ Packages::PackageSelector::HierarchicalPackageSelector
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem class methodsFor:'instance creation'!
+
+package:something
+    ^ self basicNew package:something
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem methodsFor:'* As yet uncategorized *'!
+
+isSelected
+    | packagesSelected |
+    packagesSelected := (self application packagesSelected).
+
+    packagesSelected ifNotNil:[
+	^ packagesSelected includes:package
+    ].
+
+    ^ false.
+!
+
+packageManager
+    ^ PackageManager smalltalkPackageManager
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem methodsFor:'accessing'!
+
+icon
+    ^ self class iconFor:self.
+!
+
+label
+    | emphasis |
+    emphasis := OrderedCollection new.
+    package isDirty ifTrue:[
+	emphasis add:#italic.
+    ].
+    package isOverridden ifTrue:[
+	self isSelected ifFalse:[
+	    emphasis add:(#color->Color red darker )
+	]
+    ].
+
+    ^ Text string:package name emphasis:emphasis asArray.
+"/    ^ package name
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:something
+    "set the value of the instance variable 'package' (automatically generated)"
+
+    package := something.
+! !
+
+!PackageSelector::HierarchicalPackageSelector::PackageItem methodsFor:'queries'!
+
+isCategoryItem
+    ^ false
+!
+
+isPackageItem
+    ^ true
+! !
+
+!PackageSelector::HierarchicalPackageSelector::RootItem methodsFor:'queries'!
+
+isCategoryItem
+    ^ false
+!
+
+isPackageItem
+    ^ false
+! !
+
+!PackageSelector::HierarchicalPackageSelector::RootItem methodsFor:'sorting'!
+
+sort
+    self sort:[:x :y|
+	(x isCategoryItem and:[y isCategoryItem]) ifTrue:[
+	    x name < y name
+	] ifFalse:[ y isCategoryItem
+	].
+    ].
+! !
+
+!PackageSelector class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSelector.st,v 1.5 2006/08/24 08:38:35 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageSmalltalkManipulationTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,1221 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractTestCases subclass:#PackageSmalltalkManipulationTestCases
+	instanceVariableNames:'packageManager defaultPackage'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package'
+!
+
+!PackageSmalltalkManipulationTestCases class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackageSmalltalkManipulationTestCases methodsFor:'initialize / release'!
+
+initialize
+
+    packageManager ifNil:[
+        packageManager := self packageManager.
+    ].
+
+    defaultPackage ifNil:[
+        defaultPackage := packageManager defaultPackage.
+    ].
+!
+
+setUp
+    "common setup - invoked before testing"
+    super setUp.
+    self setUpUsedClasses.
+!
+
+setUpAllForQWERTY
+    | class copyQWERTYDic|
+    
+    (class := Smalltalk at:#QWERTY) ifNil:[
+        self createClassNamed:#QWERTY. 
+        (class := Smalltalk at:#QWERTY).
+    ].
+
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod3 1 + 1.'.
+    ].
+    copyQWERTYDic := QWERTY methodDictionary copy.
+    copyQWERTYDic removeKey:#aDummyMethod.
+    copyQWERTYDic removeKey:#aDummyMethod2.
+    copyQWERTYDic removeKey:#aDummyMethod3.
+    copyQWERTYDic keysAndValuesDo:[:key :value |
+       QWERTY methodDictionary removeKey:key.
+    ].
+
+    packageManager moveClass:QWERTY toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:defaultPackage.
+!
+
+setUpAllForQWERTZ
+    | class copyQWERTZDic|
+    (class := Smalltalk at:#QWERTZ) ifNil:[
+        self createClassNamed:#QWERTZ.
+        (class := Smalltalk at:#QWERTZ)
+    ].
+
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod3 1 + 1.'.
+    ].
+
+    copyQWERTZDic := QWERTZ methodDictionary copy.
+    copyQWERTZDic removeKey:#aDummyMethod.
+    copyQWERTZDic removeKey:#aDummyMethod2.
+    copyQWERTZDic removeKey:#aDummyMethod3.
+    copyQWERTZDic keysAndValuesDo:[:key :value |
+       QWERTZ methodDictionary removeKey:key.
+    ].
+
+    packageManager moveClass:QWERTZ toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:defaultPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:defaultPackage.
+!
+
+setUpUsedClasses
+    "common setup - invoked before testing"
+    |  |
+    self setUpAllForQWERTZ.
+    self setUpAllForQWERTY.                
+!
+
+tearDown
+    "common cleanup - invoked after testing"
+
+    "move class package to where it was"
+    super tearDown
+! !
+
+!PackageSmalltalkManipulationTestCases methodsFor:'test - creation'!
+
+testClassCreation
+    "tests that new classes are automatically included in workingPackage"
+     | packagedClass |
+    [
+        "prerequisites"
+        self assert:(Smalltalk classNamed:#QWERTZ2) isNil.
+
+        self createClassNamed:#QWERTZ2.
+        self assert:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (packageManager workingPackage packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk)
+    ] ensure:[
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        self assert:(defaultPackage includesPackagedClassNamed:#QWERTZ2).
+        self shouldnt:(packagedClass isInSmalltalk).
+        packagedClass removeFromPackage.
+
+        self shouldnt:(defaultPackage includesPackagedClassNamed:#QWERTZ2).
+    ]
+!
+
+testClassCreation2
+    "tests that new classes are automatically included in workingPackage"
+     | packagedClass packageTestCases |
+    [
+        self shouldnt:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ2).
+
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager workingPackage:packageTestCases.
+        self createClassNamed:#QWERTZ2.
+        self assert:(QWERTZ2 package == packageManager workingPackage name).
+
+
+        self assert:(packageTestCases includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (packageTestCases packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk)
+    ] ensure:[
+        packageTestCases ifNotNil:[
+            packageManager removePackageNamed:#'packageTestCases'.
+        ].
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+
+        packageManager workingPackage:defaultPackage.
+        self shouldnt:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ2).
+    ]
+
+!
+
+testClassRedefine
+    "tests that new classes are automatically included in workingPackage"
+     | packagedClass packageTestCases workingPackage newPackage |
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        workingPackage := packageManager workingPackage.
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self assert:(QWERTZ2 package == packageManager workingPackage name).
+
+        packageManager moveClass:QWERTZ2 toPackage:packageTestCases.
+        self assert:(packageTestCases includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (packageTestCases packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk).
+
+        self shouldnt:(workingPackage includesPackagedClassNamed:#QWERTZ2).
+
+        self createClassNamed:#QWERTZ2 inheritsFrom:#Collection.
+        newPackage := packageManager packageNamed:QWERTZ2 package.  
+
+        self assert:(newPackage includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (newPackage packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk).
+
+        workingPackage ~= newPackage ifTrue:[
+            self shouldnt:(workingPackage includesPackagedClassNamed:#QWERTZ2).
+        ].
+
+
+        packageManager moveClass:QWERTZ2 toPackage:packageTestCases.
+    ] ensure:[
+        packageManager unloadPackageNamed:#'packageTestCases'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodCreation
+    "tests that new methods are automatically included in workingPackage"
+    self createMethodFor:QWERTZ source:'testBasicMethodCreation 1 + 1'.
+    self assert:(packageManager workingPackage definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ)
+!
+
+testMethodRedefine
+    "tests that redefined are automatically included in workingPackage when they are added to
+    another package"
+     | package1 method1 packageClassIsIn packageMethodIsIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageManager addMethod:method1 toPackage:package1.
+        self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        "sometimes the #keep is done automatically. #keep meaning when a method is created a signal is asked for
+        and if not returned the method is either keep in the current project OR put into another one OR put into
+        the working package"
+        package1 ~=  packageMethodIsIn ifTrue:[
+            self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+            self shouldnt:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        ].
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRedefine2
+    "tests that redefined are automatically included in workingPackage when they are moved to
+    another package"
+     | package1 method1 packageClassIsIn packageMethodIsIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageManager moveMethod:method1 toPackage:package1.
+        self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        package1 ~= packageMethodIsIn ifTrue:[
+            self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+            self shouldnt:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        ].
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRedefine3_cancel
+    "tests that redefined methods that want to be kept in the cuurent package do so!!
+    "
+     | package1 method1 method2 packageClassIsIn packageMethodIsIn packageMethodWasIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageManager moveMethod:method1 toPackage:package1.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageMethodWasIn := packageMethodIsIn.
+
+     method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+     (Class methodRedefinitionSignal) handle:[:ex | 
+                ex proceedWith:#cancel
+        ] do:[
+            self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+            method2 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        ].
+
+        self shouldnt:(method2 package = method1 package).
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRedefine3_continue
+    "tests that redefined methods that want to be kept in the cuurent package do so!!
+    "
+     | package1 method1 packageClassIsIn packageMethodIsIn packageMethodWasIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageManager moveMethod:method1 toPackage:package1.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageMethodWasIn := packageMethodIsIn.
+
+       (Class methodRedefinitionSignal) handle:[:ex |
+                ex proceedWith:#continue
+        ] do:[
+            self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+            method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        ].
+
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageMethodWasIn ~= packageMethodIsIn ifTrue:[
+            self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+            self shouldnt:(packageMethodWasIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        ].
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRedefine3_keep
+    "tests that redefined methods that want to be kept in the cuurent package do so!!
+    "
+     | package1 method1 packageClassIsIn packageMethodIsIn packageMethodWasIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageManager moveMethod:method1 toPackage:package1.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageMethodWasIn := packageMethodIsIn.
+
+       (Class methodRedefinitionSignal) handle:[:ex |
+                ex proceedWith:#keep
+        ] do:[
+            self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+            method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        ].
+
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageMethodWasIn ~= packageMethodIsIn ifTrue:[
+            self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+            self shouldnt:(packageMethodWasIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        ].
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+! !
+
+!PackageSmalltalkManipulationTestCases methodsFor:'test - fileIn type'!
+
+testMethod_FileIn
+    "I can across an error in the GUI builder when it tried to recompile a method on the class side!!
+    it decided to change the package of the old class confusing the package completely!!
+    "
+     | package1 method1 packageClassIsIn packageMethodIsIn |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageClassIsIn := packageManager packageNamed:QWERTZ2 package.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        packageManager addMethod:method1 toPackage:package1.
+        self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+       " The test!!!!!! "
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        packageMethodIsIn := packageManager packageNamed:method1 package.
+
+        self assert:(packageMethodIsIn definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packageMethodIsIn isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        "sometimes the #keep is done automatically. #keep meaning when a method is created a signal is asked for
+        and if not returned the method is either keep in the current project OR put into another one OR put into
+        the working package"
+        package1 ~=  packageMethodIsIn ifTrue:[
+            self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+            self shouldnt:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        ].
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+! !
+
+!PackageSmalltalkManipulationTestCases methodsFor:'test - moving'!
+
+obsolete_test_moveClass1
+    "moving classes via change notification is now deprecated as i found it best to try and seperate
+    the functionality on Smalltalk and the functionality of package handling.
+    "
+    "Move QWERTZ class from package1 to package 2. Then move the class back."
+    | package1 package2 aName  |
+    [
+        package1 :=  packageManager newPackageNamed:#'package1'.
+        package2 :=  packageManager newPackageNamed:#'package2'.
+
+        packageManager addClass:QWERTZ toPackage:package1.
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ).
+
+        self assert:(package1 isDirty).
+        self shouldnt:(package2 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the class away from the classes current owner"
+            self assert:(aName := QWERTZ package) == package1 name.
+            QWERTZ setPackage:package2 name.
+            ChangeFaker classMovePackageChangeWithClass:QWERTZ oldPackageName:aName. 
+        "</simulatedChangeInBrowser>"
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.      
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.        
+        self assert:(package2 isDependentOnClassNamed:#QWERTZ).     
+        self shouldnt:(package1 isDependentOnClassNamed:#QWERTZ).       
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            self assert:(aName := QWERTZ package) == package2 name.
+            QWERTZ setPackage:package1 name.
+            ChangeFaker classMovePackageChangeWithClass:QWERTZ oldPackageName:aName. 
+        "</simulatedChangeInBrowser>"
+        self shouldnt:(package2 isDependentOnClassNamed:#QWERTZ).    
+        self assert:(package1 isDependentOnClassNamed:#QWERTZ).
+
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk. 
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+        self assert:((package1 blockedMethodsAtClassNamed:#QWERTZ) size == 0).
+        packageManager addClass:QWERTZ toPackage:defaultPackage.
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+    ].
+!
+
+obsolete_test_moveClass2
+    "moving classes via change notification is now deprecated as i found it best to try and seperate
+    the functionality on Smalltalk and the functionality of package handling.
+    "
+    "Move QWERTZ class to a new package named the same as the old package
+    but with a 1 on the end. Then move the class back."
+    | package1 package2 aName package3 |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+        package3 := packageManager newPackageNamed:#'package3'.
+
+        packageManager addClass:QWERTZ toPackage:package1.
+        packageManager addClass:QWERTZ toPackage:package2.
+        packageManager addClass:QWERTZ toPackage:package3.
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package3 includesPackagedClassNamed:#QWERTZ).
+
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self assert:(package3 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        self assert:(package1 isDirty).
+        self assert:(package2 isDirty).
+        self assert:(package3 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the class away from the classes current owner"
+            self assert:(aName := QWERTZ package) == package3 name.
+            QWERTZ setPackage:package2 name.
+            ChangeFaker classMovePackageChangeWithClass:QWERTZ oldPackageName:aName. 
+        "</simulatedChangeInBrowser>"
+        self assert:(package2 includesPackagedClassNamed:#QWERTZ).
+        self assert:(package3 includesPackagedClassNamed:#QWERTZ).
+
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.         
+        self shouldnt:(package3 packagedClassNamed:#QWERTZ) isInSmalltalk.         
+
+        self assert:(package2 isDirty).
+        self assert:(package3 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            self assert:(aName := QWERTZ package) == package2 name.
+            QWERTZ setPackage:package1 name.
+            ChangeFaker classMovePackageChangeWithClass:QWERTZ oldPackageName:aName. 
+        "</simulatedChangeInBrowser>"
+        self assert:(package2 includesPackagedClassNamed:QWERTZ).
+        self assert:(package1 includesPackagedClassNamed:QWERTZ).
+
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.    
+        self shouldnt:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.  
+
+        self assert:(package3 isDirty).
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        packageManager unloadPackageNamed:#'package3'.
+    ].
+!
+
+test_moveClass1
+    "Move QWERTZ class from package1 to package 2. Then move the class back."
+    | package1 aName  |
+    [
+        package1 :=  packageManager newPackageNamed:#'package1'.
+
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the class away from the classes current owner"
+            self assert:(aName := QWERTZ package) == defaultPackage name.
+            QWERTZ setPackage:package1 name.
+            self should:[ChangeFaker classMovePackageChangeWithClass:QWERTZ oldPackageName:aName] raise:Error.
+        "</simulatedChangeInBrowser>"
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+    ].
+!
+
+test_moveMethod1
+    "moving classes via change notification is now deprecated as i found it best to try and seperate
+    the functionality on Smalltalk and the functionality of package handling.
+    "
+    "Move QWERTZ class from package1 to package 2. Then move the class back."
+    | package1 aName  theMethod methodOwnedClass|
+    [
+        package1 :=  packageManager newPackageNamed:#'package1'.
+        theMethod :=(QWERTZ compiledMethodAt:#'aDummyMethod').
+        methodOwnedClass := QWERTZ.
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the method away from the classes current owner"
+            self assert:(aName := theMethod package) == defaultPackage name.
+            theMethod setPackage:package1 name.
+            self should:[ChangeFaker methodMovePackageChangeWithMethod:theMethod class:methodOwnedClass oldPackageName:aName.]
+                    raise:Error.
+        "</simulatedChangeInBrowser>"
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+    ].
+! !
+
+!PackageSmalltalkManipulationTestCases methodsFor:'test - removing'!
+
+testClassRemove
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+     | packagedClass packageTestCases|
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager workingPackage:packageTestCases.
+
+        self createClassNamed:#QWERTZ2.
+
+        self assert:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (packageManager workingPackage packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+
+        self shouldnt:(packagedClass isInSmalltalk).
+        self assert:(packageManager workingPackage includesPackagedClassNamed:#QWERTZ2).
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'packageTestCases'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testClassRemove2
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+    "WARNING!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! DONT correct during the debugger otherwise changes made could be removed!!!!!!"
+     | packagedClass packageTestCases packagedMethod |
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager workingPackage:packageTestCases.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+
+        self assert:(packageTestCases includesPackagedClassNamed:#QWERTZ2).
+        self assert:(packageTestCases definesSelector:#'testBasicMethodCreation' forClassNamed:#QWERTZ2).
+        packagedClass := (packageTestCases packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package still retains it!!"
+        self assert:(packageTestCases includesPackagedClassNamed:#QWERTZ2).
+        self assert:(packageTestCases definesSelector:#'testBasicMethodCreation' forClassNamed:#QWERTZ2).
+        self shouldnt:(packagedClass isInSmalltalk).
+
+        "test that the METHOD is removed from Smalltalk BUT the package still retains it!!"
+        packagedMethod := (packageTestCases packagedMethodNamed:#'testBasicMethodCreation' forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod notNil).
+        self shouldnt:(packagedMethod isInSmalltalk).
+        
+
+    ] ensure:[
+        packageManager workingPackage:packageManager defaultPackage.
+        packageManager unloadPackageNamed:#'packageTestCases'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testClassRemove3
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+    "WARNING!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! DONT correct during the debugger otherwise changes made could be removed!!!!!!"
+     | packagedClass package1 package2 packagedMethod1 packagedMethod2 method1 method2 |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        method2 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation2.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+        "This blocks method2 from package1"
+        packageManager moveMethod:method2 toPackage:package2.
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2). 
+        "package1 stores method2 as blocked"
+        self shouldnt:(package1 definesSelector:method2 name forClassNamed:#QWERTZ2). 
+
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2). 
+        self assert:packagedClass notNil.    
+        self assert:(packagedClass isInSmalltalk).
+
+        "Package2 should NOT define the class QWERTZ2 but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package2 definesSelector:method2 name forClassNamed:#QWERTZ2).
+        packagedMethod2 := (package2 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod2 isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package1 definesSelector:#'testBasicMethodCreation' forClassNamed:#QWERTZ2).
+        self shouldnt:(packagedClass isInSmalltalk).
+
+        "test that the METHOD is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2).
+        packagedMethod1 := (package1 packagedMethodNamed:method1 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:method2 name forClassNamed:#QWERTZ2).
+        packagedMethod2 := (package2 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod2 notNil).
+        self shouldnt:(packagedMethod2 isInSmalltalk).
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testClassRemove4
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+     | packagedClass package1 package2 packagedMethod1 packagedMethod2 method1 method2 |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+        method2 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation2.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+        "This blocks method2 from package1"
+        packageManager addMethod:method2 toPackage:package2.
+        "method2 has been overridden in package1 by package2!!"
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2).
+        self assert:(packagedClass isInSmalltalk).
+
+        "Method1 in package1 "
+        self assert:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2). 
+        self assert:(package1 isDependentOnMethodNamed:method1 name forClassNamed:#QWERTZ2). 
+        packagedMethod1 := (package1 packagedMethodNamed:method1 name forClassNamed:#QWERTZ2).  
+        self assert:(packagedMethod1 isInSmalltalk).
+
+        "Method2 in package1 is overridden but still own's a copy which it is not dependant on"
+        self assert:(package1 definesSelector:method2 name forClassNamed:#QWERTZ2). 
+        self shouldnt:(package1 isDependentOnMethodNamed:method2 name forClassNamed:#QWERTZ2). 
+        packagedMethod2 := (package1 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).  
+        self shouldnt:(packagedMethod2 isInSmalltalk).
+
+        "Package2 should NOT define the class QWERTZ2 but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package2 definesSelector:method2 name forClassNamed:#QWERTZ2).
+        packagedMethod2 := (package2 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod2 isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2).
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2).  
+        self shouldnt:(packagedClass isInSmalltalk).
+
+        "test that the METHOD1 is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2).
+        self shouldnt:(package1 isDependentOnMethodNamed:method1 name forClassNamed:#QWERTZ2). 
+        packagedMethod1 := (package1 packagedMethodNamed:method1 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+        "This that method2 is still overridden but still own's a copy which it is not dependant on"
+        self assert:(package1 definesSelector:method2 name forClassNamed:#QWERTZ2). 
+        self shouldnt:(package1 isDependentOnMethodNamed:method2 name forClassNamed:#QWERTZ2). 
+        packagedMethod2 := (package1 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod2 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:method2 name forClassNamed:#QWERTZ2).
+        self shouldnt:(package2 isDependentOnMethodNamed:method2 name forClassNamed:#QWERTZ2). 
+        packagedMethod2 := (package2 packagedMethodNamed:method2 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod2 notNil).
+        self shouldnt:(packagedMethod2 isInSmalltalk).
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testClassRemove5
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+     | packagedClass package1 package2 method1 |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2). 
+        self assert:packagedClass notNil.    
+        self assert:(packagedClass isInSmalltalk).
+        self assert:(packagedClass packagedMethods size == 2).
+
+        packageManager addClass:QWERTZ2 toPackage:package2.
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2). 
+        self assert:packagedClass notNil.    
+        self assert:(packagedClass packagedMethods size == 2).
+        packagedClass packagedMethods do:[:aPackagedMethod |
+            self assert:(aPackagedMethod isInSmalltalk).
+        ].
+        self shouldnt:(packagedClass isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        "package1 still has all the information it had before"
+        packagedClass := (package1 packagedClassNamed:#QWERTZ2). 
+        self assert:packagedClass notNil.    
+        self assert:(packagedClass packagedMethods size == 2).
+        packagedClass packagedMethods do:[:aPackagedMethod |
+            self shouldnt:(aPackagedMethod isInSmalltalk).
+        ].
+        self shouldnt:(packagedClass isInSmalltalk).
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        packagedClass := (package2 packagedClassNamed:#QWERTZ2). 
+        self assert:packagedClass notNil.    
+        self assert:(packagedClass packagedMethods size == 2).
+        packagedClass packagedMethods do:[:aPackagedMethod |
+            self shouldnt:(aPackagedMethod isInSmalltalk).
+        ].
+        self shouldnt:(packagedClass isInSmalltalk).
+
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRemove
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+    "WARNING!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! DONT correct during the debugger otherwise changes made could be removed!!!!!!"
+     | package1 package2 packagedMethod1 method1  |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+        "This blocks method1 from package1"
+        packageManager moveMethod:method1 toPackage:package2.
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2). 
+        "package1 stores method2 as blocked"
+        self shouldnt:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2). 
+
+
+        "Package2 should NOT define the class QWERTZ2 but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package2 definesSelector:method1 name forClassNamed:#QWERTZ2).
+        packagedMethod1 := (package2 packagedMethodNamed:method1 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[        
+            QWERTZ2 removeSelector:method1 name.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2).
+        self shouldnt:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        "test that the METHOD is still blocked in package1!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        packagedMethod1 := (package2 packagedMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRemove2
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+    "WARNING!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! DONT correct during the debugger otherwise changes made could be removed!!!!!!"
+     | package1 package2 packagedMethod1 method1  |
+
+    [
+        "prerequisites"
+        self assert:(Smalltalk classNamed:#QWERTZ2) isNil.
+
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.   
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 compiledMethodAt:#testBasicMethodCreation.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+        self assert:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2). 
+        self assert:(package1 isDependentOnMethodNamed:method1 name forClassNamed:#QWERTZ2). 
+
+        "This blocks method1 from package1"
+        packageManager addMethod:method1 toPackage:package2.
+
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2). 
+        "package1 stores method2 as overridden"
+        self assert:(package1 definesSelector:method1 name forClassNamed:#QWERTZ2). 
+        self shouldnt:(package1 isDependentOnMethodNamed:method1 name forClassNamed:#QWERTZ2). 
+
+
+        "Package2 should NOT define the class QWERTZ2 but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package2 definesSelector:method1 name forClassNamed:#QWERTZ2).
+        packagedMethod1 := (package2 packagedMethodNamed:method1 name forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[        
+            QWERTZ2 removeSelector:method1 name.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:#QWERTZ2).
+        self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2). 
+        self shouldnt:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2). 
+
+        "test that the METHOD is still defined but overridden in package1!!"
+
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self shouldnt:(package2 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2). 
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        packagedMethod1 := (package2 packagedMethodNamed:#testBasicMethodCreation forClassNamed:#QWERTZ2).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+
+    ] ensure:[
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[
+                (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+    ]
+!
+
+testMethodRemoveClassSide
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+     | package1 package2 packagedMethod1 method1  theClassName  workingPackage |
+    [
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.
+        workingPackage := packageManager packageNamed:QWERTZ2 package.
+        self createMethodFor:QWERTZ2 class source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 class source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 class compiledMethodAt:#testBasicMethodCreation.
+        theClassName := (QWERTZ2 class name asSymbol).
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+
+        self assert:(package1 includesPackagedClassNamed:theClassName). 
+        self assert:(package1 definesSelector:method1 name forClassNamed:theClassName). 
+
+
+        "This blocks method1 from package1"       
+        packageManager moveMethod:method1 toPackage:package2.
+        self assert:(package1 includesPackagedClassNamed:theClassName). 
+        "package1 stores method2 as blocked"
+        self shouldnt:(package1 definesSelector:method1 name forClassNamed:theClassName). 
+
+
+        "Package2 should NOT define the class QWERTZ2 class but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:theClassName).
+        self assert:(package2 definesSelector:method1 name forClassNamed:theClassName).
+        packagedMethod1 := (package2 packagedMethodNamed:method1 name forClassNamed:theClassName).
+        self assert:(packagedMethod1 isInSmalltalk).
+
+        (Smalltalk classNamed:theClassName) ifNotNil:[        
+           (Smalltalk classNamed:theClassName) removeSelector:method1 name.
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:theClassName).
+        self shouldnt:(package1 definesSelector:#testBasicMethodCreation forClassNamed:theClassName).
+
+        "test that the METHOD is still blocked in package1!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:theClassName).
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:theClassName).
+        packagedMethod1 := (package2 packagedMethodNamed:#testBasicMethodCreation forClassNamed:theClassName).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+        (Smalltalk classNamed:theClassName) ifNotNil:[ 
+            (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+    ]
+!
+
+testMethodRemoveClassSide2
+    "Changes caught my the manager should not affect the packages state.
+    So a class removal should remove the class in Smalltalk yet the package should still keep hold of the
+    entire definition INCLUDING the methods it requires!!"
+    "This one tests if the methods are still kept within the pacakge as packagedMethods"
+     | package1 package2 packagedMethod1 method1  theClassSideName |
+
+    [
+        "prerequisites"
+        self assert:(Smalltalk classNamed:#QWERTZ2) isNil.
+
+        package1 := packageManager newPackageNamed:#'package1'.
+        package2 := packageManager newPackageNamed:#'package2'.
+
+        self createClassNamed:#QWERTZ2.   
+        theClassSideName := QWERTZ2 class name asSymbol.
+        self createMethodFor:QWERTZ2 class source:'testBasicMethodCreation 1 + 1'.
+        self createMethodFor:QWERTZ2 class source:'testBasicMethodCreation2 1 + 1'.
+        method1 := QWERTZ2 class compiledMethodAt:#testBasicMethodCreation.
+
+        packageManager moveClass:QWERTZ2 toPackage:package1.
+        self assert:(package1 definesSelector:method1 name forClassNamed:theClassSideName). 
+        self assert:(package1 isDependentOnMethodNamed:method1 name forClassNamed:theClassSideName). 
+
+        "This blocks method1 from package1"
+        packageManager addMethod:method1 toPackage:package2.
+
+        self assert:(package1 includesPackagedClassNamed:theClassSideName). 
+        "package1 stores method2 as overridden"
+        self assert:(package1 definesSelector:method1 name forClassNamed:theClassSideName). 
+        self shouldnt:(package1 isDependentOnMethodNamed:method1 name forClassNamed:theClassSideName). 
+
+
+        "Package2 should NOT define the class but should define method2 which should also be in Smalltalk!!"
+        self shouldnt:(package2 includesPackagedClassNamed:theClassSideName).
+        self assert:(package2 definesSelector:method1 name forClassNamed:theClassSideName).
+        packagedMethod1 := (package2 packagedMethodNamed:method1 name forClassNamed:theClassSideName).
+        self assert:(packagedMethod1 isInSmalltalk).
+
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[        
+            QWERTZ2 class removeSelector:method1 name. 
+        ].
+        "test that the CLASS is removed from Smalltalk BUT the package1 still retains it!!"
+        self assert:(package1 includesPackagedClassNamed:theClassSideName).
+        self assert:(package1 definesSelector:#testBasicMethodCreation forClassNamed:theClassSideName). 
+        self shouldnt:(package1 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:theClassSideName). 
+
+        "test that the METHOD is still defined but overridden in package1!!"
+
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:theClassSideName).
+        self shouldnt:(package2 isDependentOnMethodNamed:#testBasicMethodCreation forClassNamed:theClassSideName). 
+
+        "test that the METHOD is removed from Smalltalk BUT the package2 still retains it!!"
+        self assert:(package2 definesSelector:#testBasicMethodCreation forClassNamed:theClassSideName).
+        packagedMethod1 := (package2 packagedMethodNamed:#testBasicMethodCreation forClassNamed:theClassSideName).
+        self assert:(packagedMethod1 notNil).
+        self shouldnt:(packagedMethod1 isInSmalltalk).
+
+
+    ] ensure:[
+        (Smalltalk classNamed:#QWERTZ2) ifNotNil:[
+                (Smalltalk classNamed:#QWERTZ2) removeFromSystem.
+        ].
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+    ]
+! !
+
+!PackageSmalltalkManipulationTestCases class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageSmalltalkManipulationTestCases.st,v 1.6 2006/01/10 09:31:41 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackageTestCases.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,403 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+AbstractTestCases subclass:#PackageTestCases
+	instanceVariableNames:'packageManager workingPackage'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package'
+!
+
+!PackageTestCases class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+         (james@miraculix)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+history
+    "Created: / 24.1.2003 / 16:15:21 / james"
+! !
+
+!PackageTestCases methodsFor:'initialize / release'!
+
+initialize
+
+    packageManager ifNil:[
+        packageManager := self packageManager.
+    ].
+
+    workingPackage ifNil:[
+        workingPackage := packageManager workingPackage.
+    ].
+!
+
+setUp
+    "common setup - invoked before testing"
+    super setUp.
+    self setUpUsedClasses.
+!
+
+setUpAllForQWERTY
+    | class copyQWERTYDic|
+    
+    (class := Smalltalk at:#QWERTY) ifNil:[
+        self createClassNamed:#QWERTY. 
+        (class := Smalltalk at:#QWERTY).
+    ].
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTY source:'aDummyMethod3 1 + 1.'.
+    ].
+
+    copyQWERTYDic := QWERTY methodDictionary copy.
+    copyQWERTYDic removeKey:#aDummyMethod.
+    copyQWERTYDic removeKey:#aDummyMethod2.
+    copyQWERTYDic removeKey:#aDummyMethod3.
+    copyQWERTYDic keysAndValuesDo:[:key :value |
+       QWERTY methodDictionary removeKey:key.
+    ].
+
+
+    packageManager moveClass:QWERTY toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:workingPackage.
+!
+
+setUpAllForQWERTZ
+    | class copyQWERTZDic|
+    (class := Smalltalk at:#QWERTZ) ifNil:[
+        self createClassNamed:#QWERTZ.
+        (class := Smalltalk at:#QWERTZ)
+    ].
+
+
+    (class compiledMethodAt:#aDummyMethod) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod2) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod2 1 + 1.'.
+    ].
+    (class compiledMethodAt:#aDummyMethod3) ifNil:[
+        self createMethodFor:QWERTZ source:'aDummyMethod3 1 + 1.'.
+    ].
+
+    copyQWERTZDic := QWERTZ methodDictionary copy.
+    copyQWERTZDic removeKey:#aDummyMethod.
+    copyQWERTZDic removeKey:#aDummyMethod2.
+    copyQWERTZDic removeKey:#aDummyMethod3.
+    copyQWERTZDic keysAndValuesDo:[:key :value |
+       QWERTZ methodDictionary removeKey:key.
+    ].
+
+    packageManager moveClass:QWERTZ toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod) toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod2) toPackage:workingPackage.
+    packageManager moveMethod:(class compiledMethodAt:#aDummyMethod3) toPackage:workingPackage.
+!
+
+setUpUsedClasses
+    "common setup - invoked before testing"
+    |  |
+    self setUpAllForQWERTZ.
+    self setUpAllForQWERTY.                
+!
+
+tearDown
+    "common cleanup - invoked after testing"
+
+    "move class package to where it was"
+    super tearDown
+! !
+
+!PackageTestCases methodsFor:'test - accessing'!
+
+test_classNames
+    | packageTestCases |
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager moveClass:QWERTZ toPackage:packageTestCases.
+        packageManager moveClass:QWERTY toPackage:packageTestCases.
+
+        self assert:(packageTestCases classNames includesAll:#(#QWERTZ #QWERTY)).
+        self assert:(packageTestCases isDirty).
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_isDirty
+    | packageTestCases |
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageManager moveClass:QWERTZ toPackage:packageTestCases.
+        self assert:(packageTestCases isDirty).
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+! !
+
+!PackageTestCases methodsFor:'test - adding and removing'!
+
+test_addMethod
+    | packageTestCases |
+
+    [
+        "setting up the test"
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+
+        packageManager moveClass:QWERTZ toPackage:packageTestCases.
+        packageTestCases isDirty:false.   "i am telling it a fib here "
+        "prerequisites to test"
+        self assert:((packageTestCases blockedMethodsAtClassNamed:#QWERTZ) size == 0).
+        self shouldnt:(packageTestCases isDirty).
+        self assert:(packageTestCases isInstalled).
+
+        "add a method for QWERTZ and test that the package adds a blocked method, as
+        the method is from the workingPackage "
+        self createMethodFor:QWERTZ source:'aDummyMethodTest_test_addMethod2 1 + 1.'.   
+        self assert:((packageTestCases blockedMethodsAtClassNamed:#QWERTZ) size == 1).
+        self assert:(packageTestCases isInstalled).
+        self shouldnt:(packageTestCases isDirty).
+
+        self assert:(QWERTZ compiledMethodAt:#aDummyMethodTest_test_addMethod2) package == workingPackage name.
+
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+
+        QWERTZ methodDictionary removeKey:#aDummyMethodTest_test_addMethod2 ifAbsent:["do nothing"].
+    ]
+!
+
+test_addMethod2
+    "
+    check that when a method is added to a new package and then added back to the old package
+    that 
+    1) the oldPackage has got the method and has not got any overriddenMethods
+    2) the 'newPackage' has got the method registered as an overriddenMethod
+    "
+    | packageTestCases packageTestCases2 aMethodToOverride|
+
+    [
+        "setting up the test"
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        packageTestCases2 := packageManager newPackageNamed:#'packageTestCases2'.
+
+        packageManager moveClass:QWERTZ toPackage:packageTestCases.
+        packageTestCases isDirty:false.   "i am telling it a fib here "
+        "prerequisites to test"
+        self shouldnt:(packageTestCases isDirty).
+        aMethodToOverride :=  QWERTZ methodDictionary values first.
+        "add a method for QWERTZ and test that the package adds a blocked method, as
+        the method is from the workingPackage "
+
+        packageManager addMethod:aMethodToOverride toPackage:packageTestCases2.
+
+       "Tests for packageTestCases"
+        self assert:(packageTestCases overriddenChangesIncludesMethodName:aMethodToOverride name forClassNamed:#QWERTZ).
+        self shouldnt:(packageTestCases isDirty).  "it is overridden not dirty"
+
+        "Tests for packageTestCases2"
+        self assert:(packageTestCases2 definesSelector:aMethodToOverride name forClassNamed:#QWERTZ).
+        self assert:(packageTestCases2 isDirty).  "was not there before so is dirty!!"
+        self shouldnt:(packageTestCases2 overriddenChangesIncludesMethodName:aMethodToOverride name forClassNamed:#QWERTZ).
+
+        packageManager addMethod:aMethodToOverride toPackage:packageTestCases.
+
+       "Tests for packageTestCases"
+        self assert:(packageTestCases isDirty).  "a new version of the method is added!!"
+        self shouldnt:(packageTestCases overriddenChangesIncludesMethodName:aMethodToOverride name forClassNamed:#QWERTZ).
+
+        "Tests for packageTestCases2"
+        self assert:(packageTestCases2 overriddenChangesIncludesMethodName:aMethodToOverride name forClassNamed:#QWERTZ).
+        self assert:(packageTestCases2 isDirty).
+
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases2.
+        ].
+
+        QWERTZ methodDictionary removeKey:#aDummyMethodTest_test_addMethod2 ifAbsent:["do nothing"].
+    ]
+!
+
+test_moveMethod
+    | packageTestCases method1 method2|
+    "prerequisites to test"
+
+    [
+        packageTestCases := packageManager newPackageNamed:#'packageTestCases'.
+        method1 := (QWERTZ compiledMethodAt:#aDummyMethod).
+        method2 := (QWERTZ compiledMethodAt:#aDummyMethod2).
+
+        self shouldnt:(packageTestCases isDirty).
+
+        packageManager moveMethod:method1 toPackage:packageTestCases.
+        packageManager moveMethod:method2 toPackage:packageTestCases.
+
+        self assert:(packageTestCases isDirty).
+        self assert:(packageTestCases isInstalled).
+        self assert:(packageTestCases definesSelector:method1 name forClassNamed:method1 mclass name).
+        self assert:(packageTestCases definesSelector:method2 name forClassNamed:method2 mclass name).
+
+    ] ensure:
+    [
+        packageTestCases ifNotNil:[
+            packageManager removePackage:packageTestCases.
+        ].
+    ]
+!
+
+test_packagedClass_isInSmalltalk
+    | package1 package2|
+    "prerequisites to test"
+
+    [
+        package1 := Package packageManager newPackageNamed:#'package1'.
+        package2 := Package packageManager newPackageNamed:#'package2'. 
+
+        packageManager moveClassNamed:#QWERTZ fromPackage:workingPackage toPackage:package1.
+        self assert:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+
+        packageManager addClass:QWERTZ toPackage:package2.
+
+        self assert:(package2 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        self shouldnt:(package1 packagedClassNamed:#QWERTZ) isInSmalltalk.
+        
+        (package2 packagedClassNamed:#QWERTZ) .
+
+    ] ensure:
+    [
+        package1 ifNotNil:[
+            packageManager unloadPackageNamed:#'package1'.
+        ].
+        package2 ifNotNil:[
+            packageManager unloadPackageNamed:#'package2'.
+        ].
+    ]
+! !
+
+!PackageTestCases methodsFor:'test - moving'!
+
+obsolete_test_moveMethod1
+    "moving classes via change notification is now deprecated as i found it best to try and seperate
+    the functionality on Smalltalk and the functionality of package handling.
+    "
+    "Move QWERTZ class from package1 to package 2. Then move the class back."
+    | package1 package2 aName  theMethod methodOwnedClass|
+    [
+        package1 :=  packageManager newPackageNamed:#'package1'.
+        package2 :=  packageManager newPackageNamed:#'package2'.
+        theMethod :=(QWERTZ compiledMethodAt:#'aDummyMethod').
+        methodOwnedClass := QWERTZ.
+
+        packageManager addMethod:theMethod toPackage:package1.
+
+        self assert:(package1 definesSelector:#'aDummyMethod' forClassNamed:#QWERTZ).
+        self shouldnt:(package2 definesSelector:#'aDummyMethod' forClassNamed:#QWERTZ).
+
+        self assert:(package1 isDirty).
+        self shouldnt:(package2 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the method away from the classes current owner"
+            self assert:(aName := theMethod package) == package1 name.
+            theMethod setPackage:package2 name.
+            ChangeFaker methodMovePackageChangeWithMethod:theMethod class:methodOwnedClass oldPackageName:aName.
+        "</simulatedChangeInBrowser>"
+        self assert:(package1 definesSelector:#'aDummyMethod' forClassNamed:#QWERTZ).
+        self assert:(package2 definesSelector:#'aDummyMethod' forClassNamed:#QWERTZ).
+
+        self assert:(package2 packagedMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ) isInSmalltalk.      
+        self shouldnt:(package1 packagedMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ) isInSmalltalk.     
+
+        self assert:(package2 isDependentOnMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ).     
+        self shouldnt:(package1 isDependentOnMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ).       
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+        "<simulatedChangeInBrowser>"
+            "This change always moves the method away from the classes current owner"
+            self assert:(aName := theMethod package) == package2 name.
+            theMethod setPackage:package1 name.
+            ChangeFaker methodMovePackageChangeWithMethod:theMethod class:methodOwnedClass oldPackageName:aName.
+        "</simulatedChangeInBrowser>"
+        self assert:(package1 isDependentOnMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ).     
+        self shouldnt:(package2 isDependentOnMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ).       
+
+        self shouldnt:(package2 packagedMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ) isInSmalltalk.      
+        self assert:(package1 packagedMethodNamed:#'aDummyMethod' forClassNamed:#QWERTZ) isInSmalltalk.
+
+        self assert:(package2 isDirty).
+        self assert:(package1 isDirty).
+
+        packageManager addClass:QWERTZ toPackage:defaultPackage.
+    ] ensure:[
+        packageManager unloadPackageNamed:#'package1'.
+        packageManager unloadPackageNamed:#'package2'.
+    ].
+! !
+
+!PackageTestCases class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackageTestCases.st,v 1.5 2006/01/10 09:31:48 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PackagesInstalled.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,163 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#PackagesInstalled
+	instanceVariableNames:'collection workingPackage'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+!PackagesInstalled class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PackagesInstalled class methodsFor:'instance creation'!
+
+new
+    ^ self basicNew initialize.
+!
+
+workingPackage:aPackage
+    ^ self new workingPackage:aPackage
+! !
+
+!PackagesInstalled methodsFor:'* As yet uncategorized *'!
+
+allPackages
+    ^ collection copy at:#workinPackage put:workingPackage; yourself.
+!
+
+select:aBlock 
+    ^ self allPackages values select:aBlock
+! !
+
+!PackagesInstalled methodsFor:'accessing'!
+
+workingPackage
+    "return the value of the instance variable 'currentPackage' (automatically generated)"
+
+    ^ workingPackage
+!
+
+workingPackage:something
+    "set the value of the instance variable 'currentPackage' (automatically generated)"
+
+    workingPackage := something.
+! !
+
+!PackagesInstalled methodsFor:'adding & removing'!
+
+atKey:aSymbol 
+    
+    ^ collection at:aSymbol
+!
+
+pop
+    collection removeKey:collection last key
+!
+
+pop:aNumber 
+
+    aNumber timesRepeat:[ self pop].
+!
+
+popAt:aKey 
+    collection removeKey:aKey.
+!
+
+popAt:aKey ifAbsent:aBlock
+    collection removeKey:aKey ifAbsent:aBlock.
+!
+
+pull
+    ^ self pop
+!
+
+pull:aNumber
+    | col |
+    col :=  collection last:aNumber.
+    self pop:aNumber.
+    ^ col
+!
+
+pullAt:aKey 
+    ^ collection removeKey:aKey.
+!
+
+pullAt:aKey ifAbsent:aBlock
+    ^ collection removeKey:aKey ifAbsent:aBlock.
+!
+
+push:aPackage 
+    
+    ^ collection at:aPackage name put:aPackage
+!
+
+removeKey:aSymbol 
+    
+    ^ collection removeKey:aSymbol
+!
+
+top
+    ^ collection last value
+! !
+
+!PackagesInstalled methodsFor:'enumerating'!
+
+do:aBlock 
+    "goes through all the objects in the collection"
+    aBlock value:workingPackage.
+    collection reverseDo:[:anAssociation | aBlock value:anAssociation value]
+! !
+
+!PackagesInstalled methodsFor:'initialization'!
+
+initialize
+    collection := OrderedDictionary new.
+! !
+
+!PackagesInstalled methodsFor:'queries'!
+
+includes:aPackage
+    ^ (aPackage == workingPackage or:[(collection includesValue:aPackage)]).
+!
+
+includesKey:aKey
+    ^ (collection includesKey:aKey)
+!
+
+isEmpty
+    ^ collection isEmpty
+! !
+
+!PackagesInstalled class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PackagesInstalled.st,v 1.2 2006/01/10 09:32:15 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__Prerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,124 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#Prerequisite
+	instanceVariableNames:'name ifFailedString'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Prerequisite'
+!
+
+!Prerequisite class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!Prerequisite class methodsFor:'instance creation'!
+
+named:aName ifFail:anActionBlock
+    ^ self basicNew name:aName ifFailedAction:anActionBlock
+!
+
+named:aName ifFailString:aString
+    ^ self basicNew name:aName ifFailedString:aString
+! !
+
+!Prerequisite methodsFor:'accessing'!
+
+ifFailedString
+    "return the value of the instance variable 'ifFailedString' (automatically generated)"
+
+    ^ ifFailedString
+!
+
+ifFailedString:something
+    "set the value of the instance variable 'ifFailedString' (automatically generated)"
+
+    ifFailedString := something.
+!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+
+    ^ name
+!
+
+name:something
+    "set the value of the instance variable 'name' (automatically generated)"
+
+    name := something.
+!
+
+name:nameArg ifFailedString:ifFailedStringArg 
+    "set instance variables (automatically generated)"
+
+    name := nameArg.
+    ifFailedString := ifFailedStringArg.
+! !
+
+!Prerequisite methodsFor:'evaluation'!
+
+evaluate
+    (self testCondition) ifFalse:[
+        self evaluateIfFailedAction.
+    ]
+
+
+
+
+
+
+
+
+
+
+
+!
+
+evaluateIfFailedAction
+    Compiler evaluate:ifFailedString
+!
+
+testCondition
+    self subclassResponsibility
+! !
+
+!Prerequisite methodsFor:'queries'!
+
+isClassPrerequisite
+    ^ false
+!
+
+isPackagePrerequisite
+    ^ false
+! !
+
+!Prerequisite class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/Prerequisite.st,v 1.2 2006/01/10 09:32:17 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__PrerequisiteCollection.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,103 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Collection subclass:#PrerequisiteCollection
+	instanceVariableNames:'collection'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Prerequisite'
+!
+
+!PrerequisiteCollection class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!PrerequisiteCollection class methodsFor:'instance creation'!
+
+new
+    ^ self basicNew initialize
+! !
+
+!PrerequisiteCollection methodsFor:'adding & removing'!
+
+add:anObject 
+    ^ collection add:anObject
+!
+
+addFirst:anObject 
+    ^ collection addFirst:anObject
+!
+
+remove:anObject ifAbsent:aBlock 
+    ^ collection remove:anObject ifAbsent:aBlock 
+!
+
+removeIdentical:arg1 ifAbsent:aBlock 
+    ^ collection removeIdentical:arg1 ifAbsent:aBlock 
+!
+
+removeLast
+    ^ collection removeLast
+! !
+
+!PrerequisiteCollection methodsFor:'enumerating'!
+
+do:aOneArgBlock 
+    ^ collection do:aOneArgBlock
+!
+
+reverseDo:aOneArgBlock 
+    ^ collection reverseDo:aOneArgBlock
+! !
+
+!PrerequisiteCollection methodsFor:'evaluation'!
+
+evaluate
+    self do:[:aPrerequisite |
+        aPrerequisite evaluate.
+    ].
+
+! !
+
+!PrerequisiteCollection methodsFor:'growing'!
+
+grow:anInteger 
+    ^ collection grow:anInteger 
+! !
+
+!PrerequisiteCollection methodsFor:'initialize'!
+
+initialize
+    collection := OrderedCollection new.
+! !
+
+!PrerequisiteCollection class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PrerequisiteCollection.st,v 1.2 2006/01/10 09:25:29 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__StxPackageFileHandler.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,207 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+PackageHandler subclass:#StxPackageFileHandler
+	instanceVariableNames:'package filename'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Handlers'
+!
+
+!StxPackageFileHandler class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!StxPackageFileHandler class methodsFor:'instance creation'!
+
+forFilename:aFilename
+
+    (self isFileBase:aFilename) ifTrue:[
+        ^ StxBasePackageHandler forFilename:aFilename
+    ].
+    (self isFileVersion1:aFilename) ifTrue:[
+        ^ Version1 forFilename:aFilename
+    ].
+
+    self error:'File type unknown'
+!
+
+forPackage:aPackage 
+    ^ self basicNew package:aPackage
+!
+
+openStxPackageFormat:aFormat
+    ^ ((StxPackageFileReader) version:aFormat) new
+!
+
+version:aVersionNumber
+    aVersionNumber == 0 ifTrue:[
+        ^ StxBasePackageHandler.
+    ].
+
+    aVersionNumber == 1 ifTrue:[
+        ^ Version1.
+    ].
+    self error:'Version unknown'
+! !
+
+!StxPackageFileHandler class methodsFor:'accessing-globals'!
+
+packageManager
+    ^ PackageManager smalltalkPackageManager
+! !
+
+!StxPackageFileHandler class methodsFor:'queries'!
+
+isFileBase:aFilename
+    ^ false
+!
+
+isFileVersion1:aFilename
+    ^ true
+! !
+
+!StxPackageFileHandler methodsFor:'accessing'!
+
+filename
+    "return the value of the instance variable 'filename' (automatically generated)"
+
+    ^ filename
+!
+
+filename:something
+    "set the value of the instance variable 'filename' (automatically generated)"
+
+    filename := something.
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:something
+    "set the value of the instance variable 'package' (automatically generated)"
+
+    package := something.
+!
+
+version
+    ^ 1
+! !
+
+!StxPackageFileHandler methodsFor:'api'!
+
+fileInFrom:arg1 notifying:arg2 passChunk:arg3 single:arg4 silent:arg5 
+!
+
+installPackageIn:aPackageManager 
+    ^ (self newPackageReader) installPackageIn:aPackageManager 
+!
+
+loadPackageIn:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+savePackageAs:arg 
+
+    ^ (self newPackageWriter) savePackageAs:arg 
+
+!
+
+savePackageOn:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+uninstallPackageFrom:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+unloadPackageIn:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+! !
+
+!StxPackageFileHandler methodsFor:'checks'!
+
+canReadFilename:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+checkOkToInstall:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+!
+
+checkOkToUninstall:arg 
+    "raise an error: must be redefined in concrete subclass(es)"
+
+    ^ self subclassResponsibility
+! !
+
+!StxPackageFileHandler methodsFor:'factory'!
+
+newPackageReader
+    ^ (self packageReaderClass version:self version) new 
+            filename:filename;
+            package:package.
+!
+
+newPackageWriter
+    ^ (self packageWriterClass version:self version) new 
+            package:package.
+
+
+
+
+!
+
+packageReaderClass
+    ^ StxPackageFileReader
+!
+
+packageWriterClass
+    ^ StxPackageFileWriter
+! !
+
+!StxPackageFileHandler class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileHandler.st,v 1.2 2006/01/10 09:32:05 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__StxPackageFileReader.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,345 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#StxPackageFileReader
+	instanceVariableNames:'handler stream'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Handlers'
+!
+
+Object subclass:#Version1
+	instanceVariableNames:'filename package'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:StxPackageFileReader
+!
+
+!StxPackageFileReader class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!StxPackageFileReader class methodsFor:'instance creation'!
+
+forFilename:aFilename
+
+    (self isFileVersion1:aFilename) ifTrue:[
+        ^ Version1 forFilename:aFilename
+    ].
+
+    self error:'File type unknown'
+!
+
+forPackage:aPackage 
+
+    ^ (self version:1) forPackage:aPackage 
+!
+
+version:aVersionNumber
+
+    aVersionNumber == 1 ifTrue:[
+        ^ Version1.
+    ].
+    self error:'Version unknown'
+! !
+
+!StxPackageFileReader class methodsFor:'queries'!
+
+isFileBase:aFilename
+    ^ false
+!
+
+isFileVersion1:aFilename
+    ^ true
+! !
+
+!StxPackageFileReader::Version1 class methodsFor:'globals'!
+
+smalltalkPackageManager
+    ^ PackageManager smalltalkPackageManager
+! !
+
+!StxPackageFileReader::Version1 class methodsFor:'instance creation'!
+
+forFilename:aPackage
+    ^ self basicNew filename:aPackage
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'accessing'!
+
+filename
+    "return the value of the instance variable 'filename' (automatically generated)"
+
+    ^ filename
+!
+
+filename:something
+    "set the value of the instance variable 'filename' (automatically generated)"
+
+    filename := something.
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:something
+    "set the value of the instance variable 'package' (automatically generated)"
+
+    package := something.
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'api'!
+
+fileInFrom:aStream notifying:someone passChunk:passChunk single:single silent:beSilent 
+    "sent by a file browser or something similar"
+    | packageManager |
+
+    packageManager := PackageManager smalltalkPackageManager.
+    packageManager ifNil:[
+        self error: 'Error during fileIn'.
+        ^ self.
+    ].
+
+    package := (self getInitialPackageFromChunk:aStream nextChunk).
+    package ifNil:[
+        self error: 'Error during fileIn'.
+        ^ self.
+    ].
+
+    self package:package.
+    self 
+        basicInstallPackage:package 
+        fromStream:aStream 
+        in:self class smalltalkPackageManager.
+
+    packageManager addPackage:package.
+!
+
+installPackageIn:aPackageManager
+    (self checkOkToInstall:package).   "/ may produce errors
+    self basicInstallPackage:package in:aPackageManager.
+    ^ package
+!
+
+loadPackageIn:aPackageManager 
+
+    |aStream aPackage|
+    self canReadFilename:filename.
+
+    [
+        aStream := filename readStream.
+        aStream nextChunk.
+        aStream nextChunk.
+        aPackage := self getInitialPackageFromChunk:aStream nextChunk.
+    ] ensure:[aStream close].
+
+    self filename:filename.
+    aPackageManager addPackage:aPackage.
+    self package:aPackage.
+    aPackage packageHandler:self.
+    aPackage initializeLoaded.
+    ^ aPackage
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'checks'!
+
+canReadFilename:aFilename
+
+    aFilename isFilename ifFalse:[
+        ^ self error:aFilename printString, ' is not a filename so cannot be written to.'.
+    ].
+
+    aFilename directory exists ifFalse:[
+        ^ self error:aFilename directory printString, ' directory does not exist.'.
+    ].
+
+    aFilename exists ifFalse:[
+        ^ self error:aFilename printString, ' file does not exist'.
+    ].
+
+    (aFilename isDirectory not) ifFalse:[
+        ^ self error:aFilename printString, ' is a directory and cannot be read'.
+    ].
+!
+
+checkOkToInstall:aPackage
+    "check that aPackage is ok to install. Look for incompatibilities"
+
+    self canReadFilename:filename
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'helpers'!
+
+applyChange:aChange fromPackage:aPackage 
+    "apply change and make sure created objects are associated
+    with package"
+
+    | aMethod |
+    aChange isMethodChange ifTrue:[
+        aChange apply.
+"/        aMethod := ChangesHelper getCurrentMethodFromMethodChange:aChange.
+        aMethod := aChange changeMethod.
+        aMethod ifNil:[
+            self error:'Error during fileIn'.
+            ^ self.
+        ].
+
+        aMethod setPackage:aPackage name.
+        ^ self
+    ].
+
+    aChange apply
+!
+
+createPackagePath                                                    
+    " create the path name for the filename if it does not already exist"
+    ^ self createPathFor:package filename
+!
+
+createPathFor:aFilename
+    " create the path name for the filename if it does not already exist"
+    ^ aFilename directory makeDirectory.
+!
+
+openReadStreamStreamOn:aFilename andDo:aOneArgBlockWithAnExpectedStream
+    | aStream |
+    [
+        aStream := aFilename readStream.
+        aOneArgBlockWithAnExpectedStream value:aStream
+    ] ensure:[
+        aStream close
+    ]
+
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'installation / uninstallation'!
+
+basicInstallPackage:aPackage fromStream:aStream in:aPackageManager
+    "install a package"
+    | changeSet |
+    aPackage prerequisites evaluate.
+    aPackage preInstallScript evaluate.
+
+    changeSet := ChangeSet fromStream:aStream.  
+    changeSet do:[:aChange |
+        self applyChange:aChange fromPackage:aPackage.
+    ].
+    self validateInstallation. "/ may produce errors
+    aPackage initializeInstalled.
+
+"/    aPackage isInstalled:true. 
+    aPackage postInstallScript evaluate.
+!
+
+basicInstallPackage:aPackage in:aPackageManager
+    "install a package"
+    
+    self openReadStreamStreamOn:aPackage filename andDo:[:aStream |
+        self skipPackageHeaderFrom:aStream.
+"/        aStream nextChunk       
+        self basicInstallPackage:aPackage fromStream:aStream  in:aPackageManager
+    ].
+!
+
+skipPackageHeaderFrom:aReadStream 
+    aReadStream nextChunk. "/ nothing
+    aReadStream nextChunk. "/ script for creating the receiver
+    aReadStream nextChunk. "/ the package header
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'loading'!
+
+loadFromStream:aStream 
+    aStream nextChunk.
+    aStream nextChunk.    "/ anEmpty string
+    package := self getInitialPackageFromChunk:aStream nextChunk.    "/ the receiver representation
+    package filename:filename.
+    ^ package
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'stream messages'!
+
+getChangeSetFrom:aStream 
+    ^ ChangeSet fromStream:aStream
+!
+
+getInitialPackageFrom:aStream 
+    |nextChunk|
+
+    nextChunk := aStream nextChunk.
+    Class nameSpaceQuerySignal 
+            answer:Packages
+            do:[
+        ^ (Compiler evaluate:nextChunk)
+    ]
+!
+
+getInitialPackageFromChangeSet:aChangeSet 
+    |nextChunk|
+
+    nextChunk := aChangeSet first source.
+    Class nameSpaceQuerySignal 
+            answer:Packages
+            do:[
+        ^ (Compiler evaluate:nextChunk)
+    ]
+!
+
+getInitialPackageFromChunk:aChunk 
+
+    Class nameSpaceQuerySignal 
+            answer:Packages
+            do:[
+        ^ (Compiler evaluate:aChunk)
+    ]
+! !
+
+!StxPackageFileReader::Version1 methodsFor:'validation'!
+
+validateAllClassesAreInImage
+
+    #toDo
+!
+
+validateAllMethodsAreInImage
+    #toDo
+!
+
+validateInstallation
+    self validateAllClassesAreInImage.
+    self validateAllMethodsAreInImage.
+! !
+
+!StxPackageFileReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileReader.st,v 1.2 2006/01/10 09:32:03 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__StxPackageFileWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,460 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#StxPackageFileWriter
+	instanceVariableNames:'handler stream'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-Handlers'
+!
+
+Object subclass:#Version1
+	instanceVariableNames:'package'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:StxPackageFileWriter
+!
+
+!StxPackageFileWriter class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!StxPackageFileWriter class methodsFor:'instance creation'!
+
+forPackage:aPackage 
+
+    ^ (self version:1) forPackage:aPackage 
+!
+
+version:aVersionNumber
+
+    aVersionNumber == 1 ifTrue:[
+        ^ Version1.
+    ].
+    self error:'Version unknown'
+! !
+
+!StxPackageFileWriter::Version1 class methodsFor:'instance creation'!
+
+forPackage:aPackage
+    ^ self basicNew package:aPackage
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'accessing'!
+
+fileOutVersion
+    ^ 1
+!
+
+package
+    "return the value of the instance variable 'package' (automatically generated)"
+
+    ^ package
+!
+
+package:something
+    "set the value of the instance variable 'package' (automatically generated)"
+
+    package := something.
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'api'!
+
+savePackageAs:aFilename
+    | writeStream |
+    self createPathFor:aFilename.
+    [ 
+        self canWriteTo:aFilename. "may return exceptions"
+        writeStream := aFilename writeStream.
+        self savePackageOn:writeStream.   "may return exceptions"
+    ] ensure:[
+        writeStream close.
+    ].
+
+    package markClean.
+    ^ package
+!
+
+savePackageOn:aWriteStream
+    self forPackage:package saveInstallationScriptChunkOn:aWriteStream.
+    self forPackage:package saveClassDefinitionsOn:aWriteStream.
+    self forPackage:package saveLooseMethodsOn:aWriteStream.
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'fileOut - chunks'!
+
+forPackage:aPackage saveClassDefinitionsOn:aWriteStream 
+
+    aPackage classNames size > 0 ifTrue:[
+        aWriteStream nextPutAll:'"Class Definitions"!!'.
+        aWriteStream cr.
+        aPackage classesDo:[:aClass |
+            aClass nameSpace isNameSpace ifTrue:[
+                self fileOutClass:aClass on:aWriteStream.
+            ] ifFalse:[| ownerClass |
+                "aClass is a privateClass"
+                ownerClass := aClass nameSpace.    
+                ownerClass package == aPackage name ifFalse:[
+                ]. "ifTrue:[
+                    Do nothing - the class has already been filed out by its ownerClass!!
+                ]."
+            ]
+        ].
+        aWriteStream cr.
+        aWriteStream nextPutAll:'"End of Class Definitions"!!'.
+        aWriteStream cr.
+    ].
+!
+
+forPackage:aPackage saveInstallationScriptChunkOn:aWriteStream
+    "create an installation script which is used to create
+     an initial package which can help determine if the package
+     is loadable"
+    self forPackage:aPackage savePackageFormatOn:aWriteStream.
+    self forPackage:aPackage savePackageInstanceCreationOn:aWriteStream.
+    self forPackage:aPackage savePackageFileVersionOn:aWriteStream.
+    self forPackage:aPackage savePackageCommentOn:aWriteStream.
+    self forPackage:aPackage saveClassNamesOn:aWriteStream.
+    self forPackage:aPackage saveLooseMethodNamesOn:aWriteStream.
+    self forPackage:aPackage saveScriptsOn:aWriteStream.
+    self forPackage:aPackage savePrerequisitesOn:aWriteStream.
+    self forPackage:aPackage saveEndingOn:aWriteStream.
+!
+
+forPackage:aPackage saveLooseMethodsOn:aWriteStream 
+    aPackage looseMethods size > 0 ifTrue:[
+        aWriteStream nextPutAll:'"LooseMethods"!!'.
+        aWriteStream cr.
+        aPackage looseMethods do:[:aLooseMethod |
+            self fileOutLooseMethod:aLooseMethod on:aWriteStream
+        ].
+        aWriteStream nextPutAll:'!!'.
+        aWriteStream cr.
+
+        aWriteStream nextPutAll:'"End of LooseMethods"!!'.
+    ].
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'fileOut - subparts'!
+
+fileOutClass:aClass on:aWriteStream
+
+    "ClassDescription fileOutErrorSignal can occur here from autoloaded classes"
+    aClass isLoaded ifFalse:[
+        aClass autoload
+    ].
+
+    package blockedMethods isEmpty ifFalse:[
+        Transcript 
+                nextPutAll:'Finnish me!!'; 
+                cr;
+                nextPutAll:'''blockedMethods '' are not accounted for at the moment!!'' in:'; 
+                cr;
+                nextPutAll:'Packages::StxPackageFileWriter::Version1>>fileOutClass:on:'  ; 
+                cr
+        
+    ].
+    aClass fileOutOn:aWriteStream
+!
+
+fileOutLooseMethod:aMethod on:aWriteStream 
+
+    aWriteStream nextPut:$!!.
+    aWriteStream nextPutAll:aMethod mclass asString.
+    aWriteStream nextPutAll:' methodsFor:'.
+    aWriteStream nextPut:$'.
+    aWriteStream nextPutAll:(aMethod category).
+    aWriteStream nextPut:$'.
+    aWriteStream nextPut:$!!.
+    aWriteStream cr.
+
+    aWriteStream nextPutAll:aMethod source.
+    aWriteStream nextPut:$!!.
+    aWriteStream cr.
+!
+
+forPackage:aPackage saveClassNamesOn:aWriteStream
+
+    aPackage classNames size > 0 ifTrue:[
+
+        aWriteStream 
+            nextPutAll:'"ClassNames"';
+            cr.
+
+        aWriteStream 
+            nextPutAll:'aPackage ';
+            cr.
+
+        aPackage classNames do:[:aClassname |
+            aWriteStream 
+                nextPutAll:'    addClassNamed:#', aClassname, ';';
+                cr.
+        ].
+
+        aWriteStream nextPutAll:'    yourself.'; "pointless but makes this code more readable"    
+        cr.
+
+        aWriteStream 
+            nextPutAll:'"End of ClassNames"';
+            cr;
+            cr.
+
+    ].
+!
+
+forPackage:aPackage saveEndingOn:aWriteStream
+    aWriteStream 
+        nextPutAll:'aPackage!!';
+        cr;
+        cr.
+!
+
+forPackage:aPackage saveLooseMethodNamesOn:aWriteStream
+
+    aPackage looseMethods size > 0 ifTrue:[
+
+        aWriteStream 
+            nextPutAll:'"LooseMethodNames"';
+            cr.
+
+        aWriteStream 
+            nextPutAll:'aPackage ';
+            cr.
+
+        aPackage looseMethods do:[:aMethod |
+            aWriteStream 
+                nextPutAll:'    addMethodNamed:#', aMethod name asString, ' forClassNamed:#', aMethod ownedClassName asString, ';';
+                cr.
+        ].
+
+        aWriteStream nextPutAll:'    yourself.'. "pointless but makes this code more readable"    
+        aWriteStream 
+            cr;
+            nextPutAll:'"End of LooseMethodNames"';
+            cr;
+            cr.
+    ].
+!
+
+forPackage:aPackage savePackageCommentOn:aWriteStream 
+    aWriteStream
+        nextPutAll:'aPackage packageComment:';
+        nextPutAll:aPackage packageComment ? '''''';
+        nextPut:$.;
+        cr;
+        cr.
+!
+
+forPackage:aPackage savePackageFileVersionOn:aWriteStream 
+
+    aWriteStream 
+        nextPutAll:'aPackage packageVersion:';
+        nextPutAll:self fileOutVersion printString;
+        nextPut:$.;
+        cr.
+!
+
+forPackage:aPackage savePackageFormatOn:aWriteStream 
+    aWriteStream nextPutAll:'!!Packages::PackageHandler openStxPackageFormat:1!!';
+    cr
+!
+
+forPackage:aPackage savePackageInstanceCreationOn:aWriteStream 
+    aWriteStream 
+        nextPutAll:'|aPackage|';
+        cr;
+        nextPutAll:'aPackage := Package named: ';
+        nextPut:$';
+        nextPutAll:aPackage name;
+        nextPut:$';
+        nextPut:$.;
+        cr.
+!
+
+forPackage:aPackage savePrerequisitesOn:aWriteStream
+
+    aPackage prerequisites size > 0 ifTrue:[
+        aWriteStream
+            nextPutAll:'"Prerequisites"';
+            cr.
+
+        self forPackage:aPackage savePrerequisteClassesOn:aWriteStream.
+        self forPackage:aPackage  savePrerequistePackagesOn:aWriteStream.
+        aWriteStream
+            nextPutAll:'"End of Prerequisites"';
+            cr;
+            cr.
+        
+    ]
+
+!
+
+forPackage:aPackage savePrerequisteClassesOn:aWriteStream
+
+    aPackage classPrerequisites size > 0 ifTrue:[
+
+        aPackage classPrerequisites do:[:prerequisite |
+
+            aWriteStream
+                nextPutAll:'aPackage' ;
+                cr;
+                nextPutAll:'   addClassNamePrerequisite:#', prerequisite name;
+                cr;
+                nextPutAll:'   ifFailString:';
+                nextPut:$';
+                nextPutAll:prerequisite ifFailedString;
+                nextPut:$';
+                nextPut:$;;
+                cr.
+        ].
+
+        aWriteStream nextPutAll:'   yourself.'; "pointless but makes this code more readable"    
+        cr.
+
+
+    ].
+!
+
+forPackage:aPackage savePrerequistePackagesOn:aWriteStream
+
+    aPackage packagePrerequisites size > 0 ifTrue:[
+
+        aPackage packagePrerequisites do:[:prerequisite |
+
+            aWriteStream
+                nextPutAll:'aPackage' ;
+                cr;
+                nextPutAll:'   addPackageNamePrerequisite:#', prerequisite name;
+                cr;
+                nextPutAll:'   ifFailString:';
+                nextPut:$';
+                nextPutAll:prerequisite ifFailedString;
+                nextPut:$';
+                nextPut:$;;
+                cr.
+        ].
+
+        aWriteStream nextPutAll:'   yourself.'; "pointless but makes this code more readable"    
+        cr.
+    ]
+!
+
+forPackage:aPackage saveScriptsOn:aWriteStream 
+
+    aPackage scripts size > 0 ifTrue:[ | aScript |
+
+        aWriteStream 
+            nextPutAll:'"Scripts"';
+            cr.
+        (aScript := aPackage postInstallScript) getString size == 0 ifFalse:[
+            aWriteStream
+                nextPutAll:'aPackage postInstallScriptString:';
+                nextPut:$';
+                nextPutAll:aScript getString;
+                nextPut:$';
+                nextPut:$.;
+                cr.
+        ].
+
+        (aScript := aPackage preInstallScript) getString size == 0 ifFalse:[
+            aWriteStream
+                nextPutAll:'aPackage preInstallScriptString:';
+                nextPut:$';
+                nextPutAll:aScript getString;
+                nextPut:$';
+                nextPut:$.;
+                cr.
+        ].
+
+        (aScript := aPackage postUninstallScript) getString size == 0 ifFalse:[
+            aWriteStream
+                nextPutAll:'aPackage postUninstallScriptString:';
+                nextPut:$';
+                nextPutAll:aScript getString;
+                nextPut:$';
+                nextPut:$.;
+                cr.
+        ].
+
+        (aScript := aPackage postUninstallScript) getString size == 0 ifFalse:[
+            aWriteStream
+                nextPutAll:'aPackage preUninstallScriptString:';
+                nextPut:$';
+                nextPutAll:aScript getString;
+                nextPut:$';
+                nextPut:$.;
+                cr.
+        ].
+        aWriteStream
+            cr;
+            cr.
+
+
+    ].
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'helpers'!
+
+createPathFor:aFilename
+    " create the path name for the filename if it does not already exist"
+    ^ aFilename directory makeDirectory.
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'instance creation'!
+
+forPackage:aPackage
+    ^ self basicNew package:aPackage
+! !
+
+!StxPackageFileWriter::Version1 methodsFor:'queries'!
+
+canWriteTo:aFilename
+    "return an error if the reciever cannot write to aFilename"
+
+    aFilename isFilename ifFalse:[
+        ^ self error:aFilename printString, ' is not a filename so cannot be written to.'.
+    ].
+
+    aFilename directory exists ifFalse:[
+        ^ self error:aFilename directory printString, ' directory does not exist.'.
+    ].
+
+    aFilename directory canBeWritten ifFalse:[
+        ^ self error:aFilename printString, ' cannot be written to.'.
+    ].
+
+    (aFilename isDirectory not) ifFalse:[
+        ^ self error:aFilename printString, ' is a directory and cannot be written to'.
+    ].
+! !
+
+!StxPackageFileWriter class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileWriter.st,v 1.5 2006/01/10 09:31:44 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__VersionHistory.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,368 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Object subclass:#VersionHistory
+	instanceVariableNames:'versions'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+VersionHistory comment:'I am a version history.  A version history is a collection of VersionNumbers that together form a tree of versions.  I enforce rules about how versions are added and removed from the history.
+
+To add a new version to a VersionHistory based on an existing version:
+
+  VersionHistory startingAt1 addNewVersionBasedOn: ''1'' asVersion; yourself
+
+If you add 2 new versions based on the same version, a branch will be started:
+
+  VersionHistory startingAt1 
+		addNewVersionBasedOn: ''1'' asVersion;
+		addNewVersionBasedOn: ''1'' asVersion; 
+		yourself
+
+To remove a single version (note: only versions at the tip of a branch, or at the base of the trunk (if it has only one successor) can be individually removed):
+
+  VersionHistory startingAt1 
+		addNewVersionBasedOn: ''1'' asVersion;
+		addNewVersionBasedOn: ''1'' asVersion; 
+		remove: ''1.1'' asVersion;
+		yourself
+
+To remove an entire branch:
+
+  VersionHistory startingAt1 
+		addNewVersionBasedOn: ''1'' asVersion;
+		addNewVersionBasedOn: ''1'' asVersion; 
+		addNewVersionBasedOn: ''1.1'' asVersion; 
+		addNewVersionBasedOn: ''1.2'' asVersion; 
+		removeBranch: ''1.1'' asVersion;
+		yourself
+
+To remove a portion of the trunk:
+
+  VersionHistory startingAt1 
+		addNewVersionBasedOn: ''1'' asVersion;
+		addNewVersionBasedOn: ''2'' asVersion; 
+		addNewVersionBasedOn: ''3'' asVersion; 
+		addNewVersionBasedOn: ''3'' asVersion; 
+		removeTrunk: ''2'' asVersion;
+		yourself
+
+To get a string description of a version history:
+
+  VersionHistory startingAt1 
+		addNewVersionBasedOn: ''1'' asVersion;
+		addNewVersionBasedOn: ''2'' asVersion; 
+		addNewVersionBasedOn: ''3'' asVersion; 
+		addNewVersionBasedOn: ''3'' asVersion; 
+		treeString
+
+Also, the following methods are useful for accessing the versions:
+
+	#firstVersion
+	#versionBefore:
+	#versionsAfter:
+	#mainLineStartingAt:
+	#allVersionsAfter:
+	#allVersionsBefore:
+'
+!
+
+!VersionHistory class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    Taken from KomPackaging in squeak.
+
+    [author:]
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+examples
+"
+
+  more examples to be added:
+                                                                [exBegin]
+    ... add code fragment for 
+    ... executable example here ...
+                                                                [exEnd]
+"
+!
+
+history
+    "Created: / 20.5.2003 / 08:28:06 / james"
+! !
+
+!VersionHistory class methodsFor:'as yet unclassified'!
+
+fromCollection: aCollection
+	"Note: this does not validate the continuity of version
+	numbers passed in aCollection...need to add continuity
+	checks in the future"
+
+	^self new
+		initializeVersionsFrom: aCollection;
+		yourself
+!
+
+startingAt1
+
+	^self startingAt: '1' asVersion
+!
+
+startingAt: aVersion
+
+	^self new
+		initializeVersionsAt: aVersion;
+		yourself
+! !
+
+!VersionHistory methodsFor:'accessing'!
+
+allVersionsAfter: aVersion
+	"Answer all the versions based on aVersion."
+
+	| answer |
+	answer := Set new.
+	versions do: [ :ea |
+		((ea inSameBranchAs: aVersion) and: 
+			[ea > aVersion]) ifTrue: [answer add: ea]].
+	^answer
+!
+
+allVersionsBefore: aVersion
+	"Answer all versions that came before aVersion"
+
+	| answer |
+	answer := Set new.
+	versions do: [ :ea |
+		((ea inSameBranchAs: aVersion) and: 
+			[ea < aVersion]) ifTrue: [answer add: ea]].
+	^answer
+!
+
+firstVersion
+	"Answer the first version in the entire version history"
+
+	^versions inject: versions anyOne into: [ :x :ea |
+		(x inSameBranchAs: ea)
+			ifTrue: [(x < ea) ifTrue: [x] ifFalse: [ea]]
+			ifFalse: [ea]]
+!
+
+latestMainLineVersion
+
+	^(self mainLineStartingAt: self firstVersion) last
+!
+
+mainLineStartingAt: aVersion
+	"Answer all versions based on aVersion that are not branches (they have 
+	the same number of digits with the same values, except the last value is
+	greater than the last value of aVersion)."
+
+	| answer tmp |
+	answer := OrderedCollection new.
+	tmp := aVersion.
+	[versions includes: tmp] 
+		whileTrue: 
+			[answer add: tmp.
+			tmp := tmp next].
+	^answer
+!
+
+versionBefore: aVersion
+
+	"Answer the version immediately preceeding aVersion."
+
+	| tmp |
+	(aVersion > '1' asVersion) ifFalse: [^nil].
+	(versions includes: (tmp := aVersion previous)) ifFalse: [^nil].
+	^tmp
+!
+
+versionsAfter: aVersion
+	"Answer all the versions immediately following aVersion."
+
+	| answer tmp |
+	answer := Set new.
+	tmp := aVersion next.
+	(versions includes: aVersion next) ifTrue: [answer add: tmp].
+
+	tmp := aVersion.
+	[versions includes: (tmp := tmp branchNext)] whileTrue:
+		[answer add: tmp].
+	^answer
+! !
+
+!VersionHistory methodsFor:'adding'!
+
+addNewVersionBasedOn: aVersion
+
+	| tmp |
+	(versions includes: aVersion) ifFalse: [^self error: 'Version is not in this history'].
+
+	tmp := aVersion next.
+	(versions includes: tmp) ifFalse: 
+		[versions add: tmp.
+		^tmp].
+
+	tmp := aVersion.
+	[versions includes: (tmp := tmp branchNext)] whileTrue.
+	versions add: tmp.
+	^tmp
+	
+! !
+
+!VersionHistory methodsFor:'initialization'!
+
+initializeVersionsAt: aVersion
+
+	versions := Set new.
+	versions add: aVersion.
+!
+
+initializeVersionsFrom: aCollection
+
+	versions := Set new.
+	aCollection do: [ :ea | versions add: ea ].
+! !
+
+!VersionHistory methodsFor:'printing'!
+
+treeString
+	"Answer a string that show the entire version history with
+	each branch starting on a new line"
+
+	^self treeStringStartingAt: self firstVersion
+!
+
+treeStringOn: strm startingAt: aVersion
+
+	| tmp |
+	tmp := self mainLineStartingAt: aVersion.
+	tmp do: [ :ea | ea versionStringOn: strm. strm space; space ].
+	strm cr.
+	tmp do: 
+		[ :ea | 
+		(versions includes: ea branchNext)
+			ifTrue: [self treeStringOn: strm startingAt: ea branchNext]].
+!
+
+treeStringStartingAt: aVersion
+
+	| strm |
+	strm := WriteStream on: ''.
+	self treeStringOn: strm startingAt: aVersion.
+	^strm contents
+! !
+
+!VersionHistory methodsFor:'removing'!
+
+remove: aVersion
+	"Remove aVersion from this version history."
+
+	^self remove: aVersion ifAbsent: [self error: 'version not found'].
+!
+
+remove: aVersion ifAbsent: aBlock
+	"Remove aVersion from this version history."
+
+	(versions includes: aVersion) ifFalse: [^aBlock value].
+
+	(self canRemove: aVersion) ifFalse:
+		[^self error: 'Only versions at the beginning or end with no more than one follower may be removed'].
+
+	versions remove: aVersion.
+!
+
+removeBranch: aVersion
+	"Remove aVersion and all of it's successors, providing that
+	aVersion is not the first version."
+
+	(self versionBefore: aVersion)
+		ifNil: [^self error: 'version is the first version in the history'].
+
+	versions removeAll: (self allVersionsAfter: aVersion).
+	versions remove: aVersion.
+!
+
+removeTrunk: aVersion
+	"Remove aVersion and all of it's predecessors, providing there
+	are no other branches stemming from the trunk.  Note, a trunk is defined
+	as all versions, starting with the first version, that have only one successor."
+
+	| tmp |
+	(self versionsAfter: aVersion) size > 1 
+		ifTrue: [^self error: 'version is at a fork'].
+
+	tmp := self allVersionsBefore: aVersion.
+	(tmp detect: [ :ea | (self versionsAfter: ea) size > 1 ] ifNone: [nil])
+		ifNotNil: [^self error: 'not a trunk, other branches detected'].
+
+	versions removeAll: tmp.
+	versions remove: aVersion.
+! !
+
+!VersionHistory methodsFor:'testing'!
+
+canRemove: aVersion
+
+	| hasPriors followers |
+	(versions includes: aVersion) ifFalse: [^false].
+	hasPriors := (self versionBefore: aVersion) notNil.
+	followers := self versionsAfter: aVersion.		
+
+	"Don't allow versions in the middle to be extracted"
+	(hasPriors and: [followers size > 0]) ifTrue: [^false].
+	
+	"Don't allow versions with more than one follower to be extracted"
+	(hasPriors not and: [followers size > 1]) ifTrue: [^false].
+	^true
+
+!
+
+includesVersion: aVersion
+
+	^versions includes: aVersion
+! !
+
+!VersionHistory class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/VersionHistory.st,v 1.2 2006/01/10 09:31:46 cg Exp $'
+! !
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/packages/Packages__VersionNumber.st	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,248 @@
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+"{ Package: 'stx:libbasic3' }"
+
+"{ NameSpace: Packages }"
+
+Magnitude subclass:#VersionNumber
+	instanceVariableNames:'numbers'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Package-helpers'
+!
+
+VersionNumber comment:'I am a version number.  My representation allows me to handle an entire tree of versions.  Once created, an instance should not change (note: VersionNumbers could be canonicalized like Symbols, but are not currently).  
+
+I am a magnitude so that you can see if one version preceeds another (only if the two versions are in the same branch).  
+
+	''2.1'' asVersion < ''2.2.1'' asVersion	"true"
+	''2.3'' asVersion < ''2.2.1'' asVersion	"error different branches"
+	''2.3'' asVersion inSameBranchAs: ''2.2.1'' asVersion	"false, why the previous one failed."	
+	''2.1'' asVersion = ''2.1'' asVersion		"true, obviously"
+
+To get the next version number in the same branch:
+
+	''2.3.4'' asVersion next	"2.3.5"
+
+To get the next version number, starting a new branch:
+
+	''2.3.4'' asVersion branchNext		"2.3.4.1"
+
+To get the common base version of any two version numbers (useful for merging):
+
+	''2.3.8'' asVersion commonBase: ''2.3.4.1'' asVersion		"2.3.4"'
+!
+
+!VersionNumber class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    Taken from KomPackaging in squeak.
+
+    [author:]
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+!
+
+examples
+"
+
+  more examples to be added:
+                                                                [exBegin]
+    ... add code fragment for 
+    ... executable example here ...
+                                                                [exEnd]
+"
+!
+
+history
+    "Created: / 20.5.2003 / 08:29:00 / james"
+! !
+
+!VersionNumber class methodsFor:'as yet unclassified'!
+
+first
+
+	^self fromCollection: #(1)
+!
+
+fromCollection: aCollection
+
+	^self new
+		initializeNumbers: aCollection;
+		yourself
+!
+
+fromString: aString
+
+	^self fromCollection: 
+		((aString findTokens: '.') collect: [:ea | ea asNumber ])
+	
+! !
+
+!VersionNumber methodsFor:'accessing'!
+
+branchNext
+
+	^self class fromCollection: (numbers, (Array with: 1))
+!
+
+commonBase: aVersion
+
+	| smallNums largeNums cutoff |
+	(aVersion numbers size <= numbers size) 
+		ifTrue: [smallNums := aVersion numbers. largeNums := numbers] 
+		ifFalse: [smallNums := numbers. largeNums := aVersion numbers].
+
+	cutoff := (1 to: smallNums size) 
+		detect: [ :in | ((smallNums at: in) ~= (largeNums at: in))] 
+		ifNone: [^self class fromCollection: smallNums].
+
+	^self class fromCollection: 
+		((numbers copyFrom: 1 to: (cutoff - 1)), 
+		(Array with: ((smallNums at: cutoff) min: (largeNums at: cutoff))))
+!
+
+next
+
+	| tmp |
+	tmp := numbers copy.
+	tmp at: numbers size put: (numbers last + 1).
+	^self class fromCollection: tmp
+!
+
+numbers
+	"Answer a copy (to discourage people from directly changing a version number).
+	VersionNumbers should never change, instead, instantiate a new instance."
+
+	^numbers copy
+!
+
+previous
+
+	| tmp |
+	numbers last = 1 ifTrue: 
+		[^self class fromCollection: (numbers allButLast)].
+	tmp := numbers copy.
+	tmp at: numbers size put: (numbers last - 1).
+	^self class fromCollection: tmp
+! !
+
+!VersionNumber methodsFor:'comparing'!
+
+< another 
+	"Answer whether the receiver is less than the argument."
+
+	| tmp |
+	(self inSameBranchAs: another) ifFalse: 
+		[^self error: 'Receiver and argument in different branches'].
+
+	tmp := another numbers.
+	(tmp size = numbers size) ifTrue:
+		[1 to: numbers size do: 
+			[ :in | (numbers at: in) < (tmp at: in) ifTrue: [^true]].
+		^false].
+
+	^numbers size < tmp size
+!
+
+= aVersion
+
+	^numbers = aVersion numbers
+!
+
+hash
+
+	^numbers hash
+! !
+
+!VersionNumber methodsFor:'initialization'!
+
+initializeNumbers: aCollection
+
+	aCollection do: [ :ea | 
+		ea <= 0 ifTrue: 
+			[^self error: 'VersionNumbers cannot contain zero or negative numbers']].
+
+	numbers := aCollection asArray
+! !
+
+!VersionNumber methodsFor:'printing'!
+
+printOn: strm
+
+	self storeOn: strm
+!
+
+storeOn: strm
+
+	strm nextPut: $'.
+	self versionStringOn: strm.
+	strm nextPutAll: ''' asVersion'.
+!
+
+versionString
+
+	^String streamContents: [ :strm | self versionStringOn: strm ]
+!
+
+versionStringOn: strm
+
+	| first |
+	first := true.
+	numbers do: [ :ea |
+		first ifFalse: [strm nextPut: $.].
+		first := false.
+		ea printOn: strm]
+	
+! !
+
+!VersionNumber methodsFor:'testing'!
+
+inSameBranchAs: aVersion
+
+	| less more |
+	(aVersion numbers size <= numbers size) 
+		ifTrue: [less := aVersion numbers. more := numbers] 
+		ifFalse: [less := numbers. more := aVersion numbers].
+
+	1 to: (less size - 1) do: [ :in | ((less at: in) = (more at: in)) ifFalse: [^false]].
+	^less size = more size or:
+		[(less at: less size) <= (more at: less size)]
+! !
+
+!VersionNumber class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/packages/VersionNumber.st,v 1.2 2006/01/10 09:31:53 cg Exp $'
+! !
\ No newline at end of file
--- a/packages/Prerequisite.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/Prerequisite.st	Fri Jul 29 06:57:08 2016 +0200
@@ -120,5 +120,5 @@
 !Prerequisite class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/Prerequisite.st,v 1.2 2006-01-10 09:32:17 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/Prerequisite.st,v 1.2 2006-01-10 09:32:17 cg Exp $'
 ! !
--- a/packages/PrerequisiteCollection.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/PrerequisiteCollection.st	Fri Jul 29 06:57:08 2016 +0200
@@ -99,5 +99,5 @@
 !PrerequisiteCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/PrerequisiteCollection.st,v 1.2 2006-01-10 09:25:29 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/PrerequisiteCollection.st,v 1.2 2006-01-10 09:25:29 cg Exp $'
 ! !
--- a/packages/StxPackageFileHandler.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/StxPackageFileHandler.st	Fri Jul 29 06:57:08 2016 +0200
@@ -203,5 +203,5 @@
 !StxPackageFileHandler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileHandler.st,v 1.2 2006-01-10 09:32:05 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/StxPackageFileHandler.st,v 1.2 2006-01-10 09:32:05 cg Exp $'
 ! !
--- a/packages/StxPackageFileReader.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/StxPackageFileReader.st	Fri Jul 29 06:57:08 2016 +0200
@@ -341,5 +341,5 @@
 !StxPackageFileReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileReader.st,v 1.2 2006-01-10 09:32:03 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/StxPackageFileReader.st,v 1.2 2006-01-10 09:32:03 cg Exp $'
 ! !
--- a/packages/StxPackageFileWriter.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/StxPackageFileWriter.st	Fri Jul 29 06:57:08 2016 +0200
@@ -456,5 +456,5 @@
 !StxPackageFileWriter class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/StxPackageFileWriter.st,v 1.5 2006-01-10 09:31:44 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/StxPackageFileWriter.st,v 1.5 2006-01-10 09:31:44 cg Exp $'
 ! !
--- a/packages/VersionHistory.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/VersionHistory.st	Fri Jul 29 06:57:08 2016 +0200
@@ -364,5 +364,5 @@
 !VersionHistory class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/VersionHistory.st,v 1.2 2006-01-10 09:31:46 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/VersionHistory.st,v 1.2 2006-01-10 09:31:46 cg Exp $'
 ! !
--- a/packages/VersionNumber.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/packages/VersionNumber.st	Fri Jul 29 06:57:08 2016 +0200
@@ -244,5 +244,5 @@
 !VersionNumber class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/packages/VersionNumber.st,v 1.2 2006-01-10 09:31:53 cg Exp $'
+    ^ '$Header: /var/local/cvs/stx/libbasic3/packages/VersionNumber.st,v 1.2 2006-01-10 09:31:53 cg Exp $'
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/stx_libbasic3-config.bat	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,12 @@
+rem
+rem
+rem Simple script to (auto)create libprofiler-config.h
+rem based on what is available on current system
+rem
+
+echo  /* Do not edit! Automatically generated by config.bat */ > stx_libbasic3-config.h
+echo  /* Sorry, no profiling support on Windows */ >> stx_libbasic3-config.h
+
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/stx_libbasic3-config.sh	Fri Jul 29 06:57:08 2016 +0200
@@ -0,0 +1,30 @@
+#!/bin/bash
+#
+# Simple script to (auto)create libprofiler-config.h
+# based on what is available on current system
+#
+
+HEADER=stx_libbasic3-config.h
+INCLUDE_DIRS="/usr/include /usr/local/include"
+
+function out() {
+    echo "$1" >> $HEADER
+}
+
+echo -n > $HEADER
+out "/* Do not edit! Automatically generated at $(date) */"
+out ""
+for inc in $INCLUDE_DIRS; do
+    if [ -r "$inc/valgrind/valgrind.h" ]; then
+        out "#define HAS_VALGRIND"        
+        if [ -r "$inc/valgrind/callgrind.h" ]; then
+            out "#define HAS_CALLGRIND"        
+        fi        
+    fi        
+done
+
+out ""
+
+
+
+
--- a/stx_libbasic3.st	Thu Jul 28 15:03:23 2016 +0200
+++ b/stx_libbasic3.st	Fri Jul 29 06:57:08 2016 +0200
@@ -73,25 +73,30 @@
     "list packages which are mandatory as a prerequisite.
      This are packages containing superclasses of my classes and classes which
      are extended by myself.
-     They are mandatory, beacuse we need these packages as a prerequisite for loading and compiling.
+     They are mandatory, because we need these packages as a prerequisite for loading and compiling.
      This method is generated automatically,
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "AbstractSourceFileWriter - superclass of ChangeSet::ClassSourceWriter "
+        #'stx:libbasic'    "AbstractSourceFileWriter - superclass of BeeSourceWriter"
     )
 !
 
 referencedPreRequisites
     "list packages which are a prerequisite, because they contain
      classes which are referenced by my classes.
-     We do not need these packages as a prerequisite for loading or compiling.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
      This method is generated automatically,
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:libbasic2'    "HTMLUtilities - referenced by HTMLDocGenerator>>generateClassDocReferenceFor:text:autoloading: "
+        #'stx:libbasic2'    "HTMLUtilities - referenced by HTMLDocGenerator>>generateClassDocReferenceFor:text:autoloading:"
     )
+
+    "Modified: / 31-05-2016 / 23:19:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 subProjects
@@ -116,6 +121,57 @@
 '
 !
 
+additionalRules_bc_dot_mak
+    "allows for additional static libraries to be added to the bc.mak file.
+     Subclasses may redefine this"
+
+    ^ '
+stx_libbasic3-config.h: stx_libbasic3-config.bat
+        call stx_libbasic3-config.bat
+
+clean::
+        del stx_libbasic3-config.h
+
+'
+
+    "Created: / 11-11-2012 / 12:22:21 / jv"
+    "Modified: / 31-05-2016 / 23:18:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+additionalRules_make_dot_proto
+    "allows for additional rules to be added to the make.proto file."
+
+    ^ '
+stx_libbasic3-config.h: stx_libbasic3-config.sh
+        ./stx_libbasic3-config.sh
+
+clean::
+        rm -f stx_libbasic3-config.h
+
+'
+
+    "Created: / 01-11-2012 / 22:35:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-05-2016 / 23:18:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+additionalTargets_bc_dot_mak
+    "obsolete - kept for compatibility with old project files"
+
+   ^ 'stx_libbasic3-config.h'
+
+    "Created: / 09-11-2012 / 12:14:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-05-2016 / 22:59:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+additionalTargets_make_dot_proto
+    "allows for additional targets to be added to the make.proto file."
+
+    ^ 'stx_libbasic3-config.h'
+
+    "Created: / 01-11-2012 / 22:35:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-05-2016 / 22:59:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 stcWarningOptions
     ^ '-warnNonStandard -warnUnused'
 ! !
@@ -131,6 +187,8 @@
     ^ #(
         "<className> or (<className> attributes...) in load order"
         AbstractSourceCodeManager
+        BeeProjectWriter
+        BeeSourceWriter
         CallChain
         Change
         ChangeDeltaInformation
@@ -152,11 +210,13 @@
         SourceCodeManagerUtilities
         SystemEnvironment
         SystemOrganizer
+        SystemProfiler
         TraceBuffer
-        (VSEFileSourceWriter autoload)
         VersionInfo
         WrappedMethod
         #'stx_libbasic3'
+        BeeProjectDefinitionWriter
+        BeeProjectSourceWriter
         CVSSourceCodeManager
         CVSVersionInfo
         ChangeSetDiffEntry
@@ -179,8 +239,6 @@
         SourceCodeManagerUtilitiesForContainerBasedManagers
         SourceCodeManagerUtilitiesForWorkspaceBasedManagers
         StoreSourceCodeManager
-        (VSEChunkFileSourceWriter autoload)
-        (VSEPackageFileSourceWriter autoload)
         ClassCategoryChange
         ClassClassVariableChange
         ClassCommentChange
@@ -206,15 +264,22 @@
         MethodPackageChange
         MethodPrivacyChange
         MethodRemoveChange
-        (VisualAgeChunkFileSourceWriter autoload)
+        (TraitClassTraitDefinitionChange autoload)
         (TraitDefinitionChange autoload)
-        (TraitClassTraitDefinitionChange autoload)
+        (VSEFileSourceWriter autoload)
+        (VSEChunkFileSourceWriter autoload)
+        (VSEPackageFileSourceWriter autoload)
+        (VisualAgeChunkFileSourceWriter autoload)
     )
+
+    "Modified: / 31-05-2016 / 23:19:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 extensionMethodNames
     "lists the extension methods which are to be included in the project.
-     Entries are pairwise elements, consisting of class-name and selector."
+     Entries are 2-element array literals, consisting of class-name and selector.
+     A correponding method with real names must be present in my concrete subclasses
+     if it has extensions."
 
     ^ #(
         UserPreferences historyManagerModificationLimit
@@ -290,6 +355,10 @@
     ^ '$Header$'
 !
 
+version_HG
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id$'
 ! !
--- a/vcmake.bat	Thu Jul 28 15:03:23 2016 +0200
+++ b/vcmake.bat	Fri Jul 29 06:57:08 2016 +0200
@@ -13,8 +13,11 @@
 @REM Kludge got Mercurial, cannot be implemented in Borland make
 @FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
 @IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+
+
 make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
 
 
+@IF "%1" EQU "test" exit /b 0
 
 
--- a/vms.mak	Thu Jul 28 15:03:23 2016 +0200
+++ b/vms.mak	Fri Jul 29 06:57:08 2016 +0200
@@ -2,7 +2,7 @@
 # DO NOT EDIT 
 # automatically generated from Make.proto
 #
-# $Header: /cvs/stx/stx/libbasic3/vms.mak,v 1.4 1999-09-18 14:10:24 cg Exp $
+# $Header: /cvs/stx/stx/libbasic3/vms.mak,v 1.4 1999/09/18 14:10:24 cg Exp $
 #
 TOP=..
 LIBNAME=libbasic3