The Trunk: System-fbs.572.mcz

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

The Trunk: System-fbs.572.mcz

commits-2
Frank Shearar uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-fbs.572.mcz

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

Name: System-fbs.572
Author: fbs
Time: 20 July 2013, 11:31:03.483 pm
UUID: 590cdd39-6f6c-1949-9950-0a7d2094f56a
Ancestors: System-fbs.571

self == SmalltalkImage current when you execute these messages, or really really should be.

=============== Diff against System-fbs.571 ===============

Item was changed:
  ----- Method: SmalltalkImage>>abandonTempNames (in category 'shrinking') -----
  abandonTempNames
  "Replaces every method by a copy with no source pointer or
  encoded temp names."
  "Smalltalk abandonTempNames"
  | continue oldMethods newMethods n |
  continue := self confirm: '-- CAUTION --
  If you have backed up your system and
  are prepared to face the consequences of
  abandoning all source code, hit Yes.
  If you have any doubts, hit No,
  to back out with no harm done.'.
  continue
  ifFalse: [^ self inform: 'Okay - no harm done'].
  self garbageCollect.
  oldMethods := OrderedCollection new.
  newMethods := OrderedCollection new.
  n := 0.
  'Removing temp names to save space...'
  displayProgressFrom: 0
  to: CompiledMethod instanceCount "This is just a rough guess."
  during: [:bar | self systemNavigation
  allBehaviorsDo: [:cl | cl methodsDo: [:m |
  bar value: (n := n + 1).
  oldMethods addLast: m.
  newMethods
  addLast: (m copyWithTrailerBytes: CompiledMethodTrailer empty)]]].
  oldMethods asArray elementsExchangeIdentityWith: newMethods asArray.
+ self closeSourceFiles.
- SmalltalkImage current closeSourceFiles.
  self flag: #shouldUseAEnsureBlockToBeSureThatTheFileIsClosed.
  "sd: 17 April 2003"
  Preferences disable: #warnIfNoChangesFile.
  Preferences disable: #warnIfNoSourcesFile!

Item was changed:
  ----- Method: SmalltalkImage>>condenseChanges (in category 'housekeeping') -----
  condenseChanges
  "Move all the changes onto a compacted sources file."
  "Smalltalk condenseChanges"
  | f oldChanges |
  f := FileStream fileNamed: 'ST80.temp'.
  f header; timeStamp.
  'Condensing Changes File...'
  displayProgressFrom: 0
  to: self classNames size + self traitNames size
  during: [:bar | | count |
  count := 0.
  self
  allClassesAndTraitsDo: [:classOrTrait |
  bar value: (count := count + 1).
  classOrTrait moveChangesTo: f.
  classOrTrait putClassCommentToCondensedChangesFile: f.
  classOrTrait classSide moveChangesTo: f]].
+ self lastQuitLogPosition: f position.
- SmalltalkImage current lastQuitLogPosition: f position.
  f trailer; close.
  oldChanges := SourceFiles at: 2.
  oldChanges close.
  FileDirectory default deleteFileNamed: oldChanges name , '.old';
  rename: oldChanges name toBe: oldChanges name , '.old';
  rename: f name toBe: oldChanges name.
  self setMacFileInfoOn: oldChanges name.
  SourceFiles
  at: 2
  put: (FileStream oldFileNamed: oldChanges name)!

Item was changed:
  ----- Method: SmalltalkImage>>condenseSources (in category 'housekeeping') -----
  condenseSources
  "Move all the changes onto a compacted sources file."
  "Smalltalk condenseSources"
 
  | newSourcesFile defaultDirectory newVersion currentVersion |
  Utilities fixUpProblemsWithAllCategory.
  "The above removes any concrete, spurious '-- all --' categories, which mess up the process."
  defaultDirectory := FileDirectory default.
+ currentVersion := self sourceFileVersionString.
- currentVersion := SmalltalkImage current sourceFileVersionString.
  newVersion := UIManager default
  request: 'Please designate the version\for the new source code file...' withCRs
  initialAnswer: currentVersion.
  newVersion ifEmpty: [ ^ self ].
  newVersion = currentVersion ifTrue: [ ^ self error: 'The new source file must not be the same as the old.' ].
+ self sourceFileVersionString: newVersion.
- SmalltalkImage current sourceFileVersionString: newVersion.
 
  "Write all sources with fileIndex 1"
