The Trunk: Collections-nice.264.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-nice.264.mcz

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

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

Name: Collections-nice.264
Author: nice
Time: 26 December 2009, 11:12:07 am
UUID: 8db81a5b-e4a4-400a-bae3-f92ecfa1d1a6
Ancestors: Collections-nice.263

Cosmetic: puch a few temps inside closures

=============== Diff against Collections-nice.263 ===============

Item was changed:
  ----- Method: SharedQueue>>peek (in category 'accessing') -----
  peek
  "Answer the object that was sent through the receiver first and has not
  yet been received by anyone but do not remove it from the receiver. If
  no object has been sent, return nil"
 
+ ^accessProtect
+ critical: [
+ | value |
+ readPosition >= writePosition
- | value |
- accessProtect
- critical: [readPosition >= writePosition
  ifTrue: [readPosition := 1.
  writePosition := 1.
  value := nil]
+ ifFalse: [value := contentsArray at: readPosition].
+ value].!
- ifFalse: [value := contentsArray at: readPosition]].
- ^value!

Item was changed:
  ----- Method: SharedQueue>>next (in category 'accessing') -----
  next
  "Answer the object that was sent through the receiver first and has not
  yet been received by anyone. If no object has been sent, suspend the
  requesting process until one is."
 
- | value |
  readSynch wait.
+ ^accessProtect
+ critical: [
+ | value |
+ readPosition = writePosition
- accessProtect
- critical: [readPosition = writePosition
  ifTrue:
  [self error: 'Error in SharedQueue synchronization'.
  value := nil]
  ifFalse:
  [value := contentsArray at: readPosition.
  contentsArray at: readPosition put: nil.
+ readPosition := readPosition + 1].
+ value].!
- readPosition := readPosition + 1]].
- ^value!

Item was changed:
  ----- Method: String>>keywords (in category 'converting') -----
  keywords
  "Answer an array of the keywords that compose the receiver."
+ | keywords |
- | kwd char keywords |
  keywords := Array streamContents:
