[Pkg] Monticello Public: Monticello.impl-kph.598.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Dec 7 01:16:43 UTC 2008


A new version of Monticello.impl was added to project Monticello Public:
http://www.squeaksource.com/mc/Monticello.impl-kph.598.mcz

==================== Summary ====================

Name: Monticello.impl-kph.598
Author: kph
Time: 7 December 2008, 1:15:45 am
UUID: 263d0b6c-78a8-4e2b-82e9-d91575b70094
Ancestors: Monticello.impl-kph.597

+ Files support working (fully debuggged?)
- Dont hang on to cruft that is intended to make MC loadable in older MCs we have LPF now

=============== Diff against Monticello.impl-kph.597 ===============

Item was added:
+ ----- Method: MCSnapshotBrowser>>filesCategory (in category 'accessing') -----
+ filesCategory
+ 	^ ':FILES'!

Item was added:
+ ----- Method: MCMczWriter>>writeFile: (in category 'files') -----
+ writeFile: definition
+ 
+ 	self addFile: definition pathToSnapshotFull at: definition pathToSnapshot
+ 	
+  !

Item was changed:
  ----- Method: MCVersionInfo>>authorFromName (in category 'pillaging') -----
  authorFromName
   	
+ 	| authorTokens out |
- 	| authorTokens |
  	
  	authorTokens := OrderedCollection new.
  	
  	self nameAfterLastDashAsTokens do: [ : token |
  
  		token first isDigit ifFalse: [ authorTokens add: token ].
  	
  	].
  
+ 	out := String streamContents: [:str | 
+ 	   authorTokens do: [ :ea | str nextPutAll: ea ; nextPut: $. ]
+ 	].
+ 
+ 	^ out allButLast 
- 	^ authorTokens	reduce: [ :a :b | a , '.' , b ]
-  
  !

Item was changed:
  MCDefinition subclass: #MCScriptDefinition
  	instanceVariableNames: 'script packageName properties'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  ----- Method: MCSnapshotBrowser>>classDefinitionString (in category 'text') -----
  classDefinitionString
  	| defs |
+ 	defs := self packageClasses 
+ 			detect: [ : ea | ea className = classSelection] ifNone: [ ^ 'This class is defined elsewhere.' ].
- 	defs := items select: [:ea | (ea isClassDefinition or: [ea isClassDefinitionExtension])
- 			and: [ea className = classSelection]].
- 
- 	defs isEmpty ifTrue: [^ 'This class is defined elsewhere.'].
  
  	^ String streamContents: [:stream | 
  		defs asArray sort 
  			do: [:ea | ea printDefinitionAndCommentOn: stream]
  			separatedBy: [stream nextPut: $.; cr]
  	].!

Item was added:
+ ----- Method: MCMczReader>>snapshot (in category 'as yet unclassified') -----
+ snapshot
+ 	snapshot ifNil: [self loadSnapshot].
+ 	^ snapshot!

Item was changed:
  MCMethodDefinition subclass: #MCMethodBeforeCommitUnloadDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!

Item was added:
+ ----- Method: MCFileDefinition>>summary (in category 'as yet unclassified') -----
+ summary
+ 	^ ':FILE: ', self path , ' (' , self fileSize asString , ' bytes)'!

Item was changed:
  ----- Method: MCMethodBeforeCommitUnloadDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString beginsWith: 'mcOnUninstall'  !
- 	^ selector beginsWith: 'mcOnUninstall'  !

Item was added:
+ ----- Method: MCMczWriter>>writeFiles: (in category 'files') -----
+ writeFiles: definitions
+  
+ 	definitions ifNil: [ ^ self ].
+ 	
+ 	definitions do: [ :ea | self writeFile: ea ].!

Item was added:
+ ----- Method: MCFileDefinition>>pathToOriginalFull (in category 'as yet unclassified') -----
+ pathToOriginalFull
+ 
+ 	^ FileDirectory default fullNameFor: self path!

