Queue.st
author Claus Gittinger <cg@exept.de>
Tue, 26 Nov 2002 10:03:40 +0100
changeset 1121 e7136d381499
parent 904 f4791de2295b
child 1245 99e070f7c351
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libbasic2' }"

Collection subclass:#Queue
	instanceVariableNames:'contentsArray readPosition writePosition tally'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Ordered'
!

!Queue class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Queues provides a simple implementation of a queue, where
    elements are added at one end and removed at the other.
    Access protocol is somewhat like a streams protocol, i.e. access
    is by #nextPut: and #next.
    The queue is created with a size argument, defining how many elements
    are to be stored. It will report an error if the queue ever becomes full
    and another element is to be added. Likewise, it will report an error
    if its empty and an element is to be removed.

    It is NOT safe when two processes access Queues simultanously,
    since accesses to the internals are not protected against process-switches.
    See SharedQueue for a class which IS safe with processes and blocks
    on write when full or on read when empty.

    [Implementation note:]
        All of queues functionality is also provided by the OrderedCollection (OC)
        class; OC could easily simulate a queue (using #addLast: / #removeFirst).
        The reason for providing Queue is not any speed advantage (actually,
        OC seems to be a tiny bit faster). 
        The point is that an implementation of SharedQueue as a subclass of OC
        would require that many OC methods had to be blocked and/or redefined in
        such a subclass, to care for simultaneous access.
        Since queue implements a much more lightweight protocol, 
        the sharedQueue implementation is much cleaner when based on a more
        lightweight Queue class.
        
    [author:]
        Claus Gittinger
"
!

examples
"
  adding at one end, removing at the other ...
                                                        [exBegin]
    |q element  |

    q := Queue new:10.
    1 to:5 do:[:i | 
        Transcript showCR:('adding ' , i printString).
        q nextPut:i
    ].

    [q notEmpty] whileTrue:[
        element := q next.
        Transcript showCR:('removed ' , element printString).
    ].
                                                        [exEnd]



  timing; Queue vs. OrderedCollection
                                                        [exBegin]
    |q oc tQueue tOC  |

    q := Queue new:100.
    tQueue := Time millisecondsToRun:[
        1000 timesRepeat:[
            1 to:100 do:[:i | 
                q nextPut:i
            ].
            [q isEmpty] whileFalse:[
                q next
            ].
        ]
    ].

    oc := OrderedCollection new:100.
    tOC := Time millisecondsToRun:[
        1000 timesRepeat:[
            1 to:100 do:[:i | 
                oc addLast:i
            ].
            [oc isEmpty] whileFalse:[
                oc removeFirst
            ].
        ]
    ].
    Transcript showCR:('queue time: ' , tQueue printString , ' ms').
    Transcript showCR:('oc time   : ' , tOC printString , ' ms').
                                                        [exEnd]


"
! !

!Queue class methodsFor:'instance creation'!

new
    "return a new queue with space for some elements"

    ^ self new:50
!

new:size
    "return a new queue with space for size elements"

    ^ super new init:size

    "
     |q|

     q := Queue new.
     (1 to:5) do:[:i | q nextPut:i].
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     q nextPutAll:(6 to:10).
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript show:(q next); space.
     Transcript showCR:(q next).
    "
! !

!Queue methodsFor:'accessing'!

next
    "return the next value in the queue; 
     Return nil, if the queue is empty"

    |value pos "{ Class: SmallInteger }"|

    (tally == 0) ifTrue:[^ nil].

    pos := readPosition.

    value := contentsArray at:pos.
    contentsArray at:pos put:nil.       "/ to help the garbage collector
    pos := pos + 1.
    pos > contentsArray size ifTrue:[pos := 1].
    readPosition := pos.
    tally := tally - 1.
    ^ value
!

nextPut:anObject
    "enter anObject into the queue - if the queue is full, report an error"

    |sz pos "{ Class: SmallInteger }" |

    sz := contentsArray size.
    pos := writePosition.

    (tally == sz) ifTrue:[
        self error:'queue is full' mayProceed:true.
        ^ self
    ].

    contentsArray at:pos put:anObject.
    pos := pos + 1.
    pos > sz ifTrue:[pos := 1].
    writePosition := pos.
    tally := tally + 1
!

nextPutAll:aCollection
    "enter all elements from aCollection into the queue."

    aCollection do:[:element | self nextPut:element]
!

nextPutFirst:anObject
    |sz pos "{ Class: SmallInteger }" |

    tally == 0 ifTrue:[
        self nextPut:anObject.
        ^ self
    ].

    sz := contentsArray size.
    (tally == sz) ifTrue:[
        self error:'queue is full' mayProceed:true.
        ^ self
    ].
    pos := readPosition - 1.
    pos < 1 ifTrue:[pos := sz].
    contentsArray at:pos put:anObject.
    readPosition := pos.

    tally := tally + 1
!

peek
    "return the next value in the queue without removing it.
     If the queue is empty, return nil."

    (tally == 0) ifTrue:[^ nil].
    ^ contentsArray at:readPosition.
!

removeAll
    "remove all elements in the queue; return the receiver"

    tally := 0.
    readPosition := writePosition := 1.
    contentsArray atAllPut:nil          "/ to help the garbage collector
!

removeLast
    "return the last value in the queue; 
     Return nil, if the queue is empty"

    |value pos "{ Class: SmallInteger }"|

    (tally == 0) ifTrue:[^ nil].

    pos := writePosition.
    pos == 1 ifTrue:[
        pos := contentsArray size
    ] ifFalse:[
        pos := pos - 1.
    ].

    value := contentsArray at:pos.
    contentsArray at:pos put:nil.       "/ to help the garbage collector
    writePosition := pos.
    tally := tally - 1.
    ^ value

    "Created: 22.6.1996 / 18:49:41 / cg"
! !

!Queue methodsFor:'accessing-protocol compatibility'!

addLast:someObject
    "same as #nextPut: - for protocol compatibility with other collections"

    self nextPut:someObject.
    ^ someObject

    "Created: / 27.8.1998 / 11:15:29 / cg"
!

removeFirst
    "same as #next - for protocol compatibility with other collections"

    ^ self next

    "Created: / 27.8.1998 / 11:15:48 / cg"
! !

!Queue methodsFor:'enumerating'!

do:aBlock
    "evaluate the argument, aBlock for each element in the queue"

    |n   "{ Class: SmallInteger }"
     pos "{ Class: SmallInteger }"|

    pos := readPosition.
    n := tally.
    1 to:n do:[:i |
        aBlock value:(contentsArray at:pos).
        pos := pos + 1.
        pos > contentsArray size ifTrue:[
            pos := 1
        ]
    ]

    "Modified: 18.10.1997 / 16:24:01 / cg"
! !

!Queue methodsFor:'initialization'!

init:size
    "initialize the receiver for size entries"

    contentsArray := Array new:size.
    readPosition := writePosition := 1.
    tally := 0.
! !

!Queue methodsFor:'queries'!

capacity 
    "return the number of elements the queue can hold"

    ^ contentsArray size
!

size
    "return the number of elements in the queue"

    ^ tally
! !

!Queue methodsFor:'testing'!

isEmpty
    "return true, if there are no elements in the queue"

    ^ tally == 0
!

isFull
    "return true, if the queue is full i.e. if writing is not
     possible"

    ^ tally == contentsArray size
! !

!Queue class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Queue.st,v 1.27 2002-11-26 09:03:40 cg Exp $'
! !