home *** CD-ROM | disk | FTP | other *** search
/ Really Useful CD 1 / ReallyUsefulCD1.iso / extras / languages / smalltalk / _smalltalk / prelude / collection < prev    next >
Encoding:
Text File  |  1987-12-30  |  2.8 KB  |  102 lines

  1. Class Collection
  2. [
  3.         addAll: aCollection
  4.                 aCollection do: [:x | self add: x ]
  5.  
  6. |
  7.      asArray
  8.           ^ Array new: self size ;
  9.                replaceFrom: 1 to: self size with: self
  10. |
  11.      asBag
  12.                 ^ Bag new addAll: self
  13. |
  14.      asSet
  15.                 ^ Set new addAll: self
  16. |
  17.      asList
  18.                 ^ List new addAllLast: self
  19. |
  20.      asString
  21.           ^ String new: self size ; 
  22.                replaceFrom: 1 to: self size with: self
  23. |
  24.      coerce: aCollection | newobj |
  25.           newobj <- self class new.
  26.           aCollection do: [:x | newobj add: x].
  27.           ^ newobj
  28. |
  29.      collect: aBlock
  30.           ^ self inject: self class new
  31.                  into: [:x :y | x add: (aBlock value: y). x ]
  32. |
  33.      deepCopy       | newobj |
  34.           newobj <- List new .
  35.           self do: [:x | newobj addLast: x copy ].
  36.           ^ self coerce: newobj
  37. |
  38.      detect: aBlock
  39.           ^ self detect: aBlock
  40.           ifAbsent: [self error: 'no object found matching detect']
  41.  
  42. |
  43.         detect: aBlock ifAbsent: exceptionBlock   
  44.                 self do: [:x | 
  45.                           (aBlock value: x) ifTrue: [^ x]].
  46.                 ^ exceptionBlock value
  47. |
  48.      first
  49.           ^ self error: 'subclass should implement first'
  50. |
  51.         includes: anObject
  52.           self do: [:x | (x == anObject) ifTrue: [^ true]].
  53.           ^ false
  54. |
  55.         inject: thisValue into: binaryBlock     | last |
  56.                 last <- thisValue.
  57.                 self do: [:x | last <- binaryBlock value: last value: x].
  58.                 ^ last
  59. |
  60.         isEmpty
  61.                 ^ (self size = 0)
  62. |
  63.      occurrencesOf: anObject
  64.           ^ self inject: 0
  65.                        into: [:x :y | (y = anObject) 
  66.                                          ifTrue: [x + 1]
  67.                                          ifFalse: [x] ]
  68. |
  69.      printString
  70.           ^ ( self inject: self class printString , ' ('
  71.                 into: [:x :y | x , ' ' , y printString]), ' )'
  72. |
  73.      reject: aBlock          
  74.           ^ self select: [:x | (aBlock value: x) not ]
  75. |
  76.         remove: oldObject
  77.                 self remove: oldObject ifAbsent:
  78.                   [^ self error: 
  79.                'attempt to remove object not found in collection' ].
  80.                 ^ oldObject
  81. |
  82.      remove: oldObject ifAbsent: exceptionBlock
  83.           ^ (self includes: oldObject)
  84.                ifTrue: [self remove: oldObject]
  85.                ifFalse: exceptionBlock
  86. |
  87.      select: aBlock          
  88.           ^ self inject: self class new
  89.                  into: [:x :y | (aBlock value: y) 
  90.                                         ifTrue: [x add: y]. x]
  91. |
  92.      shallowCopy         | newobj |
  93.           newobj <- List new .
  94.           self do: [:x | newobj addLast: x].
  95.           ^ self coerce: newobj
  96. |
  97.      size      | i |
  98.           i <- 0.
  99.           self do: [:x | i <- i + 1 ].
  100.           ^ i
  101. ]
  102.