BooleanArray.st
author Stefan Vogel <sv@exept.de>
Wed, 21 Nov 2007 18:24:07 +0100
changeset 1917 61c602336f3d
parent 1176 8224efd15c5a
child 2076 57efa314833a
permissions -rw-r--r--
Clean up code and document differences between #add: and #addLast:

"
 COPYRIGHT (c) 1995 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.

 This is a demo example:

 THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
 ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
 IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
 ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
 FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
 DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
 OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
 HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
 OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
 SUCH DAMAGE.
"

"{ Package: 'stx:libbasic2' }"

ArrayedCollection variableByteSubclass:#BooleanArray
	instanceVariableNames:'tally'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Arrayed'
!

!BooleanArray class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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.

 This is a demo example:

 THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
 ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
 IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
 ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
 FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
 DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
 OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
 HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
 OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
 SUCH DAMAGE.
"
!

documentation
"
    This is a simple demo class only; currently not used in the system.

    example for bulk boolean data (requires only 1/32th the memory
    compared to an array of booleans).

    This one stores 8 booleans per byte. Since instances store bits in multiples
    of 8, we have to keep the real size of the collection in an extra instance
    variable (tally).
    It may be useful if huge boolean arrays are to be used.

    Bits 1 to 8 of the BooleanArray are stored in bits 8 to 1 of the
    corresponding byte, to allow easy mapping to ASN.1 BIT STRING encoding
    in the BER.

    [memory requirements:]
        OBJ-HEADER + ((size + 7) // 8)

    [see also:]
        ByteArray WordArray Array

    [author:]
        Claus Gittinger
"
!

examples
"
                                                                        [exBegin]
    (BooleanArray new:7) inspect
                                                                        [exEnd]
                                                                        [exBegin]
    (BooleanArray new:7) basicInspect
                                                                        [exEnd]
                                                                        [exBegin]
    |flags|

    flags := BooleanArray new:1000000.
    (flags at:9999) printNL.
    flags at:9999 put:true.
    (flags at:9999) printNL.
                                                                        [exEnd]
"
! !

!BooleanArray class methodsFor:'instance creation'!

new:size
    "return a new instance, capable of holding size booleans"

    |nBytes|

    nBytes := size // 8.
    (size \\ 8) ~~ 0 ifTrue:[nBytes := nBytes + 1].
    ^ (super new:nBytes) setTally:size

    "
     BooleanArray new:10
    "
! !

!BooleanArray methodsFor:'accessing'!

at:index
    "retrieve the boolean at index"

    |byte mask i0|

    (index between:1 and:tally) ifFalse:[
        ^ self subscriptBoundsError:index
    ].
    i0 := index - 1.
    byte := super basicAt:(i0 // 8)+1.
    mask := 1 bitShift:(7 - (i0 \\ 8)).
    ^ (byte bitAnd:mask) ~~ 0

    "
     (BooleanArray new:1000) at:555
    "

    "
     |b|

     b := BooleanArray new:1000.
     b at:555 put:true.
     b at:555   
    "

    "Modified: / 31.7.1997 / 18:37:25 / cg"
    "Modified: / 23.5.1999 / 20:02:57 / stefan"
!

at:index put:aBoolean
    "store the argument, aBoolean at index; return aBoolean."

    |byte mask idx i0|

    (index between:1 and:tally) ifFalse:[
        ^ self subscriptBoundsError:index
    ].

    i0 := index - 1.
    idx := (i0 // 8) + 1.
    byte := super basicAt:idx.
    mask := 1 bitShift:(7 - (i0 \\ 8)).
    aBoolean == true ifTrue:[
        byte := byte bitOr:mask
    ] ifFalse:[
        aBoolean == false ifTrue:[
            byte := byte bitAnd:(mask bitInvert)
        ] ifFalse:[
            "/ not true or false
            ^ self elementBoundsError:aBoolean
        ]
    ].
    super basicAt:idx put:byte.
    ^ aBoolean.

    "
     |b|

     b := BooleanArray new:1000.
     b at:555 put:true.
     b at:555   
    "

    "Modified: / 31.7.1997 / 18:37:35 / cg"
    "Modified: / 23.5.1999 / 20:02:42 / stefan"
! !

!BooleanArray methodsFor:'filling & replacing'!

atAllPut:aBoolean
    |v|

    aBoolean == true ifTrue:[
        v := 255
    ] ifFalse:[
        aBoolean == false ifTrue:[
            v := 0
        ] ifFalse:[
            "/
            "/ booleanArrays can only hold true and false
            "/
            ^ self elementBoundsError:aBoolean
        ]
    ].
    1 to:self basicSize do:[:i |
        super basicAt:i put:v
    ].
! !

!BooleanArray methodsFor:'private'!

setTally:size
    tally := size
! !

!BooleanArray methodsFor:'queries'!

defaultElement
    ^ false
!

size
    "return the size of the receiver"

    ^ tally
! !

!BooleanArray class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/BooleanArray.st,v 1.11 2003-04-22 09:38:23 cg Exp $'
! !