Item was added:
+ ----- Method: MCSnapshotBrowser>>selectedFileSource (in category 'text') -----
+ selectedFileSource 
+ 	
+ 	^ (self fileDefinitions detect: [ :ea | ea path = classSelection ] ifNone: [ ^ 'file?' ]) source!

Item was changed:
  ----- Method: MCSnapshotBrowser>>visibleClasses (in category 'listing') -----
  visibleClasses
+ 
+ 	categorySelection = self filesCategory ifTrue: [ 
+ 		^ self fileDefinitions collect: #path
+ 	].
+ 
  	^ categorySelection = self extensionsCategory
  		ifTrue: [self extensionClassNames]
  		ifFalse: [self packageClasses
  					select: [:ea | ea category = categorySelection]
  					thenCollect: [:ea | ea className]].!

Item was added:
+ ----- Method: MCFileDefinition>>uuid: (in category 'as yet unclassified') -----
+ uuid: id
+ 
+ 	^ self propertyAt: #uuid put: id!

Item was added:
+ ----- Method: MCPackageLoader1b>>loadFiles (in category 'private') -----
+ loadFiles!

Item was added:
+ ----- Method: MCFileDefinition>>fileSize (in category 'as yet unclassified') -----
+ fileSize
+ 
+ 	^ self propertyAt: #fileSize ifAbsent: [ ]!

Item was changed:
  ----- Method: MCSnapshotReader>>snapshot (in category 'as yet unclassified') -----
  snapshot
+ 	snapshot ifNil: [self loadSnapshot].
+ 	^ snapshot!
- 	^ MCSnapshot fromDefinitions: self definitions!

Item was added:
+ ----- Method: MCMiscDefinition>>accept: (in category 'as yet unclassified') -----
+ accept: writer!

Item was changed:
  ----- Method: MCSnapshotBrowser>>allClassNames (in category 'accessing') -----
  allClassNames
  	^ (items 
+ 		select: [:ea | ea isOrganizationDefinition not and: [ ea isFileDefinition not ]] 
- 		select: [:ea | ea isOrganizationDefinition not] 
  		thenCollect: [:ea | ea className]) asSet.
  !

Item was added:
+ ----- Method: MCFileDefinition>>description (in category 'as yet unclassified') -----
+ description
+ 	^ Array with: self fileSize with: self path!

Item was added:
+ ----- Method: MCMczReader>>extractFileFrom: (in category 'as yet unclassified') -----
+ extractFileFrom: member
+ 
+ 	definitions add: (MCFileDefinition new 
+ 		path: member fileName;
+ 		uuid: ((member fileName readStream upTo: $/; yourself) upTo: $/);
+ 		fileSize: member uncompressedSize;
+ 		yourself)!

Item was added:
+ ----- Method: MCFileDefinition>>unload (in category 'as yet unclassified') -----
+ unload
+ 	
+ 	FileDirectory default deleteFileNamed: self pathToOriginalFull !

Item was changed:
  MCScriptDefinition subclass: #MCRemovalPreambleDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  ----- Method: MCPackage>>snapshot (in category 'as yet unclassified') -----
  snapshot
+ 
+ 	| definitions categories packageInfo files |
- 	| definitions categories packageInfo |
   
  	packageInfo := self packageInfo.
  	definitions := OrderedCollection new.
  	categories := packageInfo systemCategories.
  	
  	definitions addAll: (self orphanage orphansFor: packageInfo). 
  	definitions removeAllFoundIn: self orphanage unlinkedClasses.
  	   
  	categories isEmpty ifFalse: [ definitions add: (MCOrganizationDefinition categories: categories) ].
  
  	packageInfo
  		classesDo: [:ea | definitions addAll: ea classDefinitions]
  		methodsDo: [:ea | definitions add: ea asMethodDefinition]
  		displayingProgress: 'Snapshotting...'.
  	
  	MCScriptDefinition subclassesDo: [ :ea | ea from: packageInfo addTo: definitions ].
