[squeak-dev] The Trunk: System-cwp.508.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jan 2 00:03:49 UTC 2013


Colin Putney uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-cwp.508.mcz

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

Name: System-cwp.508
Author: cwp
Time: 1 January 2013, 7:02:44.065 pm
UUID: ba757102-dd85-4434-883b-f8f4f4e89285
Ancestors: System-cwp.507

Environments bootstrap - stage 3

=============== Diff against System-cwp.507 ===============

Item was changed:
  ----- Method: InternalTranslator>>scanFrom: (in category 'fileIn/fileOut') -----
  scanFrom: aStream 
+ 	^ self scanFrom: aStream environment: Environment default!
- 	"Read a definition of dictionary.  
- 	Make sure current locale corresponds my locale id"
- 	| aString newTranslations assoc currentPlatform |
- 	newTranslations := Dictionary new.
- 	currentPlatform := Locale currentPlatform.
- 	[Locale
- 		currentPlatform: (Locale localeID: id).
- 	[aString := aStream nextChunk withSqueakLineEndings.
- 	aString size > 0]
- 		whileTrue: [assoc := Compiler evaluate: aString.
- 			assoc value = ''
- 				ifTrue: [self class registerPhrase: assoc key]
- 				ifFalse: [newTranslations add: assoc]]]
- 		ensure: [Locale currentPlatform: currentPlatform].
- 	self mergeTranslations: newTranslations!

Item was changed:
  ----- Method: NaturalLanguageTranslator>>scanFrom: (in category 'fileIn/fileOut') -----
  scanFrom: aStream 
+ 	^ self scanFrom: aStream environment: Environment default!
- 	"Read a definition of dictionary.  
- 	Make sure current locale corresponds my locale id"
- 	| newTranslations currentPlatform |
- 	newTranslations := Dictionary new.
- 	currentPlatform := Locale currentPlatform.
- 	[ | aString assoc |
- 	Locale
- 		currentPlatform: (Locale localeID: id).
- 	[aString := aStream nextChunk withSqueakLineEndings.
- 	aString size > 0]
- 		whileTrue: [assoc := Compiler evaluate: aString.
- 			assoc value = ''
- 				ifTrue: [self class registerPhrase: assoc key]
- 				ifFalse: [newTranslations add: assoc]]]
- 		ensure: [Locale currentPlatform: currentPlatform].
- 	self mergeTranslations: newTranslations!

Item was changed:
  ----- Method: SmalltalkImage>>cleanOutUndeclared (in category 'housekeeping') -----
  cleanOutUndeclared 
+ 	globals undeclared removeUnreferencedKeys!
- 	Undeclared removeUnreferencedKeys!

Item was changed:
  ----- Method: SmalltalkImage>>recreateSpecialObjectsArray (in category 'special objects') -----
  recreateSpecialObjectsArray
  	"Smalltalk recreateSpecialObjectsArray"
  	
  	"To external package developers:
  	**** DO NOT OVERRIDE THIS METHOD.  *****
  	If you are writing a plugin and need additional special object(s) for your own use, 
  	use addGCRoot() function and use own, separate special objects registry "
  	
  	"The Special Objects Array is an array of objects used by the Squeak virtual machine.
  	 Its contents are critical and accesses to it by the VM are unchecked, so don't even
  	 think of playing here unless you know what you are doing."
  	| newArray |
  	newArray := Array new: 56.
  	"Nil false and true get used throughout the interpreter"
  	newArray at: 1 put: nil.
  	newArray at: 2 put: false.
  	newArray at: 3 put: true.
  	"This association holds the active process (a ProcessScheduler)"
