[Pkg] The Trunk: System-dtl.240.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 25 02:57:25 UTC 2010


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

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

Name: System-dtl.240
Author: dtl
Time: 24 January 2010, 9:51:51.331 pm
UUID: 07a9ac80-78d7-4169-b608-df3d25e0aa35
Ancestors: System-dtl.239

Remove remaining dependencies on ST80-Editors from non-MVC packages.

Remove explicit references to ST80 classes from ModalSystemWindow and various utility methods.


=============== Diff against System-dtl.239 ===============

Item was changed:
  ----- Method: SmartRefStream>>scrollControllermvslrrsmsms0 (in category 'conversion') -----
  scrollControllermvslrrsmsms0
  
+ 	^ Smalltalk at: #MouseMenuController!
- 	^ MouseMenuController!

Item was changed:
  ----- Method: SystemDictionary>>discardMVC (in category 'shrinking') -----
  discardMVC
  	"After suitable checks, strip out much of MVC from the system"
  	"Smalltalk discardMVC"
  	| keepers |
  	self flag: #bob.
  	"zapping projects"
  	self isMorphic
  		ifFalse: [self inform: 'You must be in a Morphic project to discard MVC.'.
  			^ self].
  	"Check that there are no MVC Projects"
  	(Project allProjects
  			allSatisfy: [:proj | proj isMorphic])
  		ifFalse: [(self confirm: 'Would you like a chance to remove your
  MVC projects in an orderly manner?')
  				ifTrue: [^ self].
  			(self confirm: 'If you wish, I can remove all MVC projects,
  make this project be the top project, and place
  all orphaned sub-projects of MVC parents here.
  Would you like be to do this
  and proceed to discard all MVC classes?')
  				ifTrue: [self zapMVCprojects]
  				ifFalse: [^ self]].
  	self reclaimDependents.
  	"Remove old Paragraph classes and View classes."
  	self
  		at: #Paragraph
  		ifPresent: [:paraClass | (ChangeSet superclassOrder: paraClass withAllSubclasses asArray)
  				reverseDo: [:c | c removeFromSystem]].
  	self
  		at: #View
  		ifPresent: [:viewClass | (ChangeSet superclassOrder: viewClass withAllSubclasses asArray)
  				reverseDo: [:c | c removeFromSystem]].
  	"Get rid of ParagraphEditor's ScrollController dependence"
+ 	(Smalltalk at: #ParagraphEditor) ifNotNilDo: [:paragraphEditor |
+ 		#(#markerDelta #viewDelta #scrollAmount #scrollBar #computeMarkerRegion )
+ 			do: [:sel | paragraphEditor removeSelector: sel].
+ 		paragraphEditor compile: 'updateMarker'.
+ 		"Reshape to MouseMenuController"
+ 		Compiler
+ 			evaluate: (paragraphEditor definition copyReplaceAll: 'ScrollController' with: 'MouseMenuController')].
- 	#(#markerDelta #viewDelta #scrollAmount #scrollBar #computeMarkerRegion )
- 		do: [:sel | ParagraphEditor removeSelector: sel].
- 	ParagraphEditor compile: 'updateMarker'.
- 	"Reshape to MouseMenuController"
- 	Compiler
- 		evaluate: (ParagraphEditor definition copyReplaceAll: 'ScrollController' with: 'MouseMenuController').
  	"Get rid of all Controller classes not needed by
  	ParagraphEditor and ScreenController"
  	keepers := TextMorphEditor withAllSuperclasses copyWith: ScreenController.
  	(ChangeSet superclassOrder: Controller withAllSubclasses asArray)
  		reverseDo: [:c | (keepers includes: c)
  				ifFalse: [c removeFromSystem]].
  	SystemOrganization removeCategoriesMatching: 'ST80-Paths'.
  	SystemOrganization removeCategoriesMatching: 'ST80-Symbols'.
  	SystemOrganization removeCategoriesMatching: 'ST80-Pluggable Views'.
  	self removeClassNamed: 'FormButtonCache'.
  	self removeClassNamed: 'WindowingTransformation'.
  	self removeClassNamed: 'ControlManager'.
  	self removeClassNamed: 'DisplayTextView'.
  	ScheduledControllers := nil.
  	Undeclared removeUnreferencedKeys.
  	SystemOrganization removeEmptyCategories.
  	Symbol rehash!

Item was changed:
  ----- Method: Preferences class>>noviceModeSettingChanged (in category 'reacting to change') -----
  noviceModeSettingChanged
  	"The current value of the noviceMode flag has changed;  
  	now react"
  	TheWorldMainDockingBar updateInstances.
  	PasteUpMorph allSubInstances
  		select: [:each | each isWorldMorph]
  		thenDo: [:each | each initializeDesktopCommandKeySelectors].
+ 	ParagraphEditor ifNotNilDo: [:pe | pe initialize]!
- 	ParagraphEditor initialize.!

Item was changed:
  ----- Method: SystemDictionary>>removeAllUnSentMessages (in category 'shrinking') -----
  removeAllUnSentMessages
  	"Smalltalk removeAllUnSentMessages"
  	"[Smalltalk unusedClasses do: [:c | (Smalltalk at: c) removeFromSystem]. 
  	Smalltalk removeAllUnSentMessages > 0] whileTrue."
  	"Remove all implementations of unsent messages."
  	| sels n |
  	sels := self systemNavigation allUnSentMessages.
  	"The following should be preserved for doIts, etc"
  	"needed even after #majorShrink is pulled"
  	#(#rehashWithoutBecome #compactSymbolTable #rebuildAllProjects #browseAllSelect:  #lastRemoval #scrollBarValue: vScrollBarValue: #scrollBarMenuButtonPressed: #withSelectionFrom: #to: #removeClassNamed: #dragon: #hilberts: #mandala: #web #test3 #factorial #tinyBenchmarks #benchFib #newDepth: #restoreAfter: #forgetDoIts #zapAllMethods #obsoleteClasses #removeAllUnSentMessages #abandonSources #removeUnreferencedKeys #reclaimDependents #zapOrganization #condenseChanges #browseObsoleteReferences #subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: #methodsFor:stamp: #methodsFor:stamp:prior: #instanceVariableNames: #startTimerInterruptWatcher #unusedClasses )
  		do: [:sel | sels
  				remove: sel
  				ifAbsent: []].
  	"The following may be sent by perform: in dispatchOnChar..."
+ 	(Smalltalk at: #ParagraphEditor) ifNotNilDo: [:paragraphEditor |
+ 		(paragraphEditor classPool at: #CmdActions) asSet
+ 			do: [:sel | sels
+ 					remove: sel
+ 					ifAbsent: []].
+ 		(paragraphEditor classPool at: #ShiftCmdActions) asSet
+ 			do: [:sel | sels
+ 					remove: sel
+ 					ifAbsent: []]].
- 	(ParagraphEditor classPool at: #CmdActions) asSet
- 		do: [:sel | sels
- 				remove: sel
- 				ifAbsent: []].
- 	(ParagraphEditor classPool at: #ShiftCmdActions) asSet
- 		do: [:sel | sels
- 				remove: sel
- 				ifAbsent: []].
  	sels size = 0
  		ifTrue: [^ 0].
  	n := 0.
  	self systemNavigation
  		allBehaviorsDo: [:x | n := n + 1].
  	'Removing ' , sels size printString , ' messages . . .'
  		displayProgressAt: Sensor cursorPoint
  		from: 0
  		to: n
  		during: [:bar | 
  			n := 0.
  			self systemNavigation
  				allBehaviorsDo: [:class | 
  					bar value: (n := n + 1).
  					sels
  						do: [:sel | class basicRemoveSelector: sel]]].
  	^ sels size!

Item was changed:
  ----- Method: SystemDictionary>>presumedSentMessages (in category 'shrinking') -----
  presumedSentMessages   | sent |
  "Smalltalk presumedSentMessages"
  
  	"The following should be preserved for doIts, etc"
  	sent := IdentitySet new.
  	#( rehashWithoutBecome compactSymbolTable rebuildAllProjects
  		browseAllSelect:  lastRemoval
  		scrollBarValue: vScrollBarValue: scrollBarMenuButtonPressed: 
  		withSelectionFrom:  to: removeClassNamed:
  		dragon: hilberts: mandala: web test3 factorial tinyBenchmarks benchFib
  		newDepth: restoreAfter: forgetDoIts zapAllMethods obsoleteClasses
  		removeAllUnSentMessages abandonSources removeUnreferencedKeys
  		reclaimDependents zapOrganization condenseChanges browseObsoleteReferences
  		subclass:instanceVariableNames:classVariableNames:poolDictionaries:category:
  		methodsFor:stamp: methodsFor:stamp:prior: instanceVariableNames:
  		startTimerInterruptWatcher unusedClasses) do:
  		[:sel | sent add: sel].
  	"The following may be sent by perform: in dispatchOnChar..."
+ 	(Smalltalk at: #ParagraphEditor) ifNotNilDo: [:paragraphEditor |
+ 		(paragraphEditor classPool at: #CmdActions) asSet do:
+ 			[:sel | sent add: sel].
+ 		(paragraphEditor classPool at: #ShiftCmdActions) asSet do:
+ 			[:sel | sent add: sel]].
- 	(ParagraphEditor classPool at: #CmdActions) asSet do:
- 		[:sel | sent add: sel].
- 	(ParagraphEditor classPool at: #ShiftCmdActions) asSet do:
- 		[:sel | sent add: sel].
  	^ sent!

Item was added:
+ ----- Method: Project>>formEdit: (in category 'editors') -----
+ formEdit: aForm
+ 	"Start up an instance of the form editor on a form."
+  
+ 	self subclassResponsibility!



More information about the Packages mailing list