'From Squeak3.3alpha of 30 January 2002 [latest update: #4730] on 31 January 2002 at 6:31:39 pm'! "Change Set: firstModuleFixes-hg Date: 31 January 2002 Author: Henrik Gedenryd Some quick fixes to make module unloading work better. Moving some classes that were sent to the wrong places due to bad category strings. "! ModuleRefactorer subclass: #FromVersion0p0003to0004 instanceVariableNames: '' classVariableNames: '' module: #(Squeak Language Modules Refactorings)! !Browser methodsFor: 'system category functions' stamp: 'hg 1/31/2002 18:28'! findClass "Search for a class by name." | pattern foundClass classNames index toMatch exactMatch potentialClassNames | self okToChange ifFalse: [^ self classNotFound]. pattern _ FillInTheBlank request: 'Class name or fragment?'. pattern isEmpty ifTrue: [^ self classNotFound]. toMatch _ (pattern copyWithout: $.) asLowercase. potentialClassNames _ self potentialClassNames asOrderedCollection. classNames _ pattern last = $. ifTrue: [potentialClassNames select: [:nm | nm asLowercase = toMatch]] ifFalse: [potentialClassNames select: [:n | n includesSubstring: toMatch caseSensitive: false]]. classNames isEmpty ifTrue: [^ self classNotFound]. exactMatch _ classNames detect: [:each | each asLowercase = toMatch] ifNone: [nil]. index _ classNames size = 1 ifTrue: [1] ifFalse: [exactMatch ifNil: [(PopUpMenu labelArray: classNames lines: #()) startUp] ifNotNil: [classNames addFirst: exactMatch. (PopUpMenu labelArray: classNames lines: #(1)) startUp]]. index = 0 ifTrue: [^ self classNotFound]. foundClass _ Module root allDefinitionsFor: (classNames at: index) asSymbol onlyExported: false detect: [:value :module | value isBehavior]. self selectCategoryForClass: foundClass. self selectClass: foundClass ! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'hg 1/31/2002 17:33'! definitionST80: isST80 "Answer a String that defines the receiver." | aStream path | isST80 ifTrue: [^ self definitionST80]. aStream _ WriteStream on: (String new: 300). superclass == nil ifTrue: [aStream nextPutAll: 'nil'] ifFalse: [ path _ Preferences strongModules ifTrue: [(self module qualifiedPrefixForName: superclass name andValue: superclass), ' '] ifFalse: ['']. aStream nextPutAll: path , superclass name]. aStream nextPutKeyword: self kindOfSubclass withArg: self name. aStream cr; tab; nextPutKeyword: 'instanceVariableNames: ' withArg: self instanceVariablesString. aStream cr; tab; nextPutKeyword: 'classVariableNames: 'withArg: self classVariablesString. Preferences modularClassDefinitions ifFalse: [ aStream cr; tab; nextPutAll: 'poolDictionaries: '; store: self sharedPoolsString. aStream cr; tab; nextPutAll: 'category: '; store: self module simulatedCategory asString] ifTrue: [ aStream cr; tab; nextPutAll: 'module: ', self module path literalPrintString]. ^ aStream contents! ! !Module methodsFor: 'system conversion' stamp: 'hg 1/31/2002 10:09'! declareExternalRefsForSelector: selector inClass: aClass "for all unresolved globals in the method of the given selector and class, declare the global's defining module as one of my external modules" | varName definingModule cm lits isDefined | cm _ aClass compiledMethodAt: selector. lits _ cm literals. lits do: [:lit | lit isVariableBinding ifTrue: [ varName _ (lit value isKindOf: Metaclass) ifFalse: [lit key] ifTrue: [lit value theNonMetaClass name]. isDefined _ self definesName: varName usingScheme: self weakOrStrongBindingScheme withCache: OutOfScopeCache ifTrue: [:a | ]. (isDefined or: [lit value == aClass]) ifFalse: [ definingModule _ Module root moduleDefining: varName. definingModule ifNotNil: [ "ensure that defining module exports it" "definingModule exportName: varName." self ensureExternalModule: definingModule]]]] ! ! !ModuleInstaller methodsFor: 'graph computation' stamp: 'hg 1/31/2002 10:21'! orderWithinCompositeFor: modules | dependencies | dependencies _ modules asSet collect: [:mod | mod -> ((self allModulesNeededBy: mod exceptForNeedsOf: modules) copyWithoutAll: mod deepSubmodules)]. ^self modules: modules inDependencyOrderFrom: dependencies! ! !ModuleInstaller methodsFor: '(un)loading' stamp: 'hg 1/31/2002 10:48'! unloadModule: module "Remove module from the image. This ought to be as easy as removing from parent, but it ain't for compatibility reasons" self deactivateModules: module deepSubAndDeltaModules. module deepSubmodulesBottomUpDo: [:mod | mod cleanOutModule. mod parentModule removeNeighborModule: mod]! ! !ModuleInstaller methodsFor: 'utilities' stamp: 'hg 1/31/2002 15:22'! ensureNoUsersOf: modules "safeness is defined as no other loaded modules depending on the given modules, i.e. declaring any of them as an external module." | allNeededModules unsafeToUnload | allNeededModules _ self allModulesNeededBy: Module root exceptForNeedsOf: modules. unsafeToUnload _ allNeededModules intersection: modules. unsafeToUnload isEmpty ifFalse: [ unsafeToUnload do: [:mod | self note: '>> Module ', mod pathAsMessages, ' is used by other modules.']. self notify: unsafeToUnload size printString, ' modules are used by other modules. Deactivating or unloading them may crash the system.']. ! ! !ModuleRefactorer methodsFor: 'versions' stamp: 'hg 1/31/2002 17:54'! ensurePrerequisiteVersions "simple default: just increment the version for #(Squeak), ie. the version of the Squeak standard class library" (Module squeak version closeTo: self fromVersion) ifFalse: [ self error: 'These refactorings should only be applied to version ', self fromVersion printString, ' of the Squeak modules'].! ! !ModuleRefactorer methodsFor: 'public' stamp: 'hg 1/31/2002 17:55'! runRefactorings "Trigger the whole set of refactorings in this class." self ensurePrerequisiteVersions. self class module repository useChangeSetNamed: self class name, ' Reorganization' during: [ self putAwayUnknownModules; moveModules; reorderModules. self moveGlobalsToModules. self installModuleDeclarations. self refactorClasses. self convertPools. self removeModules. self installRepositories. self incrementVersions. Preferences strongModules ifTrue: [Module root rewriteIndirectRefs]. ] ! ! !ModuleRefactorer methodsFor: 'moving modules' stamp: 'hg 1/31/2002 17:42'! newPlacesForModules "For each module, list pairs of its path before and after moving it." ^#()! ! !FromVersion0p0003to0004 methodsFor: 'moving definitions' stamp: 'hg 1/31/2002 18:31'! modulesToRemove "return a list of paths to modules to remove" ^#(#(Kernel) #(Collections) #(Squeak Media MPEG) #(SUnit) )! ! !FromVersion0p0003to0004 methodsFor: 'moving definitions' stamp: 'hg 1/31/2002 17:56'! newPlacesForModules "For each module, list pairs of its path before and after moving it." ^#(#(Temporary Movies) #(Squeak Media Movies) #(Squeak Media Movies Kernel) #(Squeak Media Movies Core) #(Kernel Numbers) #(Squeak Language Core Tests) #(TestBalloonFont) #(Squeak Morphic Tests) #(Collections SequenceableTest) #(Squeak Language Collections Tests))! ! !FromVersion0p0003to0004 methodsFor: 'moving definitions' stamp: 'hg 1/31/2002 17:57'! refactorBadlyPlacedClasses self transferBindingsNamedIn: #(AllTestSelectorsFixTest) from: Module @ #(SUnit Tests) to: Module @ #(Squeak Development Test SUnit Tests). self transferBindingsNamedIn: #(WriteStreamTest) from: Module @ #(Collections Streams) to: Module @ #(Squeak Language Collections Tests). ! ! !FromVersion0p0003to0004 methodsFor: 'versions' stamp: 'hg 1/31/2002 17:52'! fromVersion "return the version of the Squeak hierarchy to start with" ^0.0003! ! "Postscript:" FromVersion0p0003to0004 run.!