[squeak-dev] The Trunk: Collections-nice.752.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 26 20:54:18 UTC 2017


Nicolas Cellier uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-nice.752.mcz

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

Name: Collections-nice.752
Author: nice
Time: 26 April 2017, 10:54:03.973466 pm
UUID: d3620c7a-7ead-43fb-93ee-21dce320c7eb
Ancestors: Collections-ul.751

Classify a few 'as yet unclassified' methods

=============== Diff against Collections-ul.751 ===============

Item was changed:
+ ----- Method: EndOfStream>>defaultAction (in category 'handling') -----
- ----- Method: EndOfStream>>defaultAction (in category 'exceptionDescription') -----
  defaultAction
  	"Answer ReadStream>>next default reply."
  
  	^ nil!

Item was changed:
+ ----- Method: LimitedWriteStream>>nextPutAll: (in category 'writing') -----
- ----- Method: LimitedWriteStream>>nextPutAll: (in category 'as yet unclassified') -----
  nextPutAll: aCollection
  
  	| newEnd |
  	collection class == aCollection class ifFalse:
  		[^ super nextPutAll: aCollection ].
  
  	newEnd := position + aCollection size.
  	newEnd > limit ifTrue: [
  		super nextPutAll: (aCollection copyFrom: 1 to: (limit - position max: 0)).
  		limitBlock value.
  		^aCollection
  	].
  	newEnd > writeLimit ifTrue: [
  		self growTo: newEnd + 10
  	].
  
  	collection replaceFrom: position+1 to: newEnd  with: aCollection startingAt: 1.
  	position := newEnd.
  	^aCollection!

Item was changed:
+ ----- Method: LimitedWriteStream>>pastEndPut: (in category 'private') -----
- ----- Method: LimitedWriteStream>>pastEndPut: (in category 'as yet unclassified') -----
  pastEndPut: anObject
  	collection size >= limit ifTrue: [limitBlock value].  "Exceptional return"
  	^ super pastEndPut: anObject!

Item was changed:
+ ----- Method: LimitedWriteStream>>setLimit:limitBlock: (in category 'initialize-release') -----
- ----- Method: LimitedWriteStream>>setLimit:limitBlock: (in category 'as yet unclassified') -----
  setLimit: sizeLimit limitBlock: aBlock
  	"Limit the numer of elements this stream will write..."
  	limit := sizeLimit.
  	"Execute this (typically ^ contents) when that limit is exceded"
  	limitBlock := aBlock!

Item was changed:
+ ----- Method: PluggableTextAttribute>>writeScanOn: (in category 'fileIn/fileOut') -----
- ----- Method: PluggableTextAttribute>>writeScanOn: (in category 'as yet unclassified') -----
  writeScanOn: aStream
  	"Impossible for this kind of attribute"
  	^ self shouldNotImplement
  	!

Item was changed:
+ ----- Method: RWBinaryOrTextStream>>setFileTypeToObject (in category 'properties-setting') -----
- ----- Method: RWBinaryOrTextStream>>setFileTypeToObject (in category 'as yet unclassified') -----
  setFileTypeToObject
  	"do nothing.  We don't have a file type"!

Item was changed:
+ ----- Method: TextAction>>analyze: (in category 'initialize-release') -----
- ----- Method: TextAction>>analyze: (in category 'as yet unclassified') -----
  analyze: aString
  	"Analyze the selected text to find both the parameter to store and the text to emphesize (may be different from original selection).  Does not return self!!.  May be multiline or of the form:
  3+4
  <3+4>
  Click Here<3+4>
  <3+4>Click Here
  "
  	"Obtain the showing text and the instructions"
  	| b1 b2 singleLine trim param show |
  	b1 := aString indexOf: $<.
  	b2 := aString indexOf: $>.
  	singleLine := aString lineCount = 0.
  	(singleLine or: [(b1 < b2) & (b1 > 0)]) ifFalse: ["only one part"
  		param := self validate: aString.
  		param ifNil: [ ^{ nil. nil } ].
  		^ Array with: param with: (param size = 0 ifFalse: [param])].
  	"Two parts"
  	trim := aString withBlanksTrimmed.
  	(trim at: 1) == $< 
  		ifTrue: [(trim last) == $>
  			ifTrue: ["only instructions" 
  				param := self validate: (aString copyFrom: b1+1 to: b2-1).
  				show := param size = 0 ifFalse: [param]]
  			ifFalse: ["at the front"
  				param := self validate: (aString copyFrom: b1+1 to: b2-1).
  				show := param size = 0 ifFalse: [aString copyFrom: b2+1 to: aString size]]]
  		ifFalse: [(trim last) == $>
  			ifTrue: ["at the end"
  				param := self validate: (aString copyFrom: b1+1 to: b2-1).
  				show := param size = 0 ifFalse: [aString copyFrom: 1 to: b1-1]]
  			ifFalse: ["Arbitrary string. Let the compiler handle the complete string"
  				param := self validate: aString.
  				param ifNil: [ ^{ nil. nil }].
  				show := (param size = 0 ifFalse: [param])]].
  	^ Array with: param with: show
  !

