The Trunk: Morphic-dtl.1360.mcz

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

The Trunk: Morphic-dtl.1360.mcz

commits-2
David T. Lewis uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-dtl.1360.mcz

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

Name: Morphic-dtl.1360
Author: dtl
Time: 11 November 2017, 4:04:34.153784 pm
UUID: 0e1f3870-5f57-4dc6-a1e7-5d8ce68b71b5
Ancestors: Morphic-dtl.1359

World global elimination. Once the current project has been entered, Project current world == World. Begin eliminating references to the global variable World in cases where it is not required.

=============== Diff against Morphic-dtl.1359 ===============

Item was changed:
  ----- Method: ComplexProgressIndicator>>backgroundWorldDisplay (in category 'as yet unclassified') -----
  backgroundWorldDisplay
 
  self flag: #bob. "really need a better way to do this"
 
  "World displayWorldSafely."
 
  "ugliness to try to track down a possible error"
 
 
+ [Project current world displayWorld] ifError: [ :a :b |
- [World displayWorld] ifError: [ :a :b |
  | f |
  stageCompleted := 999.
  f := FileDirectory default fileNamed: 'bob.errors'.
  f nextPutAll: a printString,'  ',b printString; cr; cr.
  f nextPutAll: 'worlds equal ',(formerWorld == World) printString; cr; cr.
  f nextPutAll: thisContext longStack; cr; cr.
  f nextPutAll: formerProcess suspendedContext longStack; cr; cr.
  f close. Beeper beep.
  ].
  !

Item was changed:
  ----- Method: Debugger class>>morphicOpenInterrupt:onProcess: (in category '*Morphic-opening') -----
  morphicOpenInterrupt: aString onProcess: interruptedProcess
  "Open a notifier in response to an interrupt. An interrupt occurs when the user types the interrupt key (cmd-. on Macs, ctrl-c or alt-. on other systems) or when the low-space watcher detects that memory is low."
  | debugger |
  <primitive: 19> "Simulation guard"
  debugger := self new.
  debugger
  process: interruptedProcess
  controller: nil
  context: interruptedProcess suspendedContext.
  debugger externalInterrupt: true.
 
  Preferences logDebuggerStackToFile ifTrue:
  [(aString includesSubstring: 'Space') & (aString includesSubstring: 'low')
  ifTrue: [Smalltalk logError: aString inContext: debugger interruptedContext to: 'LowSpaceDebug.log']
  "logging disabled for 4.3 release, see
  http://lists.squeak.org/pipermail/squeak-dev/2011-December/162503.html"
  "ifFalse: [Smalltalk logSqueakError: aString inContext: debugger interruptedContext]"].
 
+ Preferences eToyFriendly ifTrue: [Project current world stopRunningAll].
- Preferences eToyFriendly ifTrue: [World stopRunningAll].
  ^debugger
  openNotifierContents: nil label: aString;
  yourself
  !

Item was changed:
  ----- Method: Morph>>updateFromResource (in category 'fileIn/out') -----
  updateFromResource
  | pathName newMorph f |
  (pathName := self valueOfProperty: #resourceFilePath) ifNil: [^self].
  (pathName asLowercase endsWith: '.morph')
  ifTrue:
  [newMorph := (FileStream readOnlyFileNamed: pathName) fileInObjectAndCode.
  (newMorph isMorph)
  ifFalse: [^self error: 'Resource not a single morph']]
  ifFalse:
  [f := Form fromFileNamed: pathName.
  f ifNil: [^self error: 'unrecognized image file format'].
+ newMorph := Project current world drawingClass withForm: f].
- newMorph := World drawingClass withForm: f].
  newMorph setProperty: #resourceFilePath toValue: pathName.
  self owner replaceSubmorph: self by: newMorph!

Item was changed:
  ----- Method: MorphHierarchyListMorph>>createContainer (in category 'private') -----
  createContainer
  "Private - Create a container"
  | container |
  container := BorderedMorph new.
+ container extent: (Project current world extent * (1 / 4 @ (2 / 3))) rounded.
- container extent: (World extent * (1 / 4 @ (2 / 3))) rounded.
  container layoutPolicy: TableLayout new.
  container hResizing: #rigid.
  container vResizing: #rigid.
  container
  setColor: (Color gray: 0.9)
  borderWidth: 1
  borderColor: Color gray.
  container layoutInset: 0.
  "container useRoundedCorners."
  ""
  container setProperty: #morphHierarchy toValue: true.
  container setNameTo: 'Objects Hierarchy' translated.
  ""
  ^ container!

Item was changed:
  ----- Method: MorphicProject>>storeSegment (in category 'file in/out') -----
  storeSegment
  "Store my project out on the disk as an ImageSegment.  Keep the outPointers in memory.  Name it <project name>.seg.  *** Caller must be holding (Project alInstances) to keep subprojects from going out. ***"
 
  | is sizeHint |
+ (Project current world == world) ifTrue: [^ false].
- (World == world) ifTrue: [^ false].
  "self inform: 'Can''t send the current world out'."
  world isInMemory ifFalse: [^ false].  "already done"
  world ifNil: [^ false].  world presenter ifNil: [^ false].
 
  ScrapBook default emptyScrapBook.
  World checkCurrentHandForObjectToPaste.
  world releaseSqueakPages.
  sizeHint := self projectParameters at: #segmentSize ifAbsent: [0].
 
  is := ImageSegment
  copyFromRootsLocalFileFor: {world presenter. world} "world, and all Players"
  sizeHint: sizeHint.
 
  is state = #tooBig ifTrue: [^ false].
  is segment size < 2000 ifTrue: ["debugging"
  Transcript show: self name, ' only ', is segment size printString,
  'bytes in Segment.'; cr].
  self projectParameters at: #segmentSize put: is segment size.
  is extract; writeToFile: self name.
  ^ true!

Item was changed:
  ----- Method: MorphicProject>>storeSegmentNoFile (in category 'file in/out') -----
  storeSegmentNoFile
  "For testing.  Make an ImageSegment.  Keep the outPointers in memory.  Also useful if you want to enumerate the objects in the segment afterwards (allObjectsDo:)"
 
  | is |
+ (Project current world == world) ifTrue: [^ self]. " inform: 'Can''t send the current world out'."
- (World == world) ifTrue: [^ self]. " inform: 'Can''t send the current world out'."
  world isInMemory ifFalse: [^ self].  "already done"
  world ifNil: [^ self].  world presenter ifNil: [^ self].
 
  "Do this on project enter"
  World flapTabs do: [:ft | ft referent adaptToWorld: World].
  "Hack to keep the Menu flap from pointing at my project"
  "Preferences setPreference: #useGlobalFlaps toValue: false."
  "Utilities globalFlapTabsIfAny do:
  [:aFlapTab | Utilities removeFlapTab: aFlapTab keepInList: false].
  Utilities clobberFlapTabList. "
  "project world deleteAllFlapArtifacts."
  "self currentWorld deleteAllFlapArtifacts. "
  ScrapBook default emptyScrapBook.
  World checkCurrentHandForObjectToPaste2.
 
  is := ImageSegment
  copyFromRootsLocalFileFor: {world presenter. world} "world, and all Players"
  sizeHint: 0.
 
  is segment size < 800 ifTrue: ["debugging"
  Transcript show: self name, ' did not get enough objects'; cr.  ^ Beeper beep].
 
  is extract.
  "is instVarAt: 2 put: is segment clone." "different memory"!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>startMessageTally (in category 'menu actions') -----
  startMessageTally
+ | world |
+ world := Project current world.
  (self confirm: 'MessageTally will start now,
  and stop when the cursor goes
  to the top of the screen') ifTrue:
  [MessageTally spyOn:
+ [[Sensor peekPosition y > 0] whileTrue: [world doOneCycle]]]!
- [[Sensor peekPosition y > 0] whileTrue: [World doOneCycle]]]!

Item was changed:
  ----- Method: TheWorldMenu>>startMessageTally (in category 'commands') -----
  startMessageTally
+ | world |
+ world := Project current world.
-
  (self confirm: 'MessageTally will start now,
  and stop when the cursor goes
  to the top of the screen') ifTrue:
  [MessageTally spyOn:
+ [[Sensor peekPosition y > 0] whileTrue: [world doOneCycle]]]!
- [[Sensor peekPosition y > 0] whileTrue: [World doOneCycle]]]!