The Trunk: Collections-fbs.525.mcz

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

The Trunk: Collections-fbs.525.mcz

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

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

Name: Collections-fbs.525
Author: fbs
Time: 25 July 2013, 8:21:27.078 am
UUID: 185d41d8-2d5e-554e-b8fc-46e19a07becc
Ancestors: Collections-fbs.524

SmalltalkImage current -> Smalltalk.

=============== Diff against Collections-fbs.524 ===============

Item was changed:
  ----- Method: ArrayedCollection>>restoreEndianness (in category 'objects from disk') -----
  restoreEndianness
  "This word object was just read in from a stream.  It was stored in Big Endian (Mac) format.  Reverse the byte order if the current machine is Little Endian.
  We only intend this for non-pointer arrays.  Do nothing if I contain pointers."
 
  self class isPointers | self class isWords not ifTrue: [^self].
+ Smalltalk  isLittleEndian
- SmalltalkImage current  isLittleEndian
  ifTrue:
  [Bitmap
  swapBytesIn: self
  from: 1
  to: self basicSize]!

Item was changed:
  ----- Method: PositionableStream>>fileInAnnouncing: (in category 'fileIn/Out') -----
  fileInAnnouncing: announcement
  "This is special for reading expressions from text that has been formatted
  with exclamation delimitors. The expressions are read and passed to the
  Compiler. Answer the result of compilation.  Put up a progress report with
       the given announcement as the title."
 
  | val |
  announcement
  displayProgressFrom: 0
  to: self size
  during:
  [:bar |
  [self atEnd] whileFalse:
  [bar value: self position.
  self skipSeparators.
 
  [ | chunk |
  val := (self peekFor: $!!)
  ifTrue: [(Compiler evaluate: self nextChunk logged: false) scanFrom: self]
  ifFalse:
  [chunk := self nextChunk.
  self checkForPreamble: chunk.
  Compiler evaluate: chunk logged: true]]
  on: InMidstOfFileinNotification
  do: [:ex | ex resume: true].
  self skipStyleChunk].
  self close].
  "Note:  The main purpose of this banner is to flush the changes file."
+ Smalltalk logChange: '----End fileIn of ' , self name , '----'.
- SmalltalkImage current logChange: '----End fileIn of ' , self name , '----'.
  self flag: #ThisMethodShouldNotBeThere. "sd"
  ^val!

Item was changed:
  ----- Method: PositionableStream>>fileInFor:announcing: (in category 'fileIn/Out') -----
  fileInFor: client announcing: announcement
  "This is special for reading expressions from text that has been formatted
  with exclamation delimitors. The expressions are read and passed to the
  Compiler. Answer the result of compilation.  Put up a progress report with
       the given announcement as the title.
  Does NOT handle preambles or postscripts specially."
  | val |
  announcement
  displayProgressFrom: 0
  to: self size
  during:
  [:bar |
  [self atEnd]
  whileFalse:
  [bar value: self position.
  self skipSeparators.
  [ | chunk |
  val := (self peekFor: $!!) ifTrue: [
  (Compiler evaluate: self nextChunk for: client logged: false) scanFrom: self
  ] ifFalse: [
  chunk := self nextChunk.
  self checkForPreamble: chunk.
  Compiler evaluate: chunk for: client logged: true ].
  ] on: InMidstOfFileinNotification
   do: [ :ex | ex resume: true].
  self atEnd ifFalse: [ self skipStyleChunk ]].
  self close].
  "Note:  The main purpose of this banner is to flush the changes file."
+ Smalltalk logChange: '----End fileIn of ' , self name , '----'.
- SmalltalkImage current logChange: '----End fileIn of ' , self name , '----'.
  ^ val!

Item was changed:
  ----- Method: PositionableStream>>fileInSilentlyAnnouncing: (in category 'fileIn/Out') -----
  fileInSilentlyAnnouncing: announcement
  "This is special for reading expressions from text that has been formatted
  with exclamation delimitors. The expressions are read and passed to the
  Compiler. Answer the result of compilation.  Put up a progress report with
       the given announcement as the title."
 
  | val chunk |
  [self atEnd] whileFalse:
  [self skipSeparators.
 
  [val := (self peekFor: $!!)
  ifTrue: [(Compiler evaluate: self nextChunk logged: false) scanFrom: self]
  ifFalse:
  [chunk := self nextChunk.
  self checkForPreamble: chunk.
  Compiler evaluate: chunk logged: true]]
  on: InMidstOfFileinNotification
  do: [:ex | ex resume: true].
  self skipStyleChunk].
  self close.
  "Note:  The main purpose of this banner is to flush the changes file."
+ Smalltalk  logChange: '----End fileIn of ' , self name , '----'.
- SmalltalkImage current  logChange: '----End fileIn of ' , self name , '----'.
  self flag: #ThisMethodShouldNotBeThere. "sd"
  SystemNavigation new allBehaviorsDo:
  [:cl |
  cl
  removeSelectorSimply: #DoIt;
  removeSelectorSimply: #DoItIn:].
  ^val!

Item was changed:
  ----- Method: WriteStream>>timeStamp (in category 'fileIn/Out') -----
  timeStamp
  "Append the current time to the receiver as a String."
  self nextChunkPut: "double string quotes and !!s"
+ (String streamContents: [:s | Smalltalk timeStamp: s]) printString.
- (String streamContents: [:s | SmalltalkImage current timeStamp: s]) printString.
  self cr!