Item was changed:
+ ----- Method: TextAction>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextAction>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	"Set the emphasis for text display"
  	Purple ifNil: [Purple := self userInterfaceTheme color ifNil: [Color r: 0.4 g: 0.0 b: 1]].
  	scanner textColor: Purple.!

Item was changed:
+ ----- Method: TextAction>>info (in category 'accessing') -----
- ----- Method: TextAction>>info (in category 'as yet unclassified') -----
  info
  	^ 'no hidden info'!

Item was changed:
+ ----- Method: TextAction>>validate: (in category 'initialize-release') -----
- ----- Method: TextAction>>validate: (in category 'as yet unclassified') -----
  validate: aString
  	"any format is OK with me"
  	^ aString!

Item was changed:
+ ----- Method: TextAlignment>>dominates: (in category 'testing') -----
- ----- Method: TextAlignment>>dominates: (in category 'as yet unclassified') -----
  dominates: other
  	"There can be only one..."
  	^self class == other class!

Item was changed:
+ ----- Method: TextAlignment>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextAlignment>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	"Set the emphasist for text scanning"
  	scanner setAlignment: alignment.!

Item was changed:
+ ----- Method: TextAlignment>>shouldFormBlocks (in category 'testing') -----
- ----- Method: TextAlignment>>shouldFormBlocks (in category 'as yet unclassified') -----
  shouldFormBlocks
  
  	^ true!

Item was changed:
+ ----- Method: TextAttribute>>anchoredMorph (in category 'accessing') -----
- ----- Method: TextAttribute>>anchoredMorph (in category 'as yet unclassified') -----
  anchoredMorph
  	"If one hides here, return it"
  	^nil!

Item was changed:
+ ----- Method: TextAttribute>>dominates: (in category 'testing') -----
- ----- Method: TextAttribute>>dominates: (in category 'as yet unclassified') -----
  dominates: another
  	"Subclasses may override condense multiple attributes"
  	^ false!

Item was changed:
+ ----- Method: TextAttribute>>emphasisCode (in category 'accessing') -----
- ----- Method: TextAttribute>>emphasisCode (in category 'as yet unclassified') -----
  emphasisCode
  	"Subclasses may override to add bold, italic, etc"
  	^ 0!

Item was changed:
+ ----- Method: TextAttribute>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextAttribute>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	"Subclasses may override to set, eg, font, color, etc"!

Item was changed:
+ ----- Method: TextAttribute>>forFontInStyle:do: (in category 'private') -----
- ----- Method: TextAttribute>>forFontInStyle:do: (in category 'as yet unclassified') -----
  forFontInStyle: aTextStyle do: aBlock
  	"No action is the default.  Overridden by font specs"!

Item was changed:
+ ----- Method: TextAttribute>>mayActOnClick (in category 'testing') -----
- ----- Method: TextAttribute>>mayActOnClick (in category 'as yet unclassified') -----
  mayActOnClick
  	"Subclasses may override to provide, eg, hot-spot actions"
  	^ false!

Item was changed:
+ ----- Method: TextAttribute>>mayBeExtended (in category 'testing') -----
- ----- Method: TextAttribute>>mayBeExtended (in category 'as yet unclassified') -----
  mayBeExtended
  	"A quality that may be overridden by subclasses, such as TextAnchors, that really only apply to a single character"
  	^ true!

