Alok I found in |
deque.st
Description: Binary data
"File : deque.st SCCS : '@(#)2017/08/23 deque.st 1.41' Author : Richard A. O'Keefe Defines: Deque, a non-indexable double-ended queue. Testing: The Squeak version of this has been tested. " require: 'ansi.st' "Usage : If you want indexing, use OrderedCollection. If you want O(1) {add,remove}{First,Last}, use Deque. Here is the reason this class exists. Measurements were done in Squeak 3.10 on a 2.53 GHz 2-core intel Mac. Time millisecondsToRun: [|c| c := OrderedCollection withAll: (1 to: 50). 1 to: 100000 do: [:i | c addLast: c removeFirst]] => 412, or about 4.12 µsec per iteration. Time millisecondsToRun: [|c| c := Deque withAll: (1 to: 50). 1 to: 100000 do: [:i | c addLast: c removeFirst]] => 25, or about 0.25 µsec per iteration. Using Visual Works Non-Commercial on a 2.53 GHz 2-core intel Mac, OrderedCollection => 84 nsec per iteration Deque => 41 nsec per iteration. And 50 elements is not a very large queue size. This Smalltalk does not offer a Stack class. Use Deque with #addLast: for push and #removeLast for pop. This Smalltalk does not offer a Queue class. Use Deque with #addLast: for enter and #removeFirst for leave. In 2012 I added BoundedDeque. The Booch Components include a circular buffer. The Boost library includes a circular buffer. The difference between a circular buffer and a deque is that if you insert into a collection that already fills the underlying array, a deque grows to hold it but a circular buffer overwrites an existing element. This is just like the difference between a Heap and a BoundedHeap. There is one major difference between our BoundedDeques and Boost circular buffers: they are indexed and ours are not. Our {,Bounded}Deques are Collections but not SequencedReadableCollections. We could do that too, there is even a draft that does it, but it hardly seems worth while. This needs to be rewritten to use better names internally because it uses three separate metaphors: first -- last left -- right top -- bottom We should stick with one, and since the interface has to be first -- last that's what we should stick with. " Integer methods: amod: other [other integer_between: 1 and: (C: maxInt)] assert. ^(self - 1) \\ other + 1 Collection abstractSubclass: #AbstractDeque instanceVariableNames: 'array left right size capacity' unshared: 'array' "hints: 'array (Array) left (SmallInteger) right (SmallInteger) size (SmallInteger) capacity (SmallInteger)'" methods for: 'checking' invariant ^(array isMemberOf: Array) and: [ capacity = array size and: [ capacity > 0 and: [ (size integer_between: 0 and: capacity) and: [ (left integer_between: 1 and: capacity) and: [ right = (left + size - 1 amod: capacity) ]]]]] methods for: 'copying' pvtArray: anArray array := anArray. left := 1. right := capacity := size := anArray size. ^self , aCollection |a i| a := Array new: size + aCollection size. i := 0. self do: [:each | a at: (i := i + 1) put: each]. aCollection do: [:each | a at: (i := i + 1) put: each]. ^self pvtClone pvtArray: a pvtPostCopy array := array copy. species ^self class reverse "If it makes sense to have #reverseDo:, it makes sense to have #reverse." |a i| a := Array new: size. i := 0. self reverseDo: [:each | a at: (i := i + 1) put: each]. ^self pvtClone pvtArray: a inPlaceReverse |a b x y| a := left. b := right. 1 to: size // 2 do: [:i | x := array at: a. y := array at: b. array at: a put: y. array at: b put: x. a := a == capacity ifTrue: [1] ifFalse: [a + 1]. b := b == 1 ifTrue: [capacity] ifFalse: [b - 1]]. methods for: 'accessing' size ^size anyOne "As long as #anyOne and #removeAnyOne are consistent, this could in general answer _any_ element. However, to be used as intended in threads.st, it must answer the first element of a deque, the best element of a heap, or indeed any element of a set-like collection" ^self first first size = 0 ifTrue: [self pvtEmptyError]. ^array at: left firstSatisfies: aBlock ^self isEmpty ifTrue: [false] ifFalse: [aBlock value: self first] last size = 0 ifTrue: [self pvtEmptyError]. ^array at: right lastSatisfies: aBlock ^self isEmpty ifTrue: [false] ifFalse: [aBlock value: self last] methods for: 'adding' add: item "In order to work with SharedQueue, this must add the item at the end removeAnyOne doesn't remove from." ^self addLast: item add: item ifPresent: exceptionBlock "Identical to AbstractSetLikeCollection>>add:ifPresent:." "Not enormously useful, but it _is_ well defined." ^(self includes: item) ifTrue: [exceptionBlock optionalValue: item] ifFalse: [self add: item] addIfNotPresent: item "Identical to AbstractSetLikeCollection>>addifNotPresent:." <compatibility: #pharo> "Not enormously useful, but it _is_ well defined." ^self add: item ifPresent: [] addIfNotPresent: item ifPresentDo: aBlock "Identical to AbstractSetLikeCollection>>addifNotPresent:." <compatibility: #pharo> "Not enormously useful, but it _is_ well defined." ^self add: item ifPresent: aBlock add: item withOccurrences: n ^self addLast: item withOccurrences: n addAll: aCollection ^self addAllLast: (self pvtCopyOr: aCollection) addAll: aCollection collect: aBlock (self pvtCopyOr: aCollection) do: [:each | self addLast: (aBlock value: each)]. addAll: aSequence from: start to: stop aSequence from: start to: stop do: [:each | self addLast: each]. addAll: aCollection keysAndValuesCollect: aBlock aCollection keysAndValuesDo: [:key :value | self addLast: (aBlock value: key value: value)]. addAllFirst: aCollection (self pvtCopyOr: aCollection) reverseDo: [:each | self addFirst: each]. addAllFirst: aCollection collect: aBlock (self pvtCopyOr: aCollection) reverseDo: [:each | self addFirst: (aBlock value: each)]. addAllFirst: aCollection from: start to: finish (self pvtCopyOr: aCollection) from: start to: finish reverseDo: [:each | self addFirst: each]. addAllFirst: aCollection from: start to: finish collect: aBlock (self pvtCopyOr: aCollection) from: start to: finish reverseDo: [:each | self addFirst: (aBlock value: each)]. addAllLast: aCollection (self pvtCopyOr: aCollection) do: [:each | self addLast: each]. addAllLast: aCollection collect: aBlock (self pvtCopyOr: aCollection) do: [:each | self addLast: (aBlock value: each)]. addAllLast: aCollection from: start to: finish (self pvtCopyOr: aCollection) from: start to: finish do: [:each | self addLast: each]. addAllLast: aCollection from: start to: finish collect: aBlock (self pvtCopyOr: aCollection) from: start to: finish do: [:each | self addLast: (aBlock value: each)]. addFirst: item self subclassResponsibility. addLast: item self subclassResponsibility. addFirst: item withOccurrences: n (n integer_between: 0 and: (C: maxSize)) ifFalse: [self pvtCountError: n]. 1 to: n do: [:i | self addFirst: item]. addLast: item withOccurrences: n (n integer_between: 0 and: (C: maxSize)) ifFalse: [self pvtCountError: n]. 1 to: n do: [:i | self addLast: item]. methods for: 'removing' removeAll array atAllPut: nil. left := 1. right := capacity. size := 0. removeAnyOne "As long as #anyOne and #removeAnyOne are consistent, this could in general remove _any_ element. However, to be used as intended in threads.st, it must remove the first element of a deque, the best element of a heap, or indeed any element of a set-like collection" ^self removeFirst removeFirst |r| size = 0 ifTrue: [self pvtEmptyError]. size := size - 1. r := array at: left. "\ was r := array _extractAt: left." array at: left put: nil. "/ was r := array _extractAt: left." left := left < capacity ifTrue: [left + 1] ifFalse: [1]. ^r removeFirstIfAbsent: aBlock "Interface from Dolphin." ^self isEmpty ifTrue: [aBlock value] ifFalse: [self removeFirst] removeFirst: n "Could be more efficient." (n integer_between: 0 and: size) ifFalse: [self pvtCountError: n]. 1 to: n do: [:i | self removeFirst]. removeLast |r| size = 0 ifTrue: [self pvtEmptyError]. size := size - 1. r := array at: right. "\ was r := array _extractAt: right." array at: right put: nil. "/ was r := array _extractAt: right." right := right == 1 ifTrue: [capacity] ifFalse: [right - 1]. ^r removeLastIfAbsent: aBlock "Interface from Dolphin." ^self isEmpty ifTrue: [aBlock value] ifFalse: [self removeLast] removeLast: n "Could be more efficient." (n integer_between: 0 and: size) ifFalse: [self pvtCountError: n]. 1 to: n do: [:i | self removeLast]. removeEvery: item self inPlaceSelect: [:each | each ~= item]. remove: item ^self remove: item ifAbsent: [self pvtNotFoundError: item] remove: item ifAbsent: aBlock |found value| found := false. self inPlaceSelect: [:each | found or: [ each = item ifTrue: [found := true. value := each. false] ifFalse: [true]]]. ^found ifTrue: [value] ifFalse: [aBlock optionalValue: item optionalValue: self] removeAll: items items do: [:each | self remove: each]. methods for: 'enumerating' do: aBlock size = 0 ifTrue: [^self]. right < left ifFalse: [ array from: left to: right do: aBlock] ifTrue: [ array from: left to: capacity do: aBlock. array from: 1 to: right do: aBlock]. collect: aBlock ^(self copy) inPlaceCollect: aBlock; yourself inPlaceCollect: aBlock size = 0 ifTrue: [^self]. right < left ifFalse: [ "array from: left to: right inPlaceCollect: aBlock" left to: right do: [:i | array at: i put: (aBlock value: (array at: i))]] ifTrue: [ "array from: left to: capacity inPlaceCollect: aBlock." left to: capacity do: [:i | array at: i put: (aBlock value: (array at: i))]. "array from: 1 to: right inPlaceCollect: aBlock" 1 to: right do: [:i | array at: i put: (aBlock value: (array at: i))]]. inPlaceReject: aBlock ^self inPlaceSelect: [:each | (aBlock value: each) not] inPlaceSelect: aBlock |d| size = 0 ifTrue: [^self]. right < left ifFalse: [ d := 0. array from: left to: right do: [:each | (aBlock value: each) ifTrue: [ array at: (d := d + 1) put: each]]. array replaceFrom: d + 1 to: right withObject: nil. left := 1. right := size := d] ifTrue: [ d := capacity + 1. capacity to: left by: -1 do: [:i | |each| (aBlock value: (each := array at: i)) ifTrue: [ array at: (d := d - 1) put: each]]. array replaceFrom: left to: d - 1 withObject: nil. left := d. d := 0. array from: 1 to: right do: [:each | (aBlock value: each) ifTrue: [ array at: (d := d + 1) put: each]]. array replaceFrom: d + 1 to: right withObject: nil. right := d. size := capacity - left + 1 + right]. removeAllSuchThat: aBlock ^self inPlaceReject: aBlock removeAllSuchThat: aBlock returnElements: aBoolean ^aBoolean ifTrue: [|r| r := self class new: self size. self inPlaceReject: [:each | (aBlock value: each) and: [r addLast: each. true]]. r] ifFalse: [self inPlaceReject: aBlock. nil] select: aBlock ^(self copy) inPlaceSelect: aBlock; yourself reverseDo: aBlock size = 0 ifTrue: [^self]. right < left ifFalse: [ array from: left to: right reverseDo: aBlock] ifTrue: [ array from: 1 to: right reverseDo: aBlock. array from: left to: capacity reverseDo: aBlock]. methods for: 'enumerating with two collections' "Sequences have a whole lot of <seq1> with: <seq2> <enum....> methods that iterate over two sequences in parallel. While deques may not be indexed, they *are* ordered in the same way that sequences are. The definitions here work whether the other collection is a sequence or a deque. The definitions in collections.st only work when the other collection is indexable. In fact, Deques *could* be indexable. Since the index of any element is constantly changing, that didn't seem like a good idea, and I certainly didn't want to drag in all the other sequence operations like #keysAndValuesDo:. It would be nice to have an AbstractSequenceLike class with AbstractDeque and AbstractSequence as subclasses, but that would clash with the AbstractKeyedCollection class. So currently deque1 with: deque2 do: aBlock -- works deque1 with: sequence2 do: aBlock -- works sequence1 with: sequence2 do: aBlock -- works sequence1 with: deque2 do: aBlock -- fails The reason the sequence methods require the other collection to be a sequence is so that the list case will work well. But list1 with: array2 do: aBlock -- fast array1 with: list2 do: aBlock -- slow so it need not be a problem. We just need to overide #with:do: in List as well. " with: aSequence collect: aBlock |a i j| a := Array new: size. i := left - 1. j := 0. aSequence do: [:each | i := i == capacity ifTrue: [1] ifFalse: [i + 1]. a at: (j := j + 1) put: (aBlock value: (array at: i) value: each)]. ^self pvtClone pvtArray: a with: aSequence do: aBlock |i| aSequence size = size ifFalse: [self pvtSizeMismatch: aSequence]. i := left - 1. aSequence do: [:each | i := i == capacity ifTrue: [1] ifFalse: [i + 1]. aBlock value: (array at: i) value: each]. with: aSequence allSatisfy: aBlock self with: aSequence do: [:x :y | (aBlock value: x value: y) ifFalse: [^false]]. ^true with: aSequence anySatisfy: aBlock self with: aSequence do: [:x :y | (aBlock value: x value: y) ifTrue: [^true]]. ^false with: aSequence noneSatisfy: aBlock self with: aSequence do: [:x :y | (aBlock value: x value: y) ifTrue: [^false]]. ^true with: aSequence oneSatisfies: aBlock |r| r := false. self with: aSequence do: [:x :y | (aBlock value: x value: y) ifTrue: [ r ifTrue: [^false] ifFalse: [r := true]]]. ^r methods for: 'streams' atEnd ^self isEmpty next ^self removeFirst nextPut: item self addLast: item. class methods for: 'instance creation' new ^self new: 4 new: size ^(self basicNew) pvtArray: (Array new: size); removeAll; yourself new: size atAllPut: item ^(self basicNew) pvtArray: ((Array new: size) atAllPut: item; yourself); yourself with: a1 ^self basicNew pvtArray: ( Array with: a1) with: a1 with: a2 ^self basicNew pvtArray: ( Array with: a1 with: a2) with: a1 with: a2 with: a3 ^self basicNew pvtArray: ( Array with: a1 with: a2 with: a3) with: a1 with: a2 with: a3 with: a4 ^self basicNew pvtArray: ( Array with: a1 with: a2 with: a3 with: a4) with: a1 with: a2 with: a3 with: a4 with: a5 ^self basicNew pvtArray: ( Array with: a1 with: a2 with: a3 with: a4 with: a5) with: a1 with: a2 with: a3 with: a4 with: a5 with: a6 ^self basicNew pvtArray: ( Array with: a1 with: a2 with: a3 with: a4 with: a5 with: a6) withAll: aCollection ^self basicNew pvtArray: ( Array withAll: aCollection) withAll: aCollection collect: aBlock ^self basicNew pvtArray: ( Array withAll: aCollection collect: aBlock) withAll: aCollection keysAndValuesCollect: aBlock ^self basicNew pvtArray: ( Array withAll: aCollection keysAndValuesCollect: aBlock) withAll: collection1 with: collection2 collect: aBlock ^self basicNew pvtArray: ( Array withAll: collection1 with: collection2 collect: aBlock) withAll: aCollection from: start to: stop ^self basicNew pvtArray: ( Array withAll: aCollection from: start to: stop) withAll: aCollection from: start to: stop collect: aBlock ^self basicNew pvtArray: ( Array withAll: aCollection from: start to: stop collect: aBlock) "How about rotateFirstToLast self addLast: self removeFirst rotateFirstToLast: n n timesRepeat: [self rotateFirstToLast] rotateLastToFirst self addFirst: self removeLast rotateLastToFirst: n n timesRepeat: [self rotateLastToFirst] but done more efficiently? " AbstractDeque subclass: #Deque methods for: 'adding' pvtGrowAtTopBy: amount |newArray| capacity := size + amount. newArray := Array new: capacity. 1 < size ifTrue: [ right < left ifTrue: [newArray replaceFrom: 1 to: size - right with: array startingAt: left. newArray replaceFrom: size - right + 1 to: size with: array startingAt: 1] ifFalse: [newArray replaceFrom: 1 to: size with: array startingAt: left]] ifFalse: [ 0 < size ifTrue: [newArray at: 1 put: (array at: left)]]. left := 1. right := size = 0 ifTrue: [capacity] ifFalse: [size]. array := newArray. pvtGrowAtBottomBy: amount |newArray| capacity := size + amount. newArray := Array new: capacity. right < left ifTrue: [newArray replaceFrom: amount + 1 to: capacity - right with: array startingAt: left. newArray replaceFrom: capacity - right + 1 to: capacity with: array startingAt: 1] ifFalse: [newArray replaceFrom: amount + 1 to: capacity with: array startingAt: left]. right := capacity. left := size = 0 ifTrue: [1] ifFalse: [capacity - size + 1]. array := newArray. addAllFirst: aCollection |n i| n := aCollection size. size + n > capacity ifTrue: [self pvtGrowAtBottomBy: n]. size := size + n. left := left - n. left < 1 ifTrue: [left := left + capacity]. i := left. aCollection do: [:each | array at: i put: each. i := i < capacity ifTrue: [i + 1] ifFalse: [1]]. addFirst: item size < capacity ifFalse: [self pvtGrowAtBottomBy: size + 1]. size := size + 1. left := left == 1 ifTrue: [capacity] ifFalse: [left - 1]. array at: left put: item. addFirst: item withOccurrences: n (n integer_between: 0 and: (C: maxSize)) ifFalse: [self pvtCountError: n]. size + n > capacity ifTrue: [self pvtGrowAtBottomBy: n]. size := size + n. 1 to: n do: [:i | left := 1 < left ifTrue: [left - 1] ifFalse: [capacity]. array at: left put: item]. addAllLast: aCollection |n i| n := aCollection size. size + n > capacity ifTrue: [self pvtGrowAtTopBy: n]. size := size + n. i := right. aCollection do: [:each | i := i < capacity ifTrue: [i + 1] ifFalse: [1]. array at: i put: each]. right := i. addLast: item size < capacity ifFalse: [self pvtGrowAtTopBy: size + 1]. size := size + 1. right := right < capacity ifTrue: [right + 1] ifFalse: [1]. array at: right put: item. addLast: item withOccurrences: n (n integer_between: 0 and: (C: maxSize)) ifFalse: [self pvtCountError: n]. size + n > capacity ifTrue: [self pvtGrowAtTopBy: n]. size := size + n. 1 to: n do: [:i | right := right < capacity ifTrue: [right + 1] ifFalse: [1]. array at: right put: item]. rehash ^self rehash: size rehash: n |newCapacity| newCapacity := n max: size. newCapacity = capacity ifFalse: [ |a d| a := Array new: newCapacity. d := 0. self do: [:each | a at: (d := d + 1) put: each]. array := a. left := 1. right := size]. AbstractDeque subclass: #BoundedDeque methods: addFirst: item left := left == 1 ifTrue: [capacity] ifFalse: [left - 1]. array at: left put: item. size == capacity ifFalse: [size := size + 1]. addLast: item right := right == capacity ifTrue: [1] ifFalse: [right + 1]. array at: right put: item. size == capacity ifFalse: [size := size + 1]. require: 'store-deque.st' if: 'store.st'
Stéphane Ducasse http://stephane.ducasse.free.fr 06 30 93 66 73 "If you knew today was your last day on earth, what would you do differently? ....ESPECIALLY if, by doing something different, today might not be your last day on earth.” Calvin & Hobbes |