+ 
+ 	files := MCFileDefinition from: packageInfo addTo: definitions.
+ 	
+ 	^ (MCSnapshot fromDefinitions: definitions) 
+ 			files: files;
+ 			yourself
-  
- 	^ MCSnapshot fromDefinitions: definitions
  !

Item was changed:
  ----- Method: MCMethodBeforeCommitLoadDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString beginsWith: 'mcOnInstall'  !
- 	^ selector beginsWith: 'mcOnInstall'  !

Item was changed:
  SystemOrganization addCategory: #'Monticello-Base'!
  SystemOrganization addCategory: #'Monticello-Base-Chunk Format'!
  SystemOrganization addCategory: #'Monticello-Base-Loading'!
  SystemOrganization addCategory: #'Monticello-Base-Merging'!
  SystemOrganization addCategory: #'Monticello-Base-Modeling'!
  SystemOrganization addCategory: #'Monticello-Orphanage'!
  SystemOrganization addCategory: #'Monticello-Base-Patching'!
  SystemOrganization addCategory: #'Monticello-Base-Repositories'!
  SystemOrganization addCategory: #'Monticello-Base-Storing'!
  SystemOrganization addCategory: #'Monticello-UI-Repository'!
  SystemOrganization addCategory: #'Monticello-Base-Versioning'!
- SystemOrganization addCategory: #'Monticello-Files'!
  SystemOrganization addCategory: #'Monticello-Configurations'!
  SystemOrganization addCategory: #'Monticello-UI-Browsers'!
  SystemOrganization addCategory: #'Monticello-UI'!
+ SystemOrganization addCategory: #'Monticello-Base-Modeling-Methods'!
+ SystemOrganization addCategory: #'Monticello-Base-Modeling-Scripts'!
+ SystemOrganization addCategory: #'Monticello-Mocks'!

Item was added:
+ ----- Method: MCFileDefinition>>realize (in category 'as yet unclassified') -----
+ realize
+ 	
+ 	| f1 f2 |
+ 	f1 := self pathToOriginalFull.
+ 	
+ 	self fileSize: (FileDirectory on: f1) directoryEntry fileSize.
+ 	
+ 	f2 := self pathToSnapshotFull.
+ 	(FileDirectory on: f2) containingDirectory assureExistence.
+ 	
+ 	FileDirectory default deleteFileNamed: f2.
+ 	 
+ 	FileDirectory default copyFileNamed: f1
+ 						 toFileNamed: f2.!

Item was added:
+ ----- Method: MCFileDefinition>>source (in category 'as yet unclassified') -----
+ source
+ 
+ 	| fs |
+ 	
+ 	fs := self class cacheDir oldFileNamed: self pathToSnapshot.
+ 		
+ 	[ ^ fs next: 1000 ] ensure: [ fs close ]!

Item was added:
+ ----- Method: MCFileDefinition>>install (in category 'as yet unclassified') -----
+ install
+ 
+ 	FileDirectory default copyFileNamed: self pathToSnapshotFull toFileNamed: self pathToOriginalFull!

Item was added:
+ ----- Method: FileDirectory>>entriesAsFDs (in category '*monticello') -----
+ entriesAsFDs
+ 
+ 	^ self entriesRecursive: false on: OrderedCollection new
+  !

Item was changed:
  ----- Method: MCPackageLoader1b>>loadComplete (in category 'private') -----
  loadComplete
  	MCMethodDefinition tidyCache.
  	self orphanage 
  		addOrphans: unloadableDefinitions;
  	 	addOrphans: errorDefinitions;
  		loadComplete.
+ 	Behavior flushObsoleteSubclasses.
+ 	self loadFiles.!
- 	Behavior flushObsoleteSubclasses.!

Item was changed:
  MCScriptDefinition subclass: #MCRemovalPostscriptDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  ----- Method: MCScriptDefinition>>installScript: (in category 'as yet unclassified') -----
  installScript: aString