+ 	newArray at: 4 put: (self bindingOf: #Processor).
- 	newArray at: 4 put: (self associationAt: #Processor).
  	"Numerous classes below used for type checking and instantiation"
  	newArray at: 5 put: Bitmap.
  	newArray at: 6 put: SmallInteger.
  	newArray at: 7 put: ByteString.
  	newArray at: 8 put: Array.
  	newArray at: 9 put: Smalltalk.
  	newArray at: 10 put: Float.
  	newArray at: 11 put: MethodContext.
  	newArray at: 12 put: BlockContext.
  	newArray at: 13 put: Point.
  	newArray at: 14 put: LargePositiveInteger.
  	newArray at: 15 put: Display.
  	newArray at: 16 put: Message.
  	newArray at: 17 put: CompiledMethod.
  	newArray at: 18 put: (self specialObjectsArray at: 18).
  	"(low space Semaphore)"
  	newArray at: 19 put: Semaphore.
  	newArray at: 20 put: Character.
  	newArray at: 21 put: #doesNotUnderstand:.
  	newArray at: 22 put: #cannotReturn:.
  	newArray at: 23 put: nil. "This is the process signalling low space."
  	"An array of the 32 selectors that are compiled as special bytecodes,
  	 paired alternately with the number of arguments each takes."
  	newArray at: 24 put: #(	#+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
  							#* 1 #/ 1 #\\ 1 #@ 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
  							#at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
  							#blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
  	"An array of the 255 Characters in ascii order.
  	 Cog inlines table into machine code at: prim so do not regenerate it."
  	newArray at: 25 put: (self specialObjectsArray at: 25).
  	newArray at: 26 put: #mustBeBoolean.
  	newArray at: 27 put: ByteArray.
  	newArray at: 28 put: Process.
  	"An array of up to 31 classes whose instances will have compact headers"
  	newArray at: 29 put: self compactClassesArray.
  	newArray at: 30 put: (self specialObjectsArray at: 30). "(delay Semaphore)"
  	newArray at: 31 put: (self specialObjectsArray at: 31). "(user interrupt Semaphore)"
  	"Entries 32 - 34 unreferenced. Previously these contained prototype instances to be copied for fast initialization"
  	newArray at: 32 put: nil. "was (Float new: 2)"
  	newArray at: 33 put: nil. "was (LargePositiveInteger new: 4)"
  	newArray at: 34 put: nil. "was Point new"
  	newArray at: 35 put: #cannotInterpret:.
  	"Note: This must be fixed once we start using context prototypes (yeah, right)"
  	"(MethodContext new: CompiledMethod fullFrameSize)."
  	newArray at: 36 put: (self specialObjectsArray at: 36). "Is the prototype MethodContext (unused by the VM)"
  	newArray at: 37 put: BlockClosure.
  	"(BlockContext new: CompiledMethod fullFrameSize)."
  	newArray at: 38 put: (self specialObjectsArray at: 38). "Is the prototype BlockContext (unused by the VM)"
  	"array of objects referred to by external code"
  	newArray at: 39 put: (self specialObjectsArray at: 39).	"preserve external semaphores"
  	newArray at: 40 put: nil. "Reserved for Mutex in Cog VMs"
  	newArray at: 41 put: nil. "Reserved for a LinkedList instance for overlapped calls in CogMT"
  	"finalization Semaphore"
  	newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]).
  	newArray at: 43 put: LargeNegativeInteger.
  	"External objects for callout.
  	 Note: Written so that one can actually completely remove the FFI."
  	newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
  	newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
  	newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
  	newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
  	newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
  	newArray at: 49 put: #aboutToReturn:through:.
  	newArray at: 50 put: #run:with:in:.
  	"51 reserved for immutability message"
  	"newArray at: 51 put: #attemptToAssign:withIndex:."
  	newArray at: 52 put: #(nil "nil => generic error" #'bad receiver'
  							#'bad argument' #'bad index'
  							#'bad number of arguments'
  							#'inappropriate operation'  #'unsupported operation'
  							#'no modification' #'insufficient object memory'
  							#'insufficient C memory' #'not found' #'bad method'
  							#'internal error in named primitive machinery'
  							#'object may move').
  	"53 to 55 are for Alien"
  	newArray at: 53 put: (self at: #Alien ifAbsent: []).
  	newArray at: 54 put: #invokeCallback:stack:registers:jmpbuf:.
  	newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
  
  	"Weak reference finalization"
  	newArray at: 56 put: (self at: #WeakFinalizationList ifAbsent: []).
  
  	"Now replace the interpreter's reference in one atomic operation"
  	self specialObjectsArray becomeForward: newArray
  	!

Item was changed:
  ----- Method: SmalltalkImage>>unloadAllKnownPackages (in category 'shrinking') -----
  unloadAllKnownPackages
  	"Unload all packages we know how to unload and reload"
  
  	"Prepare unloading"
  	Smalltalk zapMVCprojects.
  	Flaps disableGlobalFlaps: false.
  	StandardScriptingSystem removeUnreferencedPlayers.
  	Project removeAllButCurrent.
  	#('Morphic-UserObjects' 'EToy-UserObjects' 'Morphic-Imported' )
  		do: [:each | SystemOrganization removeSystemCategory: each].
  	Smalltalk at: #ServiceRegistry ifPresent:[:aClass|
  		SystemChangeNotifier uniqueInstance
  			noMoreNotificationsFor: aClass.
  	].
  	World removeAllMorphs.
  
  	"Go unloading"
  	#(	'ReleaseBuilder' 'ScriptLoader'
  		'311Deprecated' '39Deprecated'
  		'Universes' 'SMLoader' 'SMBase' 'Installer-Core'
  		'VersionNumberTests' 'VersionNumber'
  		'Services-Base' 'PreferenceBrowser' 'Nebraska'
  		'ToolBuilder-MVC' 'ST80'
  		'CollectionsTests' 'GraphicsTests' 'KernelTests'  'MorphicTests' 
  		'MultilingualTests' 'NetworkTests' 'ToolsTests' 'TraitsTests'
  		'SystemChangeNotification-Tests' 'FlexibleVocabularies' 
  		'EToys' 'Protocols' 'XML-Parser' 'Tests' 'SUnitGUI'
  		'Help-Squeak' 'HelpSystem' 'SystemReporter'
  	) do: [:pkgName| 
  			(MCPackage named: pkgName) unload.
  			MCMcmUpdater disableUpdatesOfPackage: pkgName.
  			].
  	"Traits use custom unload"
  	Smalltalk at: #Trait ifPresent:[:aClass| aClass unloadTraits].
  
  	"Post-unload cleanup"
  	MCWorkingCopy flushObsoletePackageInfos.
  	SystemOrganization removeSystemCategory: 'UserObjects'.
  	Presenter defaultPresenterClass: nil.
  	World dumpPresenter.
  	ScheduledControllers := nil.
  	Preferences removePreference: #allowEtoyUserCustomEvents.
  	SystemOrganization removeEmptyCategories.
  	ChangeSet removeChangeSetsNamedSuchThat:[:cs | (cs == ChangeSet current) not].
