[squeak-dev] The Trunk: System-dtl.976.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Nov 16 01:01:45 UTC 2017


David T. Lewis uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-dtl.976.mcz

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

Name: System-dtl.976
Author: dtl
Time: 15 November 2017, 8:01:35.111626 pm
UUID: cde703e1-3df1-4d6a-bde9-df95a3215ab6
Ancestors: System-eem.975

Remove unnecessary references to global World.

=============== Diff against System-eem.975 ===============

Item was changed:
  ----- Method: AutoStart class>>startUp: (in category 'initialization') -----
  startUp: resuming
  	"The image is either being newly started (resuming is true), or it's just been snapshotted.
  	If this has just been a snapshot, skip all the startup stuff."
  
  	| startupParameters launchers |
  	self active ifTrue: [^self].
  	self active: true.
  	resuming ifFalse: [^self].
  
  	HTTPClient determineIfRunningInBrowser.
  	startupParameters := Smalltalk namedArguments.
  	(startupParameters includesKey: 'apiSupported' asUppercase )
  		ifTrue: [
  			HTTPClient browserSupportsAPI: ((startupParameters at: 'apiSupported' asUppercase) asUppercase = 'TRUE').
  			HTTPClient isRunningInBrowser
  				ifFalse: [HTTPClient isRunningInBrowser: true]].
  
+ 	Project current world ifNotNil: [:w | w install. w firstHand position: 100 @ 100 ].
- 	World ifNotNil: [:w | w install. w firstHand position: 100 @ 100 ].
  			
  	"Some images might not have the UpdateStream package."
  	((self respondsTo: #checkForUpdates) and: [self checkForUpdates]) ifTrue: [^self].
  	self checkForPluginUpdate.
  	launchers := self installedLaunchers collect: [:launcher |
  		launcher new].
  	launchers do: [:launcher |
  		launcher parameters: startupParameters].
  	launchers do: [:launcher |
  		Project current addDeferredUIMessage: [launcher startUp]]!

Item was changed:
  ----- Method: ExternalDropHandler class>>defaultImageHandler (in category 'private') -----
  defaultImageHandler
  	^ExternalDropHandler
  		type: 'image/'
  		extension: nil
  		action: [:stream :pasteUp :event |
  			| image sketch |
  			stream binary.
  			image := Form fromBinaryStream: stream contents asByteArray readStream.
  			Project current resourceManager 
  				addResource: image 
  				url: (FileDirectory urlForFileNamed: stream name) asString.
+ 			sketch := Project current world drawingClass withForm: image.
- 			sketch := World drawingClass withForm: image.
  			pasteUp addMorph: sketch centeredNear: event position.
  			image := sketch := nil]!

Item was changed:
  ----- Method: Preferences class>>classicTilesSettingToggled (in category 'updating - system') -----
  classicTilesSettingToggled
  	"The current value of the largeTiles flag has changed; now react"
  
  	Smalltalk isMorphic ifTrue:
  		[Preferences universalTiles
  			ifFalse:
  				[self inform: 
  'note that this will only have a noticeable
  effect if the universalTiles preference is
  set to true, which it currently is not' translated]
  			ifTrue:
+ 				[Project current world recreateScripts]]!
- 				[World recreateScripts]]!

Item was changed:
  ----- Method: Preferences class>>largeTilesSettingToggled (in category 'updating - system') -----
  largeTilesSettingToggled
  	"The current value of the largeTiles flag has changed; now react"
  
  	Smalltalk isMorphic ifTrue:
  		[Preferences universalTiles
  			ifFalse:
  				[self inform: 
  'note that this will only have a noticeable
  effect if the universalTiles preference is
  set to true, which it currently is not' translated]
  			ifTrue:
+ 				[Project current world recreateScripts]]!
- 				[World recreateScripts]]!

Item was changed:
  ----- Method: Preferences class>>storePreferencesIn: (in category 'initialization - save/load') -----
  storePreferencesIn: aFileName 
  	| stream prefsSnapshot |
  	#(Prevailing PersonalPreferences) do:
  		[:ea |
  		 Parameters removeKey: ea ifAbsent: []].
  	stream := ReferenceStream fileNamed: aFileName.
  	stream nextPut: Parameters.
  	prefsSnapshot := preferencesDictionary copy.
  	prefsSnapshot keysAndValuesDo: [:key :pref | prefsSnapshot at: key put: pref asPreference].
  	stream nextPut: prefsSnapshot.
  	stream nextPut: (Smalltalk isMorphic 
+ 						 ifTrue:[Project current world fillStyle]
- 						 ifTrue:[World fillStyle]
  						 ifFalse:[self desktopColor]).
  	stream close!

Item was changed:
  ----- Method: Preferences class>>universalTilesSettingToggled (in category 'updating - system') -----
  universalTilesSettingToggled
  	"The current value of the universalTiles flag has changed; now react"
  
  	(self preferenceAt: #universalTiles ifAbsent: [^ self]) localToProject ifFalse:
  			[^ self inform: 
  'This is troubling -- you may regret having done that, because
  the change will apply to *all projects*, including pre-existing ones.  Unfortunately this check is done after the damage is done, so you
  may be hosed.  Fortunately, however, you can simply reverse your choice right now and perhaps no deep damage will have been done.'].
  
  	self universalTiles  "User just switched project to classic tiles"
  		ifFalse:
  			[self inform: 
  'CAUTION -- if you had any scripted objects in
  this project that already used universal tiles, 
  there is no reasonable way to go back to classic
  tiles.  Recommended course of action in that case:
  just toggle this preference right back to true.']
  		ifTrue:
  			[Preferences capitalizedReferences ifFalse:
  				[Preferences enable: #capitalizedReferences.
  				self inform: 
  'Note that the "capitalizedReferences" flag
  has now been automatically set to true for
  you, since this is required for the use of
  universal tiles.'].
+ 			Project current isMorphic ifTrue:
+ 				[Project current world recreateScripts]]!
- 			World isMorph ifTrue:
- 				[World recreateScripts]]!

Item was changed:
  ----- Method: ResourceManager>>formChangedReminder (in category 'private') -----
  formChangedReminder
+ 	^[Project current world newResourceLoaded].!
- 	^[World newResourceLoaded].!

Item was changed:
  ----- Method: SARInstaller>>openGraphicsFile: (in category 'client services') -----
  openGraphicsFile: memberOrName
  	| member morph |
  	member := self memberNamed: memberOrName.
  	member ifNil: [ ^self errorNoSuchMember: memberOrName ].
+ 	morph := (Project current world drawingClass fromStream: member contentStream binary).
- 	morph := (World drawingClass fromStream: member contentStream binary).
  	morph ifNotNil: [ morph openInWorld ].
  	self installed: member.!



More information about the Squeak-dev mailing list