Item was changed:
+ ----- Method: TextAttribute>>menu (in category 'accessing') -----
- ----- Method: TextAttribute>>menu (in category 'as yet unclassified') -----
  menu
  	^nil!

Item was changed:
+ ----- Method: TextAttribute>>oldEmphasisCode: (in category 'accessing') -----
- ----- Method: TextAttribute>>oldEmphasisCode: (in category 'as yet unclassified') -----
  oldEmphasisCode: default
  	"Allows running thorugh possibly multiple attributes
  	and getting the emphasis out of any that has an emphasis (font number)"
  	^ default!

Item was changed:
+ ----- Method: TextAttribute>>reset (in category 'initialize-release') -----
- ----- Method: TextAttribute>>reset (in category 'as yet unclassified') -----
  reset
  	"Allow subclasses to prepare themselves for merging attributes"!

Item was changed:
+ ----- Method: TextAttribute>>set (in category 'accessing') -----
- ----- Method: TextAttribute>>set (in category 'as yet unclassified') -----
  set
  	"Respond true to include this attribute (as opposed to, eg, a bold
  	emphasizer that is clearing the property"
  	^ true!

Item was changed:
+ ----- Method: TextDoIt>>actOnClickFor: (in category 'event handling') -----
- ----- Method: TextDoIt>>actOnClickFor: (in category 'as yet unclassified') -----
  actOnClickFor: anObject
  	"Note: evalString gets evaluated IN THE CONTEXT OF anObject
  	 -- meaning that self and all instVars are accessible"
  	Compiler evaluate: evalString for: anObject.
  	^ true !

Item was changed:
+ ----- Method: TextDoIt>>analyze: (in category 'initialize-release') -----
- ----- Method: TextDoIt>>analyze: (in category 'as yet unclassified') -----
  analyze: aString
  
  	| list |
  	list := super analyze: aString.
  	evalString := (list at: 1) asString.
  	^ list at: 2!

Item was changed:
+ ----- Method: TextDoIt>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextDoIt>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	scanner addEmphasis: 4!

Item was changed:
+ ----- Method: TextDoIt>>info (in category 'accessing') -----
- ----- Method: TextDoIt>>info (in category 'as yet unclassified') -----
  info
  	^ evalString!

Item was changed:
+ ----- Method: TextEmphasis>>dominates: (in category 'testing') -----
- ----- Method: TextEmphasis>>dominates: (in category 'as yet unclassified') -----
  dominates: other
  	(emphasisCode = 0 and: [other dominatedByCmd0]) ifTrue: [^ true].
  	^ (other class == self class)
  		and: [emphasisCode = other emphasisCode]!

Item was changed:
+ ----- Method: TextEmphasis>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextEmphasis>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	"Set the emphasist for text scanning"
  	scanner addEmphasis: emphasisCode!

Item was changed:
+ ----- Method: TextFontChange>>dominates: (in category 'testing') -----
- ----- Method: TextFontChange>>dominates: (in category 'as yet unclassified') -----
  dominates: other
  	^ other isKindOf: TextFontChange!

Item was changed:
+ ----- Method: TextFontChange>>emphasizeScanner: (in category 'accessing') -----
- ----- Method: TextFontChange>>emphasizeScanner: (in category 'as yet unclassified') -----
  emphasizeScanner: scanner
  	"Set the font for text display"
  	scanner setFont: fontNumber!

Item was changed:
+ ----- Method: TextFontChange>>forFontInStyle:do: (in category 'private') -----
- ----- Method: TextFontChange>>forFontInStyle:do: (in category 'as yet unclassified') -----
  forFontInStyle: aTextStyle do: aBlock
  	aBlock value: (aTextStyle fontAt: fontNumber)!

Item was changed:
+ ----- Method: TextFontReference>>forFontInStyle:do: (in category 'private') -----
- ----- Method: TextFontReference>>forFontInStyle:do: (in category 'as yet unclassified') -----
  forFontInStyle: aTextStyle do: aBlock
  	aBlock value: font!

