[squeak-dev] The Trunk: System-pre.1047.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 20 12:56:21 UTC 2018


Patrick Rein uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-pre.1047.mcz

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

Name: System-pre.1047
Author: pre
Time: 20 December 2018, 1:56:15.427193 pm
UUID: 59e98ffb-8cee-4a39-a7c2-5096166f181c
Ancestors: System-eem.1046

Categorizes uncategorized methods in the System category.

=============== Diff against System-eem.1046 ===============

Item was changed:
+ ----- Method: ClassDiffBuilder class>>cleanUp: (in category 'initialize-release') -----
- ----- Method: ClassDiffBuilder class>>cleanUp: (in category 'as yet unclassified') -----
  cleanUp: aggressive
  
  	SeparatorSet := nil!

Item was changed:
+ ----- Method: ClassDiffBuilder class>>separatorSet (in category 'constants') -----
- ----- Method: ClassDiffBuilder class>>separatorSet (in category 'as yet unclassified') -----
  separatorSet
  
  	^SeparatorSet ifNil: [
  		SeparatorSet := CharacterSet separators copy
  			add: $'; "for variables"
  			add: $"; "for comments in mc"
  			yourself ]!

Item was changed:
+ ----- Method: DataStream class>>example (in category 'examples') -----
- ----- Method: DataStream class>>example (in category 'as yet unclassified') -----
  example
      "An example and test of DataStream/ReferenceStream.
       11/19/92 jhm: Use self testWith:."
      "DataStream example"
      "ReferenceStream example"
      | input sharedPoint |
  
      "Construct the test data."
      input := Array new: 10.
      input at: 1 put: nil.
      input at: 2 put: true.
      input at: 3 put: (Form extent: 63 @ 50 depth: 8).
  		(input at: 3) fillWithColor: Color lightBlue.
      input at: 4 put: #(3 3.0 'three').
      input at: 5 put: false.
      input at: 6 put: 1024 @ -2048.
      input at: 7 put: #x.
      input at: 8 put: (Array with: (sharedPoint := 0 @ -30000)).
      input at: 9 put: sharedPoint.
      input at: 10 put: (Character value: 16r200d).
  
      "Write it out, read it back, and return it for inspection."
      ^ self testWith: input!

Item was changed:
+ ----- Method: DataStream class>>exampleWithPictures (in category 'examples') -----
- ----- Method: DataStream class>>exampleWithPictures (in category 'as yet unclassified') -----
  exampleWithPictures
  	"DataStream exampleWithPictures"
  	| file result |
  	file := FileStream fileNamed: 'Test-Picture'.
  	file binary.
  	(DataStream on: file) nextPut: (Form fromUser).
  	file close.
  
  	file := FileStream fileNamed: 'Test-Picture'.
  	file binary.
  	result := (DataStream on: file) next.
  	file close.
  	result display.
  	^ result!

Item was changed:
+ ----- Method: DataStream class>>fileNamed: (in category 'instance creation') -----
- ----- Method: DataStream class>>fileNamed: (in category 'as yet unclassified') -----
  fileNamed: aString
  	"Here is the way to use DataStream and ReferenceStream:
  rr := ReferenceStream fileNamed: 'test.obj'.
  rr nextPut: <your object>.
  rr close.
  "
  
  	| strm |
  	strm := self on: (FileStream fileNamed: aString).		"will be binary"
  	strm byteStream setFileTypeToObject.
  		"Type and Creator not to be text, so can attach correctly to an email msg"
  	^ strm!

