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

  1. "
  2.      Lists are implemented using Points in order to
  3.      reduce the number of classes in the standard prelude
  4. "
  5. Class List :SequenceableCollection
  6. | first current |
  7. [
  8.      add: anItem
  9.           first <- (Point new x: anItem ) y: first .
  10.           ^ anItem
  11. |
  12.      addFirst: anItem
  13.           first <- (Point new x: anItem ) y: first .
  14.           ^ anItem
  15. |
  16.      addLast: anItem
  17.           (first isNil) 
  18.                ifTrue: [^ self addFirst: anItem].
  19.           (self findLast) y: ((Point new x: anItem) y: nil).
  20.           ^ anItem
  21. |
  22.      addAllFirst: aCollection
  23.           aCollection do: [:x | self addFirst: x]
  24. |    
  25.      addAllLast: aCollection
  26.           aCollection do: [:x | self addLast: x]
  27. |
  28.      coerce: aCollection      | newList |
  29.           newList <- List new.
  30.           aCollection do: [:x | newList addLast: x].
  31.           ^ newList
  32. |
  33.      findLast       | item |
  34.           ((item <- first) isNil)
  35.                ifTrue: [^ nil].
  36.           [(item y) notNil]
  37.                whileTrue: [item <- item y].
  38.           ^ item
  39. |
  40.      remove: anItem
  41.           ^ self remove: anItem 
  42.                ifAbsent: [self error: 'cant find item']
  43. |
  44.      remove: anItem ifAbsent: exceptionBlock
  45.           (first isNil) 
  46.                ifTrue: [^ exceptionBlock value].
  47.           self inject: nil into: [:prev :current |
  48.                (current x == anItem)
  49.                     ifTrue: [(prev isNil)
  50.                               ifTrue: [first <- current y]
  51.                               ifFalse: [prev y: (current y)].
  52.                           ^ anItem].
  53.                current ] .
  54.           ^ exceptionBlock value
  55. |
  56.      removeError
  57.           ^ self error: 'cannot remove from an empty list'
  58. |
  59.      removeFirst    | item |
  60.           (first isNil)
  61.                ifTrue: [^ self removeError].
  62.           item <- first.
  63.           first <- first y.
  64.           ^ item x
  65. |
  66.      removeLast
  67.           (first isNil)
  68.                ifTrue: [^ self removeError].
  69.           ^ self remove: self last 
  70.                ifAbsent: [self removeError]
  71. |
  72.      first
  73.           ^ ((current <- first) notNil) 
  74.                ifTrue: [ current x ]
  75. |
  76.      next
  77.           ^ ((current <- current y) notNil)
  78.                ifTrue: [ current x ]
  79. |
  80.      current
  81.           ^ current x
  82. |
  83.      last
  84.           (first isNil) 
  85.                ifTrue: [^ nil].
  86.           ^ self findLast x
  87. |
  88.      isEmpty
  89.           ^ first == nil
  90. ]
  91.