+ 	
+ 	self packageInfo propertyAt: self scriptSelector put: aString.
+ 	!
- 	| sel pi |
- 	sel := (self scriptSelector, ':') asSymbol.
- 	pi := self packageInfo.
- 	(pi respondsTo: sel)
- 		ifTrue: [pi perform: sel with: aString]!

Item was added:
+ ----- Method: MCFileDefinition class>>cacheDir (in category 'as yet unclassified') -----
+ cacheDir
+ 
+ 	^ FileDirectory default directoryNamed: 'packages-cache'!

Item was added:
+ MCDefinition subclass: #MCMiscDefinition
+ 	instanceVariableNames: 'properties'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!

Item was added:
+ ----- Method: MCFileDefinition>>evaluate (in category 'as yet unclassified') -----
+ evaluate
+ 	self error!

Item was added:
+ ----- Method: MCFileDefinition>>script (in category 'as yet unclassified') -----
+ script
+ 
+ 	self error!

Item was changed:
  ----- Method: MCMczWriter>>writeDefinitions: (in category 'visiting') -----
  writeDefinitions: aVersion
+ 	self writeSnapshot: aVersion snapshot.
+ 	!
- 	self writeSnapshot: aVersion snapshot!

Item was changed:
  ----- Method: MCPackageManager class>>methodModified: (in category 'system changes') -----
  methodModified: anEvent
  	^self managersForClass: anEvent itemClass selector: anEvent itemSelector do:[:mgr| mgr modified: true].!

Item was changed:
  ----- Method: MCMczReader>>loadDefinitions (in category 'as yet unclassified') -----
  loadDefinitions
+ 	definitions := self snapshot definitions!
- 	definitions := OrderedCollection new.
- 	(self zip memberNamed: 'snapshot.bin') ifNotNilDo:
- 		[:m | [^ definitions := (DataStream on: m contentStream) next definitions]
- 			on: Error do: [:fallThrough |  self halt ]].
- 	"otherwise"
- 	(self zip membersMatching: 'snapshot/*')
- 		do: [:m | self extractDefinitionsFrom: m].
- !

Item was added:
+ ----- Method: MCFileDefinition class>>cleanUp (in category 'as yet unclassified') -----
+ cleanUp
+ 
+ 	^ (self cacheDir directoryNamed: 'files') recursiveDelete!

Item was changed:
  ----- Method: MCMczWriter>>writeVersion: (in category 'visiting') -----
  writeVersion: aVersion
  	self writeFormat.
  	self writePackage: aVersion package.
  	self writeVersionInfo: aVersion info.
  	self writeDefinitions: aVersion.
+ 	aVersion dependencies do: [:ea | self writeVersionDependency: ea].
+ 	self writeFiles: aVersion snapshot files.
+ !
- 	aVersion dependencies do: [:ea | self writeVersionDependency: ea]!

Item was added:
+ ----- Method: MCFileDefinition>>uuid (in category 'as yet unclassified') -----
+ uuid
+ 
+ 	^ self propertyAt: #uuid ifAbsent: [ self uuid: UUID new ]!

Item was changed:
  ----- Method: MCMethodUnloaderDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString = 'unload' !
- 	^ selector = #unload !

Item was added:
+ ----- Method: MCFileDefinition>>initializeWithPath:packageName: (in category 'as yet unclassified') -----
+ initializeWithPath: aString packageName: packageString
+ 	self path:aString.
+ 	"packageName := packageString"!

Item was added:
+ ----- Method: MCSnapshotBrowser>>fileDefinitions (in category 'accessing') -----
+ fileDefinitions
+ 	^ items select: [:ea | ea isFileDefinition ]!

Item was added:
+ ----- Method: MCMczWriter>>addFile:at: (in category 'writing') -----
+ addFile: aFile at: path
+ 
+ 	(zip addFile: aFile as: path) desiredCompressionMethod: ZipArchive compressionDeflated 
+ 	!

Item was added:
+ ----- Method: MCSnapshot>>files: (in category 'initializing') -----
+ files: fileDefns
+ 
+ 	files := fileDefns!