Item was changed:
+ ----- Method: DataStream class>>initialize (in category 'class initialization') -----
- ----- Method: DataStream class>>initialize (in category 'as yet unclassified') -----
  initialize
  	"TypeMap maps Smalltalk classes to type ID numbers which identify the data stream primitive formats.  nextPut: writes these IDs to the data stream.  NOTE: Changing these type ID numbers will invalidate all extant data stream files.  Adding new ones is OK.  
  	Classes named here have special formats in the file.  If such a class has a subclass, it will use type 9 and write correctly.  It will just be slow.  (Later write the class name in the special format, then subclasses can use the type also.)
  	 See nextPut:, next, typeIDFor:, & ReferenceStream>>isAReferenceType:"
  	"DataStream initialize"
  
  	| refTypes t |
  	refTypes := OrderedCollection new.
  	t := TypeMap := WeakIdentityKeyDictionary new. "It has to be weak, because some classes may go away, leaving obsolete versions in this dictionary which may make it corrupt."
  
  	t at: UndefinedObject put: 1.   refTypes add: 0.
  	t at: True put: 2.   refTypes add: 0.
  	t at: False put: 3.   refTypes add: 0.
  	t at: SmallInteger put: 4.	 refTypes add: 0.
  	t at: ByteString put: 5.   refTypes add: 1.
  	t at: ByteSymbol put: 6.   refTypes add: 1.
  	t at: ByteArray put: 7.   refTypes add: 1.
  	t at: Array put: 8.   refTypes add: 1.
  	"(type ID 9 is for arbitrary instances of any class, cf. typeIDFor:)"
  		refTypes add: 1.
  	"(type ID 10 is for references, cf. ReferenceStream>>tryToPutReference:)"
  		refTypes add: 0.
  	t at: Bitmap put: 11.   refTypes add: 1.
  	t at: Metaclass put: 12.   refTypes add: 0.
  	"Type ID 13 is used for HyperSqueak User classes that must be reconstructed."
  		refTypes add: 1.
  	t at: Float put: 14.  refTypes add: 1.
  	t at: Rectangle put: 15.  refTypes add: 1.	"Allow compact Rects."
  	"type ID 16 is an instance with short header.  See beginInstance:size:"
  		refTypes add: 1.
  self flag: #ByteArray.
  	t at: ByteString put: 17.   refTypes add: 1.	"new String format, 1 or 4 bytes of length"
  	t at: WordArray put: 18.  refTypes add: 1.	"bitmap-like"
  	t at: WordArrayForSegment put: 19.  refTypes add: 1.		"bitmap-like"
  	t at: SoundBuffer put: 20.  refTypes add: 1.	"And all other word arrays, both 
  		16-bit and 32-bit.  See methods in ArrayedCollection.  Overridden in SoundBuffer."
  	t at: CompiledMethod put: 21.  refTypes add: 1.	"special creation method"
  	"t at:  put: 22.  refTypes add: 0."
  	ReferenceStream refTypes: refTypes.		"save it"
  
  	"For all classes that are like WordArrays, store them the way ColorArray is stored.  As bits, and able to change endianness."
  	Smalltalk globals do: [:cls |
  		(cls isInMemory and: [
  			cls isBehavior and: [
  			cls isObsolete not and: [
  			cls isPointers not and: [
  			cls isVariable and: [
  			cls isWords and: [
  			(t includesKey: cls) not ] ] ] ] ] ]) 
  				ifTrue: [ t at: cls put: 20 ] ]!

Item was changed:
+ ----- Method: DataStream class>>new (in category 'instance creation') -----
- ----- Method: DataStream class>>new (in category 'as yet unclassified') -----
  new
  	^ self basicNew!

Item was changed:
+ ----- Method: DataStream class>>newFileNamed: (in category 'instance creation') -----
- ----- Method: DataStream class>>newFileNamed: (in category 'as yet unclassified') -----
  newFileNamed: aString
  	"Here is the way to use DataStream and ReferenceStream:
  rr := ReferenceStream fileNamed: 'test.obj'.
  rr nextPut: <your object>.
  rr close.
  "
  
  	| strm |
  	strm :=  self on: (FileStream newFileNamed: aString).		"will be binary"
  	strm byteStream setFileTypeToObject.
  		"Type and Creator not to be text, so can attach correctly to an email msg"
  	^ strm!

Item was changed:
+ ----- Method: DataStream class>>oldFileNamed: (in category 'instance creation') -----
- ----- Method: DataStream class>>oldFileNamed: (in category 'as yet unclassified') -----
  oldFileNamed: aString
  	"Here is the way to use DataStream and ReferenceStream:
  rr := ReferenceStream oldFileNamed: 'test.obj'.
  ^ rr nextAndClose.
  "
  
  	| strm ff |
  	ff := FileStream oldFileOrNoneNamed: aString.
  	ff ifNil: [^ nil].
  	strm := self on: (ff binary).
  	^ strm!

Item was changed:
+ ----- Method: DataStream class>>on: (in category 'instance creation') -----
- ----- Method: DataStream class>>on: (in category 'as yet unclassified') -----
  on: aStream
  	"Open a new DataStream onto a low-level I/O stream."
  
  	^ self basicNew setStream: aStream
  		"aStream binary is in setStream:"
  !

