The Trunk: System-nice.953.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: System-nice.953.mcz

commits-2
Nicolas Cellier uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-nice.953.mcz

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

Name: System-nice.953
Author: nice
Time: 10 June 2017, 6:10:55.64037 pm
UUID: 0aaa0704-3786-4b18-bce0-2490f6f58d7a
Ancestors: System-eem.952

Massively replace ifNotNilDo: by ifNotNil:
We don't need two different selectors to do a single thing.

=============== Diff against System-eem.952 ===============

Item was changed:
  ----- Method: ProjectLoading class>>openName:stream:fromDirectory:withProjectView:clearOriginFlag: (in category 'loading') -----
  openName: aFileName stream: preStream fromDirectory: aDirectoryOrNil
  withProjectView: existingView clearOriginFlag: clearOriginFlag
  "Reconstitute a Morph from the selected file, presumed to
  represent a Morph saved via the SmartRefStream mechanism, and open it
  in an appropriate Morphic world."
 
      | morphOrList archive mgr substituteFont numberOfFontSubstitutes resultArray anObject project manifests dict |
  (self checkStream: preStream) ifTrue: [^ self].
  ProgressNotification signal: '0.2'.
  archive := preStream isZipArchive
  ifTrue:[ZipArchive new readFrom: preStream]
  ifFalse:[nil].
  archive ifNotNil:[
  manifests := (archive membersMatching: '*manifest').
  (manifests size = 1 and: [((dict := self parseManifest: manifests first contents) at: 'Project-Format' ifAbsent: []) = 'S-Expression'])
  ifTrue: [
  ^ (self respondsTo: #openSexpProjectDict:stream:fromDirectory:withProjectView:)
  ifTrue: [self openSexpProjectDict: dict stream: preStream fromDirectory: aDirectoryOrNil withProjectView: existingView]
  ifFalse: [self inform: 'Cannot load S-Expression format projects without Etoys' translated]]].
 
  morphOrList := self morphOrList: aFileName stream: preStream fromDirectory: aDirectoryOrNil archive: archive.
  morphOrList ifNil: [^ self].
  ProgressNotification  signal: '0.4'.
  resultArray := self fileInName: aFileName archive: archive morphOrList: morphOrList.
  anObject := resultArray first.
  numberOfFontSubstitutes := resultArray second.
  substituteFont := resultArray third.
  mgr := resultArray fourth.
  preStream close.
  ProgressNotification  signal: '0.7'.
  "the hard part is over"
  (anObject isKindOf: ImageSegment) ifTrue: [
  project := self loadImageSegment: anObject
  fromDirectory: aDirectoryOrNil
  withProjectView: existingView
  numberOfFontSubstitutes: numberOfFontSubstitutes
  substituteFont: substituteFont
  mgr: mgr.
  project noteManifestDetailsIn: dict.
  project removeParameter: #sugarProperties.
  Smalltalk at: #SugarPropertiesNotification ifPresent: [:sp |
+ sp signal ifNotNil: [:props |
- sp signal ifNotNilDo: [:props |
  project keepSugarProperties: props monitor: true]].
  clearOriginFlag ifTrue: [project forgetExistingURL].
  ProgressNotification  signal: '0.8'.
  ^ project
  ifNil: [self inform: 'No project found in this file' translated]
  ifNotNil: [ProjectEntryNotification signal: project]].
  Project current openViewAndEnter: anObject!

Item was changed:
  ----- Method: SmalltalkImage>>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"
  #(#compactSymbolTable #rebuildAllProjects #browseAllSelect:  #lastRemoval #scrollBarValue: vScrollBarValue: #scrollBarMenuButtonPressed: #withSelectionFrom: #to: #removeClassNamed: #dragon: #hilberts: #mandala: #web #test3 #factorial #tinyBenchmarks #benchFib #newDepth: #restoreAfter: #zapAllMethods #obsoleteClasses #removeAllUnSentMessages #abandonSources #removeUnreferencedKeys #reclaimDependents #zapOrganization #condenseChanges #browseObsoleteReferences #subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: #methodsFor:stamp: #methodsFor:stamp:prior: #instanceVariableNames: #unusedClasses )
  do: [:sel | sels
  remove: sel
  ifAbsent: []].
  "The following may be sent by perform: in dispatchOnChar..."
+ (Smalltalk at: #ParagraphEditor) ifNotNil: [:paragraphEditor |
- (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: []]].
  sels size = 0
  ifTrue: [^ 0].
  n := 0.
  self systemNavigation
  allBehaviorsDo: [:x | n := n + 1].
  'Removing ' , sels size printString , ' messages . . .'
  displayProgressFrom: 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: SmalltalkImage>>zapMVCprojects (in category 'shrinking') -----
  zapMVCprojects
  "Smalltalk zapMVCprojects"
 
  (Smalltalk classNamed: #MVCProject)
+ ifNotNil: [:mvc | mvc removeProjectsFromSystem]
- ifNotNilDo: [:mvc | mvc removeProjectsFromSystem]
  !