+ [:kwds |
+ | kwd |
+ kwd := WriteStream on: (String new: 16).
- [:kwds | kwd := WriteStream on: (String new: 16).
  1 to: self size do:
  [:i |
+ | char |
  kwd nextPut: (char := self at: i).
  char = $: ifTrue:
  [kwds nextPut: kwd contents.
  kwd reset]].
  (kwd position = 0) ifFalse: [kwds nextPut: kwd contents]].
  (keywords size >= 1 and: [(keywords at: 1) = ':']) ifTrue:
  ["Has an initial keyword, as in #:if:then:else:"
  keywords := keywords allButFirst].
  (keywords size >= 2 and: [(keywords at: keywords size - 1) = ':']) ifTrue:
  ["Has a final keyword, as in #nextPut::andCR"
  keywords := keywords copyReplaceFrom: keywords size - 1
  to: keywords size with: {':' , keywords last}].
  ^ keywords!

Item was changed:
  ----- Method: String>>compressWithTable: (in category 'converting') -----
  compressWithTable: tokens
  "Return a string with all substrings that occur in tokens replaced
  by a character with ascii code = 127 + token index.
  This will work best if tokens are sorted by size.
  Assumes this string contains no characters > 127, or that they
  are intentionally there and will not interfere with this process."
+ | str null finalSize result ri c |
- | str null finalSize start result ri c ts |
  null := Character value: 0.
  str := self copyFrom: 1 to: self size.  "Working string will get altered"
  finalSize := str size.
  tokens doWithIndex:
  [:token :tIndex |
+ | start ts |
  start := 1.
  [(start := str findString: token startingAt: start) > 0]
  whileTrue:
  [ts := token size.
  ((start + ts) <= str size
  and: [(str at: start + ts) = $  and: [tIndex*2 <= 128]])
  ifTrue: [ts := token size + 1.  "include training blank"
  str at: start put: (Character value: tIndex*2 + 127)]
  ifFalse: [str at: start put: (Character value: tIndex + 127)].
  str at: start put: (Character value: tIndex + 127).
  1 to: ts-1 do: [:i | str at: start+i put: null].
  finalSize := finalSize - (ts - 1).
  start := start + ts]].
  result := String new: finalSize.
  ri := 0.
  1 to: str size do:
  [:i | (c := str at: i) = null ifFalse: [result at: (ri := ri+1) put: c]].
  ^ result!

Item was changed:
  ----- Method: RunArray>>runsFrom:to:do: (in category 'enumerating') -----
  runsFrom: start to: stop do: aBlock
  "Evaluate aBlock with all existing runs in the range from start to stop"
- | run value index |
  start > stop ifTrue:[^self].
  self at: start setRunOffsetAndValue:[:firstRun :offset :firstValue|
+ | run value index |
  run := firstRun.
  value := firstValue.
  index := start + (runs at: run) - offset.
  [aBlock value: value.
  index <= stop] whileTrue:[
  run := run + 1.
  value := values at: run.
  index := index + (runs at: run)]].
  !

Item was changed:
  ----- Method: SharedQueue2>>nextOrNilSuchThat: (in category 'accessing') -----
  nextOrNilSuchThat: aBlock
  "Answer the next object that satisfies aBlock, skipping any intermediate objects.
  If no such object has been queued, answer <nil> and leave me intact."
 
- | index |
  ^monitor critical: [
+ | index |
  index := items findFirst: aBlock.
  index = 0 ifTrue: [
  nil ]
  ifFalse: [
  items removeAt: index ] ].
  !

Item was changed:
  ----- Method: SequenceableCollection>>groupsOf:atATimeDo: (in category 'enumerating') -----
  groupsOf: n atATimeDo: aBlock
  "Evaluate aBlock with my elements taken n at a time. Ignore any leftovers at the end.
  Allows use of a flattened
  array for things that naturally group into groups of n.
  If aBlock has a single argument, pass it an array of n items,
  otherwise, pass the items as separate arguments.
  See also pairsDo:"
+ | passArray |
- | passArray args |
  passArray := (aBlock numArgs = 1).
  n
  to: self size
  by: n
  do: [:index |
+ | args |
  args := (self copyFrom: index - n + 1 to: index) asArray.
  passArray ifTrue: [ aBlock value: args ]
  ifFalse: [ aBlock valueWithArguments: args ]].!

Item was changed:
  ----- Method: WeakArray class>>addWeakDependent: (in category 'accessing') -----
  addWeakDependent: anObject
- | finished index weakDependent |
  self isFinalizationSupported ifFalse:[^self].
  FinalizationLock critical:[
+ | finished index weakDependent |
  finished := false.
  index := 0.
  [index := index + 1.
  finished not and:[index <= FinalizationDependents size]] whileTrue:[
  weakDependent := FinalizationDependents at: index.
  weakDependent isNil ifTrue:[
  FinalizationDependents at: index put: anObject.
  finished := true.
  ].
  ].
  finished ifFalse:[
  "Grow linearly"
  FinalizationDependents := FinalizationDependents, (WeakArray new: 10).
  FinalizationDependents at: index put: anObject.
  ].
  ] ifError:[:msg :rcvr| rcvr error: msg].!

Item was changed:
  ----- Method: String>>withBlanksCondensed (in category 'converting') -----
  withBlanksCondensed
  "Return a copy of the receiver with leading/trailing blanks removed
  and consecutive white spaces condensed."
 
- | trimmed lastBlank |
- trimmed := self withBlanksTrimmed.
  ^String streamContents: [:stream |
+ | trimmed lastBlank |
+ trimmed := self withBlanksTrimmed.
  lastBlank := false.
  trimmed do: [:c | (c isSeparator and: [lastBlank]) ifFalse: [stream nextPut: c].
  lastBlank := c isSeparator]].
 
  " ' abc  d   ' withBlanksCondensed"
  !

Item was changed:
  ----- Method: SharedQueue>>flushAllSuchThat: (in category 'accessing') -----
  flushAllSuchThat: aBlock
  "Remove from the queue all objects that satisfy aBlock."
+ ^accessProtect critical: [
+ | value newReadPos |
- | value newReadPos |
- accessProtect critical: [
  newReadPos := writePosition.
  writePosition-1 to: readPosition by: -1 do:
  [:i | value := contentsArray at: i.
  contentsArray at: i put: nil.
  (aBlock value: value) ifTrue: [
  "We take an element out of the queue, and therefore, we need to decrement
  the readSynch signals"
  readSynch wait.
  ] ifFalse: [
  newReadPos := newReadPos - 1.
  contentsArray at: newReadPos put: value]].
+ readPosition := newReadPos.
+ value]!
- readPosition := newReadPos].
- ^value
- !

Item was changed:
  ----- Method: String>>isoToUtf8 (in category 'internet') -----
  isoToUtf8
  "Convert ISO 8559-1 to UTF-8"
+ | s |
- | s v |
  s := WriteStream on: (String new: self size).
-
  self do: [:c |
+ | v |
  v := c asciiValue.
  (v > 128)
  ifFalse: [s nextPut: c]
  ifTrue: [
  s nextPut: (192+(v >> 6)) asCharacter.
  s nextPut: (128+(v bitAnd: 63)) asCharacter]].
  ^s contents.
  !

Item was changed:
  ----- Method: SharedQueue>>nextOrNil (in category 'accessing') -----
  nextOrNil
  "Answer the object that was sent through the receiver first and has not
  yet been received by anyone. If no object has been sent, answer <nil>."
 
+ ^accessProtect critical: [
+ | value |
- | value |
-
- accessProtect critical: [
  readPosition >= writePosition ifTrue: [
  value := nil
  ] ifFalse: [
  value := contentsArray at: readPosition.
  contentsArray at: readPosition put: nil.
  readPosition := readPosition + 1
  ].
  readPosition >= writePosition ifTrue: [readSynch initSignals].
+ value
+ ].!
- ].
- ^value!

Item was changed:
  ----- Method: SharedQueue>>nextOrNilSuchThat: (in category 'accessing') -----
  nextOrNilSuchThat: aBlock
  "Answer the next object that satisfies aBlock, skipping any intermediate objects.
  If no object has been sent, answer <nil> and leave me intact.
  NOTA BENE:  aBlock MUST NOT contain a non-local return (^)."
 
+ ^accessProtect critical: [
+ | value readPos |
- | value readPos |
- accessProtect critical: [
  value := nil.
  readPos := readPosition.
  [readPos < writePosition and: [value isNil]] whileTrue: [
  value := contentsArray at: readPos.
  readPos := readPos + 1.
  (aBlock value: value) ifTrue: [
  readPosition to: readPos - 1 do: [ :j |
  contentsArray at: j put: nil.
  ].
  readPosition := readPos.
  ] ifFalse: [
  value := nil.
  ].
  ].
  readPosition >= writePosition ifTrue: [readSynch initSignals].
+ value.
  ].
- ^value
  "===
  q := SharedQueue new.
  1 to: 10 do: [ :i | q nextPut: i].
  c := OrderedCollection new.
  [
  v := q nextOrNilSuchThat: [ :e | e odd].
  v notNil
  ] whileTrue: [
  c add: {v. q size}
  ].
  {c. q} explore
  ==="!

Item was changed:
  ----- Method: SequenceableCollection>>groupsOf:atATimeCollect: (in category 'enumerating') -----
  groupsOf: n atATimeCollect: aBlock
  "Evaluate aBlock with my elements taken n at a time. Ignore any
  leftovers at the end.
  Allows use of a flattened  
  array for things that naturally group into groups of n.
  If aBlock has a single argument, pass it an array of n items,
  otherwise, pass the items as separate arguments.
  See also pairsDo:"
+ | passArray |
- | passArray args  |
  passArray := aBlock numArgs = 1.
  ^(n
  to: self size
  by: n)
  collect: [:index |
+ | args |
  args := (self copyFrom: index - n + 1 to: index) asArray.
  passArray
  ifTrue: [aBlock value: args]
  ifFalse: [aBlock valueWithArguments: args]]!

Item was changed:
  ----- Method: TextColor>>writeScanOn: (in category 'scanning') -----
  writeScanOn: strm
  "Two formats.  c125000255 or cblue;"
 
+ | nn |
- | nn str |
  strm nextPut: $c.
  (nn := color name) ifNotNil: [
  (self class respondsTo: nn) ifTrue: [
  ^ strm nextPutAll: nn; nextPut: $;]].
  (Array with: color red with: color green with: color blue) do: [:float |
+ | str |
  str := '000', (float * 255) asInteger printString.
  strm nextPutAll: (str copyFrom: str size-2 to: str size)]!

Item was changed:
  ----- Method: LimitingLineStreamWrapper>>upToEnd (in category 'accessing') -----
  upToEnd
-
- | ln |
  ^String streamContents: [:strm |
+ | ln |
  [(ln := self nextLine) isNil] whileFalse: [
  strm nextPutAll: ln; cr]]!