Item was changed:
+ ----- Method: DataStream class>>streamedRepresentationOf: (in category 'conversion') -----
- ----- Method: DataStream class>>streamedRepresentationOf: (in category 'as yet unclassified') -----
  streamedRepresentationOf: anObject
  
  	| file |
  	file := (RWBinaryOrTextStream on: (ByteArray new: 5000)).
  	file binary.
  	(self on: file) nextPut: anObject.
  	^file contents!

Item was changed:
+ ----- Method: DataStream class>>testWith: (in category 'tests') -----
- ----- Method: DataStream class>>testWith: (in category 'as yet unclassified') -----
  testWith: anObject
  	"As a test of DataStream/ReferenceStream, write out anObject and read it back.
  	11/19/92 jhm: Set the file type. More informative file name."
  	"DataStream testWith: 'hi'"
  	"ReferenceStream testWith: 'hi'"
  	| file result |
  
  	file := FileStream fileNamed: (self name, ' test').
  	file binary.
  	(self on: file) nextPut: anObject.
  	file close.
  
  	file := FileStream fileNamed: (self name, ' test').
  	file binary.
  	result := (self on: file) next.
  	file close.
  	(anObject class whichClassIncludesSelector: #=) == Object ifFalse:
  		[self assert: result = anObject].
  	^result!

Item was changed:
+ ----- Method: DataStream class>>unStream: (in category 'conversion') -----
- ----- Method: DataStream class>>unStream: (in category 'as yet unclassified') -----
  unStream: aString
  
  	^(self on: ((RWBinaryOrTextStream with: aString) reset; binary)) next!

Item was changed:
+ ----- Method: DiffElement class>>string: (in category 'instance creation') -----
- ----- Method: DiffElement class>>string: (in category 'as yet unclassified') -----
  string: aString
  
  	^self new
  		string: aString;
  		yourself!

Item was changed:
+ ----- Method: FileModifyingSimpleServiceEntry>>performServiceFor: (in category 'performing service') -----
- ----- Method: FileModifyingSimpleServiceEntry>>performServiceFor: (in category 'as yet unclassified') -----
  performServiceFor: anObject
  	| retval |
  	retval := super performServiceFor: anObject.
  	self changed: #fileListChanged.
  	^retval	"is this used anywhere?"!

Item was changed:
+ ----- Method: MessageTally class>>terminateTimerProcess (in category 'spying') -----
- ----- Method: MessageTally class>>terminateTimerProcess (in category 'as yet unclassified') -----
  terminateTimerProcess
  
  	Timer ifNotNil: [
  		Timer terminate.
  		Timer := nil ].
  !

Item was changed:
+ ----- Method: MethodChangeRecord>>changeType (in category 'accessing') -----
- ----- Method: MethodChangeRecord>>changeType (in category 'as yet unclassified') -----
  changeType
  
  	^ changeType!

Item was changed:
+ ----- Method: MethodChangeRecord>>currentMethod (in category 'accessing') -----
- ----- Method: MethodChangeRecord>>currentMethod (in category 'as yet unclassified') -----
  currentMethod
  
  	^ currentMethod!

Item was changed:
+ ----- Method: MethodChangeRecord>>methodInfoFromRemoval (in category 'method changes') -----
- ----- Method: MethodChangeRecord>>methodInfoFromRemoval (in category 'as yet unclassified') -----
  methodInfoFromRemoval
  	"Return an array with the source index of the last version of the method,
  	and the category in which it was defined (so it can be put back there if
  	re-accepted from a version browser)."
  
  	(changeType == #remove or: [changeType == #addedThenRemoved])
  		ifTrue: [^ infoFromRemoval]
  		ifFalse: [^ nil]!

Item was changed:
+ ----- Method: MethodChangeRecord>>noteChangeType: (in category 'all changes') -----
- ----- Method: MethodChangeRecord>>noteChangeType: (in category 'as yet unclassified') -----
  noteChangeType: newChangeType
  
  	(changeType == #addedThenRemoved and: [newChangeType == #change])
  		ifTrue: [changeType := #add]
  		ifFalse: [changeType := newChangeType]!

Item was changed:
+ ----- Method: MethodChangeRecord>>noteMethodInfoFromRemoval: (in category 'method changes') -----
- ----- Method: MethodChangeRecord>>noteMethodInfoFromRemoval: (in category 'as yet unclassified') -----
  noteMethodInfoFromRemoval: info
  	"Store an array with the source index of the last version of the method,
  	and the category in which it was defined (so it can be put back there if
  	re-accepted from a version browser)."
  
  	infoFromRemoval := info!

Item was changed:
+ ----- Method: MethodChangeRecord>>noteNewMethod: (in category 'method changes') -----
- ----- Method: MethodChangeRecord>>noteNewMethod: (in category 'as yet unclassified') -----
  noteNewMethod: newMethod
  	"NEVER do this. It is evil."
  	currentMethod := nil.!

Item was changed:
+ ----- Method: MethodChangeRecord>>printOn: (in category 'printing') -----
- ----- Method: MethodChangeRecord>>printOn: (in category 'as yet unclassified') -----
  printOn: strm
  
  	super printOn: strm.
  	strm nextPutAll: ' ('; print: changeType; nextPutAll: ')'!

Item was changed:
+ ----- Method: MethodChangeRecord>>priorMethod: (in category 'method changes') -----
- ----- Method: MethodChangeRecord>>priorMethod: (in category 'as yet unclassified') -----
  priorMethod: ignored
  
  	"We do not save original versions of changed methods because we only
  	revoke changes at the level of entire classes, and that is done by
  	restoration of the entire methodDictionary."!

Item was changed:
+ ----- Method: MethodChangeRecord>>storeDataOn: (in category 'objects from disk') -----
- ----- Method: MethodChangeRecord>>storeDataOn: (in category 'as yet unclassified') -----
  storeDataOn: aDataStream
  	| oldMethod |
  	oldMethod := currentMethod.
  	currentMethod := nil.
  	super storeDataOn: aDataStream.
  	currentMethod := oldMethod.
  !

Item was changed:
+ ----- Method: NaturalLanguageFormTranslator class>>bitmapForJapanese (in category 'japanese locale') -----
- ----- Method: NaturalLanguageFormTranslator class>>bitmapForJapanese (in category 'as yet unclassified') -----
  bitmapForJapanese
  
  	^ (Form
  	extent: 54 at 17
  	depth: 16
  	fromArray: #( 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65536 0 1 65537 65537 65537 65537 0 0 0 0 1 0 0 0 0 65537 65537 1 65537 65537 65536 1 0 0 0 1 0 0 1 0 0 0 1 0 0 0 0 1 0 0 0 0 0 0 0 1 0 0 0 65536 0 0 65536 0 0 1 0 0 0 1 0 0 0 0 1 0 0 0 1 65537 65537 65536 1 0 0 0 1 0 0 65536 0 0 1 0 0 0 1 0 1 65537 65537 65537 65537 65537 65537 0 0 0 1 65537 65537 0 0 1 0 1 0 0 0 1 0 0 0 1 0 0 0 0 65537 65536 0 0 0 65537 65537 0 65536 1 0 0 0 65536 1 0 0 0 1 65537 65537 65537 65537 0 0 0 1 1 1 0 0 0 0 0 0 65536 1 0 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 0 1 1 1 0 0 0 65537 65537 65537 65537 65537 65537 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 0 65536 1 0 65536 0 0 0 0 0 0 0 0 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 1 0 1 0 1 0 0 65537 65537 1 65537 65537 65536 0 0 65536 1 0 0 0 1 0 0 0 1 0 0 65536 65537 65537 65537 65536 65536 0 65536 1 1 0 0 65536 0 0 65536 0 65536 0 0 1 0 0 0 1 0 1 0 0 1 0 0
  1 0 65536 1 1 0 0 65536 0 1 0 0 65536 0 0 1 65537 65537 65537 65537 0 0 0 0 1 0 0 0 0 65537 65537 1 65537 65537 65536 0 1 0 0 1 0 0 0 0 0 0 0 0 0 0 0 1 0 0 0 0 0 0 0 0 0 0 0 65536 0 0 0 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 0 0)
  	offset: 0 at 0)!

Item was changed:
+ ----- Method: NaturalLanguageFormTranslator class>>initializeJapaneseBitmap (in category 'japanese locale') -----
- ----- Method: NaturalLanguageFormTranslator class>>initializeJapaneseBitmap (in category 'as yet unclassified') -----
  initializeJapaneseBitmap
  
  	(self localeID: (LocaleID isoString: 'ja')) name: 'LanguageNameInNativeLanguage' form: self bitmapForJapanese.
  !

Item was changed:
+ ----- Method: ProjectEntryNotification class>>signal: (in category 'exceptionInstantiator') -----
- ----- Method: ProjectEntryNotification class>>signal: (in category 'as yet unclassified') -----
  signal: aProject
  
  	| ex |
  	ex := self new.
  	ex projectToEnter: aProject.
  	^ex signal: 'Entering ',aProject printString!

Item was changed:
+ ----- Method: RenamedClassSourceReader class>>formerClassName:methodsFor:stamp: (in category 'instance creation') -----
- ----- Method: RenamedClassSourceReader class>>formerClassName:methodsFor:stamp: (in category 'as yet unclassified') -----
  formerClassName: formerClassName methodsFor: aCategory stamp: aString
  
  	^self new
  		setClass: formerClassName 
  		category: aCategory 
  		changeStamp: aString!

Item was changed:
+ ----- Method: RenamedClassSourceReader class>>scanner (in category 'instance creation') -----
- ----- Method: RenamedClassSourceReader class>>scanner (in category 'as yet unclassified') -----
  scanner
  
  	^self new!

Item was changed:
+ ----- Method: RenamedClassSourceReader>>scanFrom: (in category 'fileIn/Out') -----
- ----- Method: RenamedClassSourceReader>>scanFrom: (in category 'as yet unclassified') -----
  scanFrom: aStream
  
  	self flag: #bob. 	"should this ever happen?"
  	self halt.!

Item was changed:
+ ----- Method: RenamedClassSourceReader>>scanFromNoCompile: (in category 'fileIn/Out') -----
- ----- Method: RenamedClassSourceReader>>scanFromNoCompile: (in category 'as yet unclassified') -----
  scanFromNoCompile: aStream
  
  	self flag: #bob. 	"should this ever happen?"
  	self halt.!

Item was changed:
+ ----- Method: RenamedClassSourceReader>>scanFromNoCompile:forSegment: (in category 'fileIn/Out') -----
- ----- Method: RenamedClassSourceReader>>scanFromNoCompile:forSegment: (in category 'as yet unclassified') -----
  scanFromNoCompile: aStream forSegment: anImageSegment
  	"Just move the source code for the methods from aStream."
  	| methodText d |
  
  	[
  		(methodText _ aStream nextChunkText) size > 0
  	] whileTrue: [
  		(SourceFiles at: 2) ifNotNil: [
  			d _ Dictionary new.
  			d
  				at: #oldClassName put: class;		"may be 'Player1' or 'Player1 class'"
  				at: #methodText put: methodText;
  				at: #changeStamp put: changeStamp;
  				at: #category put: category.
  			anImageSegment acceptSingleMethodSource: d.
  		]
  	]!

Item was changed:
+ ----- Method: TextSqkProjectLink>>analyze: (in category 'initialize-release') -----
- ----- Method: TextSqkProjectLink>>analyze: (in category 'as yet unclassified') -----
  analyze: aString
  
  	^url := aString!

Item was changed:
+ ----- Method: TextSqkProjectLink>>writeScanOn: (in category 'fileIn/fileOut') -----
- ----- Method: TextSqkProjectLink>>writeScanOn: (in category 'as yet unclassified') -----
  writeScanOn: strm
  
  	strm nextPut: $p; nextPutAll: url; nextPut: $;!

Item was changed:
+ ----- Method: TranslatedReceiverFinder class>>makeJapaneseTranslationFile (in category 'japanese locale') -----
- ----- Method: TranslatedReceiverFinder class>>makeJapaneseTranslationFile (in category 'as yet unclassified') -----
  makeJapaneseTranslationFile
  	| t n |
  	NaturalLanguageTranslator initializeKnownPhrases.
  	t := TranslatedReceiverFinder new senders.
  	n := NaturalLanguageTranslator
  				localeID: (LocaleID isoLanguage: 'ja').
  	t
  		do: [:w | 
  			NaturalLanguageTranslator registerPhrase: w.
  			self
  				at: w
  				ifPresent: [:k | n phrase: w translation: k]].
  	n saveToFileNamed: 'ja.translation'!

Item was changed:
+ ----- Method: WeakFinalizerItem class>>new (in category 'instance creation') -----
- ----- Method: WeakFinalizerItem class>>new (in category 'as yet unclassified') -----
  new
  	^ self basicNew: 1!



More information about the Squeak-dev mailing list