Item was changed:
+ ----- Method: TextIndent>>amount (in category 'accessing') -----
- ----- Method: TextIndent>>amount (in category 'access') -----
  amount
  	"number of tab spaces to indent by"
  	^amount!

Item was changed:
+ ----- Method: TextIndent>>amount: (in category 'accessing') -----
- ----- Method: TextIndent>>amount: (in category 'access') -----
  amount: anInteger
  	"change the number of tabs to indent by"
  	amount := anInteger!

Item was changed:
+ ----- Method: TextIndent>>shouldFormBlocks (in category 'testing') -----
- ----- Method: TextIndent>>shouldFormBlocks (in category 'nil') -----
  shouldFormBlocks
  
  	^ true!

Item was changed:
+ ----- Method: TextStream>>applyAttribute:beginningAt: (in category 'private') -----
- ----- Method: TextStream>>applyAttribute:beginningAt: (in category 'as yet unclassified') -----
  applyAttribute: att beginningAt: startPos
  	collection addAttribute: att from: startPos to: self position!

Item was changed:
+ ----- Method: TextStream>>nextPutAll: (in category 'writing') -----
- ----- Method: TextStream>>nextPutAll: (in category 'as yet unclassified') -----
  nextPutAll: aCollection 
  	"Optimized access to get around Text at:Put: overhead"
  	| n |
  	n := aCollection size.
  	position + n > writeLimit
  		ifTrue:
  			[self growTo: position + n + 10].
  	collection 
  		replaceFrom: position+1
  		to: position + n
  		with: aCollection
  		startingAt: 1.
  	position := position + n.
  	^aCollection!

Item was changed:
+ ----- Method: TextStream>>withAttribute:do: (in category 'private') -----
- ----- Method: TextStream>>withAttribute:do: (in category 'as yet unclassified') -----
  withAttribute: att do: strmBlock
  	| pos1 val |
  	pos1 := self position.
  	val := strmBlock value.
  	collection addAttribute: att from: pos1+1 to: self position.
  	^ val!

Item was changed:
+ ----- Method: TextStream>>withAttributes:do: (in category 'private') -----
- ----- Method: TextStream>>withAttributes:do: (in category 'as yet unclassified') -----
  withAttributes: attributes do: streamBlock 
  	| pos1 val |
  	pos1 := self position.
  	val := streamBlock value.
  	attributes do: [:attribute |
  		collection
  			addAttribute: attribute
  			from: pos1 + 1
  			to: self position].
  	^ val!

Item was changed:
+ ----- Method: TextURL>>analyze: (in category 'initialize-release') -----
- ----- Method: TextURL>>analyze: (in category 'as yet unclassified') -----
  analyze: aString
  
  	| list |
  	list := super analyze: aString.
  
  	(UIManager default request: 'URL to open' translated initialAnswer: (list at: 1))
  		in: [:answer | answer ifEmpty: [url := list at: 1] ifNotEmpty: [url := answer]].
  	
  	^ list at: 2!

Item was changed:
+ ----- Method: TranscriptStream>>characterLimit (in category 'accessing') -----
- ----- Method: TranscriptStream>>characterLimit (in category 'access') -----
  characterLimit
  	"Tell the views how much to retain on screen"
  	^ 20000!

Item was changed:
+ ----- Method: WordArrayForSegment>>restoreEndianness (in category 'objects from disk') -----
- ----- Method: WordArrayForSegment>>restoreEndianness (in category 'as yet unclassified') -----
  restoreEndianness
  	"This word object was just read in from a stream.  Do not correct the Endianness because the load primitive will reverse bytes as needed."
  
  	"^ self"
  !

Item was changed:
+ ----- Method: WordArrayForSegment>>writeOn: (in category 'objects from disk') -----
- ----- Method: WordArrayForSegment>>writeOn: (in category 'as yet unclassified') -----
  writeOn: aByteStream
  	"Write quickly and disregard the endianness of the words.  Store the array of bits onto the argument, aStream.  (leading byte ~= 16r80) identifies this as raw bits (uncompressed)."
  
  	aByteStream nextInt32Put: self size.	"4 bytes"
  	aByteStream nextPutAll: self
  !



More information about the Squeak-dev mailing list