+ newSourcesFile := defaultDirectory newFileNamed: (defaultDirectory localNameFor: self sourcesName).
- newSourcesFile := defaultDirectory newFileNamed: (defaultDirectory localNameFor: SmalltalkImage current sourcesName).
  newSourcesFile ifNil: [ ^ self error: 'Couldn''t create source code file in\' withCRs,  defaultDirectory name].
  newSourcesFile
  header;
  timeStamp.
  'Condensing Sources File...'
  displayProgressFrom: 0
  to: self classNames size + self traitNames size
  during:
  [ :bar |
  | count |
  count := 0.
  Smalltalk allClassesAndTraitsDo:
  [ :classOrTrait |
  bar value: (count := count + 1).
  classOrTrait
  fileOutOn: newSourcesFile
  moveSource: true
  toFile: 1 ] ].
  newSourcesFile
  trailer;
  close.
 
  "Make a new empty changes file"
+ self closeSourceFiles.
- SmalltalkImage current closeSourceFiles.
  defaultDirectory
+ rename: self changesName
+ toBe: self changesName , '.old'.
+ (FileStream newFileNamed: self changesName)
- rename: SmalltalkImage current changesName
- toBe: SmalltalkImage current changesName , '.old'.
- (FileStream newFileNamed: SmalltalkImage current changesName)
  header;
  timeStamp;
  close.
+ self lastQuitLogPosition: 0.
+ self setMacFileInfoOn: self changesName.
- SmalltalkImage current lastQuitLogPosition: 0.
- self setMacFileInfoOn: SmalltalkImage current changesName.
  self setMacFileInfoOn: newSourcesFile name.
+ self openSourceFiles.
- SmalltalkImage current openSourceFiles.
  self inform: 'Source files have been rewritten to\' withCRs, newSourcesFile name, '\Check that all is well,\and then save/quit.' withCRs!

Item was changed:
  ----- Method: SmalltalkImage>>saveChangesInFileNamed: (in category 'sources, changes log') -----
  saveChangesInFileNamed: aString
  | fullChangesName |
  fullChangesName := (FileDirectory default fullNameFor: aString).
  (FileDirectory default directoryNamed:(FileDirectory dirPathFor: fullChangesName )) assureExistence.
  FileDirectory default
+ copyFileWithoutOverwriteConfirmationNamed: self changesName
- copyFileWithoutOverwriteConfirmationNamed: SmalltalkImage current changesName
  toFileNamed: fullChangesName.
  Smalltalk setMacFileInfoOn: fullChangesName.!

Item was changed:
  ----- Method: SmalltalkImage>>setGCParameters (in category 'snapshot and quit') -----
  setGCParameters
  "Adjust the VM's default GC parameters to avoid premature tenuring."
 
+ self vmParameterAt: 5 put: 4000.  "do an incremental GC after this many allocations"
+ self vmParameterAt: 6 put: 2000.  "tenure when more than this many objects survive the GC"
- SmalltalkImage current  vmParameterAt: 5 put: 4000.  "do an incremental GC after this many allocations"
- SmalltalkImage current  vmParameterAt: 6 put: 2000.  "tenure when more than this many objects survive the GC"
  !

Item was changed:
  ----- Method: SmalltalkImage>>timeStamp: (in category 'sources, changes log') -----
  timeStamp: aStream
  "Writes system version and current time on stream aStream."
 
  | dateTime |
  dateTime := Time dateAndTimeNow.
+ aStream nextPutAll: 'From ', self datedVersion, ' [', SmalltalkImage current lastUpdateString, '] on ', (dateTime at: 1) printString,
- aStream nextPutAll: 'From ', SmalltalkImage current datedVersion, ' [', SmalltalkImage current lastUpdateString, '] on ', (dateTime at: 1) printString,
  ' at ', (dateTime at: 2) printString!

Item was changed:
  ----- Method: SmalltalkImage>>wordSize (in category 'image') -----
  wordSize
  "Answer the size in bytes of an object pointer or word in the object memory.
  The value does not change for a given image, but may be modified by a SystemTracer
  when converting the image to another format. The value is cached in WordSize to
  avoid the performance overhead of repeatedly consulting the VM."
 
  "Smalltalk wordSize"
 
+ ^ WordSize ifNil: [WordSize := [self vmParameterAt: 40] on: Error do: [4]]!
- ^ WordSize ifNil: [WordSize := [SmalltalkImage current vmParameterAt: 40] on: Error do: [4]]!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-fbs.572.mcz

David T. Lewis
On Sat, Jul 20, 2013 at 10:31:11PM +0000, [hidden email] wrote:

> Frank Shearar uploaded a new version of System to project The Trunk:
> http://source.squeak.org/trunk/System-fbs.572.mcz
>
> ==================== Summary ====================
>
> Name: System-fbs.572
> Author: fbs
> Time: 20 July 2013, 11:31:03.483 pm
> UUID: 590cdd39-6f6c-1949-9950-0a7d2094f56a
> Ancestors: System-fbs.571
>
> self == SmalltalkImage current when you execute these messages, or really really should be.
>

+1

And I notice also that SmalltalkImage class>>current was fixed by Andreas
over three years ago, with the following comment:

        "Deprecated. Use Smalltalk instead."

Hard to argue with that :-)

Dave