Item was changed:
  MCMethodDefinition subclass: #MCMethodBeforeCommitLoadDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!
  
  !MCMethodBeforeCommitLoadDefinition commentStamp: 'kph 5/30/2007 16:20' prior: 0!
  MCMethodSpecialActionDefinition
  
   !

Item was changed:
  MCMethodDefinition subclass: #MCMethodUnloaderDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!

Item was added:
+ ----- Method: MCFileDefinition>>path: (in category 'as yet unclassified') -----
+ path: p 
+ 
+ 	^ self propertyAt: #path put: p!

Item was changed:
  ----- Method: MCSnapshotBrowser>>text (in category 'text') -----
  text
  	self switchIsComment ifTrue: [^ self classCommentString].
  	methodSelection ifNotNil: [^ methodSelection source].
  	protocolSelection ifNotNil: [^ ''].
+ 	categorySelection = self filesCategory ifTrue: [ ^ self selectedFileSource ].
  	classSelection ifNotNil: [^ self classDefinitionString].
+ 	
  	^ ''!

Item was added:
+ ----- Method: MCFileDefinition>>pathToSnapshotFull (in category 'as yet unclassified') -----
+ pathToSnapshotFull
+ 
+ 	^ self class cacheDir fullNameFor: self pathToSnapshot
+ 
+  !

Item was changed:
  MCMethodDefinition subclass: #MCMethodAfterRemovalActionDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  MCMethodDefinition subclass: #MCMethodExternalFieldDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!

Item was added:
+ ----- Method: MCMczReader>>loadSnapshot (in category 'as yet unclassified') -----
+ loadSnapshot
+  	(self zip memberNamed: 'snapshot.bin') ifNotNilDo:
+ 		[:m | [^ snapshot := (DataStream on: m contentStream) next ] 
+ 			on: Error do: [:fallThrough |  self halt ]].
+ 		
+ 	"otherwise"
+ 	(self zip membersMatching: 'snapshot/*')
+ 		do: [:m | self extractDefinitionsFrom: m].
+ 
+ 	(self zip membersMatching: 'files/*')
+ 		do: [:m | self extractFileFrom: m].
+ !

Item was changed:
  ----- Method: MCMethodAfterRemovalActionDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString beginsWith: 'mcAfterRemoval'  !
- 	^ selector beginsWith: 'mcAfterRemoval'  !

Item was changed:
  ----- Method: MCMethodInitializerDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString = 'initialize' or: [ selectorString beginsWith: 'mcAfterInstall' ] !
- 	^ selector = 'initialize' or: [ selector beginsWith: 'mcAfterInstall' ] !

Item was changed:
  MCScriptDefinition subclass: #MCPreambleDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
- 	category: 'Monticello-Base-Modeling'!

Item was added:
+ ----- Method: MCSnapshot>>files (in category 'initializing') -----
+ files 
+ 	
+ 	^ files!

Item was added:
+ ----- Method: MCFileDefinition>>sortKey (in category 'as yet unclassified') -----
+ sortKey
+ 
+ 	^ self summary!

Item was changed:
  MCDefinition subclass: #MCMethodDefinition
  	instanceVariableNames: 'classIsMeta source category selector className timeStamp properties dummy1 dummy2 methodAndNode requestor compiledMethod priorMethodOrNil compiledSelector isInstalled priorMethodCategory theClass defnToInstall'
  	classVariableNames: 'Definitions'
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  Object subclass: #MCSnapshot
+ 	instanceVariableNames: 'definitions files'
- 	instanceVariableNames: 'definitions'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Base'!

Item was added:
+ ----- Method: MCMczReader>>loadFiles (in category 'files') -----
+ loadFiles
+ 
+ 	| dir |
+ 
+ 	dir := MCFileDefinition cacheDir.
+ 	
+ 	^ (self zip membersMatching: 'files/*') collect: [:m | m extractInDirectory: dir. m localFileName ].
+ !