+ 	globals undeclared removeUnreferencedKeys.
- 	Undeclared removeUnreferencedKeys.
  	StandardScriptingSystem initialize.
  	MCFileBasedRepository flushAllCaches.
  	MCDefinition clearInstances.
  	Behavior flushObsoleteSubclasses.
  	ChangeSet current clear.
  	ChangeSet current name: 'Unnamed1'.
  	Smalltalk flushClassNameCache.
  	Smalltalk at: #Browser ifPresent:[:br| br initialize].
  	DebuggerMethodMap voidMapCache.
  	DataStream initialize.
  	AppRegistry removeObsolete.
  	FileServices removeObsolete.
  	Preferences removeObsolete.
  	TheWorldMenu removeObsolete.
  	Smalltalk garbageCollect.
  	Symbol compactSymbolTable.
  	TheWorldMainDockingBar updateInstances.
  	MorphicProject defaultFill: (Color gray: 0.9).
  	World color: (Color gray: 0.9).
  !

Item was changed:
  ----- Method: SystemDictionary>>at:put: (in category 'dictionary access') -----
  at: aKey put: anObject 
  	"Override from Dictionary to check Undeclared and fix up
  	references to undeclared variables."
  	| index element |
  	(self includesKey: aKey) ifFalse: 
+ 		[self declare: aKey from: (self at: #Undeclared).
- 		[self declare: aKey from: Undeclared.
  		self flushClassNameCache].
  	super at: aKey put: anObject.
  	^ anObject!



More information about the Squeak-dev mailing list