Item was changed:
  ----- Method: MCMethodExternalFieldDefinition class>>isModelFor: (in category 'as yet unclassified') -----
+ isModelFor: selectorString
- isModelFor: selector
  
+ 	^ selectorString = 'fields'!
- 	^ selector = 'fields'!

Item was changed:
  MCScriptDefinition subclass: #MCPostscriptDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
- 	category: 'Monticello-Base-Modeling'!

Item was changed:
  ----- Method: MCSnapshotBrowser>>visibleCategories (in category 'listing') -----
  visibleCategories
+ 	| cl |
+ 	cl := (self packageClasses collect: [:ea | ea category]) 
+ 			asSet asSortedCollection 
+ 			add: self extensionsCategory;
+ 			yourself.
+ 			
+ 	self fileDefinitions size > 0 ifTrue: [ cl add: self filesCategory ].
+ 	
+ 	^ cl!
- 	^ (self packageClasses collect: [:ea | ea category]) 
- 			asSet asSortedCollection add: self extensionsCategory; yourself.!

Item was changed:
  ----- Method: MCMczReader>>loadPackage (in category 'as yet unclassified') -----
  loadPackage
  	| dict |
+ 
  	dict := self parseMember: 'package'.
  	package := MCPackage named: (dict at: #name)!

Item was added:
+ MCMiscDefinition subclass: #MCFileDefinition
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Scripts'!
+ 
+ !MCFileDefinition commentStamp: 'kph 12/6/2008 02:59' prior: 0!
+ Although we are not strictly a Script, we have similar loading behaviour!

Item was added:
+ ----- Method: MCFileDefinition>>path (in category 'as yet unclassified') -----
+ path
+ 
+ 	^ self propertyAt: #path ifAbsent: [ ]!

Item was added:
+ ----- Method: MCMczReader>>basicVersion (in category 'as yet unclassified') -----
+ basicVersion
+ 
+ 	| v |
+ 	
+ 	v := super basicVersion.
+ 	
+ 	self loadFiles.
+ 	
+ 	^ v !

Item was added:
+ ----- Method: MCPackageLoader2>>loadFiles (in category 'private') -----
+ loadFiles
+ 	MCMethodDefinition tidyCache.
+ 	self orphanage 
+ 		addOrphans: unloadableDefinitions;
+ 	 	addOrphans: errorDefinitions;
+ 		loadComplete.
+ !

Item was added:
+ ----- Method: MCFileDefinition>>pathToSnapshot (in category 'as yet unclassified') -----
+ pathToSnapshot
+ 
+ 	^ 'files/' , self uuid asString, '/', self path.
+ 	
+ !

Item was added:
+ ----- Method: FileDirectory>>entriesRecursive:on: (in category '*monticello') -----
+ entriesRecursive: isRecursive on: aCollection
+ 	
+ 	| aFD |
+ 		
+ 	self entries do: [ :dirEntry | 
+ 	
+ 		aFD := self fullNameFor: dirEntry name.
+ 
+ 		dirEntry isDirectory 
+ 			ifTrue: [ isRecursive ifTrue: [ (FileDirectory on: aFD) entriesRecursive: isRecursive on: aCollection ] ]
+ 			ifFalse: [ aCollection add: (FileDirectory on: aFD) ]
+ 	].
+  
+ 	^ aCollection!

Item was added:
+ ----- Method: MCFileDefinition>>fileSize: (in category 'as yet unclassified') -----
+ fileSize: n 
+ 
+ 	^ self propertyAt: #fileSize put: n!

Item was added:
+ ----- Method: MCFileDefinition class>>from:addTo: (in category 'as yet unclassified') -----
+ from: aPackageInfo addTo: definitions
+ 	
+ 	| entries matches trim |
+ 	
+ 	matches := aPackageInfo externalFilesMatches.
+ 	
+ 	entries := (FileDirectory default entriesAsFDs) select: [ :aFD | matches anySatisfy: [ :match | match match: aFD localName ] ].
+ 
+ 	entries addAll: (entries gather: [ :aFD | aFD allEntriesAsFDs ]).
+ 
+ 	trim := FileDirectory default fullName size + 1.
+ 		
+ 	^ entries collect: [ :aFD | definitions add: (self path: (aFD fullName allButFirst: trim) packageName: aPackageInfo name) realize ].
+ 
+ 	!

Item was added:
+ ----- Method: MCFileDefinition>>installScript (in category 'as yet unclassified') -----
+ installScript
+ 
+ 	self error!

Item was added:
+ ----- Method: MCDefinition>>isFileDefinition (in category 'testing') -----
+ isFileDefinition
+ 
+ 	^ false!

Item was changed:
  MCVersionReader subclass: #MCMczReader
+ 	instanceVariableNames: 'zip snapshot infoCache'
- 	instanceVariableNames: 'zip infoCache'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Base-Storing'!

Item was added:
+ ----- Method: MCFileDefinition class>>path:packageName: (in category 'as yet unclassified') -----
+ path: aString packageName: packageString
+ 	^ self instanceLike: (self new initializeWithPath: aString packageName: packageString)!

Item was changed:
  ----- Method: MCVersion class>>package:info: (in category 'instance creation') -----
  package: aPackage info: aVersionInfo
+ 	^ self package: aPackage info: aVersionInfo snapshot: (aPackage snapshotFor: aVersionInfo)!
- 	^ self package: aPackage info: aVersionInfo snapshot: aPackage snapshot!

Item was added:
+ ----- Method: FileDirectory>>allEntriesAsFDs (in category '*monticello') -----
+ allEntriesAsFDs
+ 
+ 	^ self entriesRecursive: true on: OrderedCollection new
+  !

Item was changed:
  MCMethodDefinition subclass: #MCMethodInitializerDefinition
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Monticello-Base-Modeling-Methods'!
- 	category: 'Monticello-Base-Modeling'!
  
  !MCMethodInitializerDefinition commentStamp: 'kph 1/16/2008 09:39' prior: 0!
  MCMethodInitializerDefinition 
  
  	is loaded as a normal method.
  	at #postloadOver:, it runs itself.
  	!

Item was added:
+ ----- Method: MCFileDefinition>>isFileDefinition (in category 'as yet unclassified') -----
+ isFileDefinition
+ 
+ 	^ true!

Item was changed:
  ----- Method: MCPackageLoader2>>loadComplete (in category 'private') -----
  loadComplete
  	MCMethodDefinition tidyCache.
  	self orphanage 
  		addOrphans: unloadableDefinitions;
  	 	addOrphans: errorDefinitions;
  		loadComplete.
+ 	self loadFiles.
  !

Item was removed:
- ----- Method: MCMethodDefinition>>load (in category 'obsolete') -----
- load
- 
- 	"obsolete , only remaining so that old MC's can load this code"
- 
- 	self actualClass
- 		compile: source
- 		classified: category
- 		withStamp: timeStamp
- 		notifying: (SyntaxError new category: category).
- 		
- 	(selector == #initialize and: [ self classIsMeta ]) 
- 		ifTrue: [
- 			self actualClass soleInstance initialize.	
- 		].		
- 	!

Item was removed:
- MCMethodDefinition subclass: #MCMethodFileReferenceDefinition
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Monticello-Files'!

Item was removed:
- ----- Method: MCMethodFileReferenceDefinition class>>isModelFor: (in category 'as yet unclassified') -----
- isModelFor: selector
- 
- 	^ selector = 'files'!

Item was removed:
- ----- Method: MCPreambleDefinition>>load (in category 'as yet unclassified') -----
- load
- 	super load.
- 	self evaluate!

Item was removed:
- ----- Method: MCDefinition>>load (in category 'installing') -----
- load
- 	!

Item was removed:
- ----- Method: MCClassDefinition>>load (in category 'installing') -----
- load
- 
- 	"for test cases and original MCPackageLoader"
- 	^ self postloadOver: nil!



More information about the Packages mailing list