UIBytes.st
author Claus Gittinger <cg@exept.de>
Wed, 21 Jan 1998 17:38:18 +0100
changeset 3209 eff7ad7f0825
parent 3207 a6e3c98e2a8e
child 3212 b8cc18f8691b
permissions -rw-r--r--
checkin from browser

"
 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.
"

ArrayedCollection subclass:#UninterpretedBytes
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Abstract'
!

!UninterpretedBytes 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
"
    UninterpretedBytes provides the common protocol for byte-storage 
    containers; concrete subclasses are 
	ByteArray (which store the bytes within the
    		   Smalltalk object memory) 
    and 
	ExternalBytes (which store the bytes in the malloc-heap).

    UninterpretedBytes itself is abstract, so no instances of it can be created.

    [author:]
        Claus Gittinger

    [See also:]
        ByteArray String ExternalBytes

    [author:]
        Claus Gittinger
"
! !

!UninterpretedBytes class methodsFor:'binary storage'!

binaryDefinitionFrom:stream manager:manager
    "get a ByteArray from the binary stream.
     ByteArrays are stored as 4-byte size, followed by the bytes.
     This is only invoked for long bytearrays. 
     Short ones are stored with 1byte length."

    self subclassResponsibility
! !

!UninterpretedBytes class methodsFor:'queries'!

isBigEndian
    "return true, if words/shorts store the most-significant
     byte first (MSB), false if least-sign.-first (LSB). 
     I.e. false for vax, intel; true for m68k, sun."

%{  /* NOCONTEXT */

    /*
     * I dont like ifdefs - you always forget some ...
     * therefore we look into a structure at run-time
     */
    union {
	unsigned int   u_l;
	char           u_c[sizeof(int)];
    } u;

    u.u_l = 0x87654321;
    if (u.u_c[0] == 0x21) RETURN (false);
    RETURN (true);
%}
    "UninterpretedBytes isBigEndian"
!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned, since ByteStore is the superclass of
     some builtIn classes (ByteArray & ExternalBytes)"

    ^ self == UninterpretedBytes

    "Modified: 23.4.1996 / 15:56:25 / cg"
! !

!UninterpretedBytes methodsFor:'accessing'!

basicAt:index
    "return the indexed instance variable with index, anInteger.
     This must be provided by a concrete subclass."

    ^ self subclassResponsibility
!

basicAt:index put:value
    "set the indexed instance variable with index, anInteger to value.
     Returns value (sigh).
     This must be provided by a concrete subclass."

    ^ self subclassResponsibility
!

byteAt:index
    "return the byte at index. 
     For ByteArray, this is the same as basicAt:; 
     however, for strings or symbols, this returns a numeric byteValue
     instead of a character."

    ^ self subclassResponsibility
!

byteAt:index put:value
    "set the byte at index. For ByteArray, this is the same as basicAt:put:.
     However, for Strings, this expects a byteValue to be stored."

    ^ self subclassResponsibility
!

doubleAt:index
    "return the 8-bytes starting at index as a Float.
     Notice, that (currently) ST/X Floats are what Doubles are in ST-80.
     Notice also, that the bytes are expected to be in this machines
     float representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

    newFloat := Float basicNew.
    1 to:8 do:[:destIndex|
	newFloat basicAt:destIndex put:(self at:index - 1 + destIndex)
    ].
    ^ newFloat.
!

doubleAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     starting at index.
     Notice, that (currently) ST/X Floats are what Doubles are in ST-80.
     Notice also, that the bytes are expected to be in this machines
     float representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |flt|

    flt := aFloat asFloat.
    1 to:8 do:[:srcIndex|
        self at:index - 1 + srcIndex put:(flt basicAt:srcIndex)
    ].
    ^ aFloat
!

doubleWordAt:index
    "return the 4-bytes starting at index as an (unsigned) Integer.
     The value is retrieved in the machines natural byte order.
     Subclasses may redefine this for better performance."

    ^ self doubleWordAt:index MSB:(UninterpretedBytes isBigEndian)

    "
     |b|

     b := ByteArray withAll:#(1 2 3 4).
     (b doubleWordAt:1) printStringRadix:16   
    "
!

doubleWordAt:index MSB:msb
    "return the 4-bytes starting at index as an (unsigned) Integer.
     The value is retrieved MSB-first, if the msb-arg is true;
     LSB-first otherwise.
     Subclasses may redefine this for better performance."

    |v|

    msb ifTrue:[
        v := self at:index.
        1 to:3 do:[:i |
            v := (v bitShift:8) bitOr:(self at:index+i)
        ].
    ] ifFalse:[
	v := self at:index+3.
	2 to:0 by:-1 do:[:i |
	    v := (v bitShift:8) bitOr:(self at:index+i)
	]
    ].
    ^ v

    "
     |b|

     b := ByteArray withAll:#(1 2 3 4).
     (b doubleWordAt:1 MSB:true) printStringRadix:16.   
     (b doubleWordAt:1 MSB:false) printStringRadix:16   
    "
!

doubleWordAt:index put:value
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The value should be in the range 0 to 16rFFFFFFFF
     (for negative values, the stored value is not defined).
     The value is stored in the machines natural byte order.
     Subclasses may redefine this for better performance."

    ^ self doubleWordAt:index put:value MSB:(UninterpretedBytes isBigEndian)

    "
     |b|
     b := ByteArray new:4.
     b doubleWordAt:1 put:16r04030201.
     b inspect
    "
!

doubleWordAt:index put:value MSB:msb
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The value must be in the range 0 to 16rFFFFFFFF.
     The value is stored MSB-first if msb is true; LSB-first otherwise.
     Subclasses may redefine this for better performance."

    |v|

    ((value < 0) or:[value > 16rFFFFFFFF]) ifTrue:[
	^ self elementBoundsError
    ].
    v := value.
    msb ifTrue:[
        3 to:0 by:-1 do:[:i |
            self at:index+i put:(v bitAnd:16rFF).
	    v := v bitShift:-8
        ].
    ] ifFalse:[
        0 to:3 by:-1 do:[:i |
            self at:index+i put:(v bitAnd:16rFF).
	    v := v bitShift:-8
        ]
    ].
    ^ value

    "
     |b|
     b := ByteArray new:8.
     b doubleWordAt:1 put:16r04030201 MSB:true.
     b doubleWordAt:5 put:16r04030201 MSB:false.
     b inspect
    "
!

floatAt:index
    "return the 4-bytes starting at index as a Float.
     Notice, that (currently) ST/X Floats are what Doubles are in ST-80;
     therefore this method reads a 4-byte float from the byteArray and returns
     a float object which keeps an 8-byte double internally.
     Notice also, that the bytes are expected to be in this machines
     float representation and order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

    newFloat := ShortFloat basicNew.
    1 to:4 do:[:destIndex|
        newFloat basicAt:destIndex put:(self at:index - 1 + destIndex)
    ].
    ^ newFloat.
!

floatAt:index put:aFloat
    "store the 4 bytes of value of the argument, aFloat into the receiver
     starting at index.
     Notice, that (currently) ST/X Floats are what Doubles are in ST-80.
     Notice also, that the bytes are expected to be in this machines
     float representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |sflt|

    sflt := aFloat asShortFloat.
    1 to:4 do:[:srcIndex|
        self at:index - 1 + srcIndex put:(sflt basicAt:srcIndex)
    ].
    ^ aFloat
!

ieeDoubleAt:index
    "retrieve the 8 bytes starting at index as a float.
     The 8 bytes are assumed to be in IEE floating point single precision
     number format."

    "
     currently, we assume that the machines native number format is already
     IEE format - we need some more code here whenever ST/X is ported
     to an IBM 370 or old VAX etc.
     To date, all supported systems use IEE float numbers, so there should be
     no problem.
    "
    ^ self doubleAt:index
!

ieeDoubleAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     starting at index. Storage is in IEE floating point double precision format.
     (i.e. 8 bytes are stored)."

    "
     currently, we assume that the machines native number format is already
     IEE format - we need some more code here whenever ST/X is ported
     to an IBM 370 or old VAX etc.
     To date, all supported systems use IEE float numbers, so there should be
     no problem.
    "
    ^ self doubleAt:index put:aFloat
!

ieeFloatAt:index
    "retrieve the 4 bytes starting at index as a float.
     The 4 bytes are assumed to be in IEE floating point single precision
     number format."

    "
     currently, we assume that the machines native number format is already
     IEE format - we need some more code here whenever ST/X is ported
     to an IBM 370 or old VAX etc.
     To date, all supported systems use IEE float numbers, so there should be
     no problem.
    "
    ^ self floatAt:index
!

ieeFloatAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     starting at index. Storage is in IEE floating point single precision format.
     (i.e. 4 bytes are stored). Since ST/X floats are really doubles, the low-
     order 4 bytes of the precision is lost."

    "
     currently, we assume that the machines native number format is already
     IEE format - we need some more code here whenever ST/X is ported
     to an IBM 370 or old VAX etc.
     To date, all supported systems use IEE float numbers, so there should be
     no problem.
    "
    ^ self floatAt:index put:aFloat
!

quadWordAt:index MSB:msb
    "return the 8-bytes starting at index as an (unsigned) Integer.
     Depending on msb, the value is retrieved MSB or LSB-first."

    |l 
     bIdx  "{ Class: SmallInteger }"
     delta "{ Class: SmallInteger }"|

    l := LargeInteger basicNew numberOfDigits:8.
    msb ifTrue:[
	bIdx := index + 7.
	delta := -1
    ] ifFalse:[
	bIdx := index.
	delta := 1
    ].
    1 to:8 do:[:i |
	l digitAt:i put:(self basicAt:bIdx).
	bIdx := bIdx + delta
    ].
    ^ l compressed

    "
     |b|

     b := ByteArray withAll:#(1 2 3 4 5 6 7 8).
     (b quadWordAt:1 MSB:false) printStringRadix:16  
    "

    "Modified: 5.11.1996 / 14:06:21 / cg"
!

quadWordAt:index put:anInteger MSB:msb
    "set the 8-bytes starting at index from the (unsigned) Integer value.
     The value must be in the range 0 to 16rFFFFFFFFFFFFFFFF.
     Depending on msb, the value is stored MSB-first or LSB-first."

    |bIdx  "{ Class: SmallInteger }"
     delta "{ Class: SmallInteger }"|

    ((anInteger < 0) or:[anInteger > 16rFFFFFFFFFFFFFFFF]) ifTrue:[
	^ self elementBoundsError
    ].

    msb ifTrue:[
	bIdx := index + 7.
	delta := -1
    ] ifFalse:[
	bIdx := index.
	delta := 1
    ].
    1 to:8 do:[:i |
	self basicAt:bIdx put:(anInteger digitAt:i).
	bIdx := bIdx + delta.
    ].
    ^ anInteger

    "
     |b|
     b := ByteArray new:8.
     b quadWordAtIndex:1 put:16r0807060504030201 MSB:false.
     b inspect
    "
!

signedByteAt:index
    "return the byte at index as a signed 8 bit value.
     This may be worth a primitive."

    ^ (self at:index) signExtendedByteValue

    "
     |b|
     b := ByteArray new:2.
     b at:1 put:16rFF.
     b at:2 put:16r7F.
     b signedByteAt:1  
    "

    "Modified: 1.7.1996 / 21:13:53 / cg"
!

signedByteAt:index put:aSignedByteValue
    "return the byte at index as a signed 8 bit value.
     Return the signedByteValue argument.
     This may be worth a primitive."

    |b "{ Class: SmallInteger }"|

    aSignedByteValue >= 0 ifTrue:[
	b := aSignedByteValue
    ] ifFalse:[
	b := 16r100 + aSignedByteValue
    ].
    self at:index put:b.
    ^ aSignedByteValue

    "
     |b|
     b := ByteArray new:2.
     b signedByteAt:1 put:-1.
     b at:1   
    "

    "Modified: 1.7.1996 / 21:12:37 / cg"
!

signedDoubleWordAt:index
    "return the 4-bytes starting at index as a signed Integer.
     The value is retrieved in the machines natural byte order.
     This may be worth a primitive."

    |w|

    w := self doubleWordAt:index.
    (w > (16r7FFFFFFF)) ifTrue:[
	^ w - (16r100000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:4.
     b doubleWordAt:1 put:16rFFFFFFFF.
     (b signedDoubleWordAt:1)    
    "

    "Modified: 1.7.1996 / 21:11:28 / cg"
!

signedDoubleWordAt:index MSB:msb
    "return the 4-bytes starting at index as a signed Integer.
     Depending on msb, the value is retrieved MSB-first or LSB-first.
     This may be worth a primitive."

    |w|

    w := self doubleWordAt:index MSB:msb.
    (w > (16r7FFFFFFF)) ifTrue:[
	^ w - (16r100000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:4.
     b doubleWordAt:1 put:16rFFFFFFFF.
     (b signedDoubleWordAt:1)    
    "

    "Modified: 1.7.1996 / 21:11:33 / cg"
!

signedDoubleWordAt:index put:value
    "set the 4-bytes starting at index from the signed Integer value.
     The value is stored in the machines natural byte order.
     This may be worth a primitive."

    |v|

    value >= 0 ifTrue:[
	v := value
    ] ifFalse:[
	v := value + 16r100000000
    ].
    self doubleWordAt:index put:v.
    ^ value

    "
     |b|
     b := ByteArray new:4.
     b signedDoubleWordAt:1 put:-1.
     (b doubleWordAt:1) printStringRadix:16   
    "

    "Modified: 1.7.1996 / 21:11:39 / cg"
!

signedDoubleWordAt:index put:value MSB:msb
    "set the 4-bytes starting at index from the signed Integer value.
     Depending on msb, the value is stored MSB-first or LSB-first.
     This may be worth a primitive."

    |v|

    value >= 0 ifTrue:[
	v := value
    ] ifFalse:[
	v := value + 16r100000000
    ].
    self doubleWordAt:index put:v MSB:msb.
    ^ value

    "
     |b|
     b := ByteArray new:4.
     b signedDoubleWordAt:1 put:-1.
     (b doubleWordAt:1) printStringRadix:16   
    "

    "Modified: 1.7.1996 / 21:11:46 / cg"
!

signedWordAt:index
    "return the 2-bytes starting at index as a signed Integer.
     The value is retrieved in the machines natural byte order.
     This may be worth a primitive."

    ^ (self wordAt:index) signExtendedShortValue

    "
     |b|
     b := ByteArray new:2.
     b wordAt:1 put:16rFFFF.
     b signedWordAt:1  
    "

    "Modified: 1.7.1996 / 21:14:38 / cg"
!

signedWordAt:index MSB:msb
    "return the 2-bytes starting at index as a signed Integer.
     The value is retrieved MSB-first if the msb-arg is true,
     LSB-first otherwise.
     This may be worth a primitive."

    ^ (self wordAt:index MSB:msb) signExtendedShortValue

    "
     |b|
     b := ByteArray new:2.
     b wordAt:1 put:16r0080.
     b signedWordAt:1 MSB:true.  
     b signedWordAt:1 MSB:false.  
    "

    "Modified: 1.7.1996 / 21:15:57 / cg"
!

signedWordAt:index put:value
    "set the 2-bytes starting at index from the signed Integer value.
     The stored value must be in the range -32768 .. +32676.
     The value is stored in the machines natural byteorder.
     This may be worth a primitive."

    |v|

    value >= 0 ifTrue:[
	v := value
    ] ifFalse:[
	v := 16r10000 + value
    ].
    self wordAt:index put:v.
    ^ value

    "
     |b|
     b := ByteArray new:6.
     b signedWordAt:1 put:-1.
     b signedWordAt:3 put:-2.
     b signedWordAt:5 put:0.
     b inspect
    "

    "Modified: 1.7.1996 / 21:12:07 / cg"
!

signedWordAt:index put:value MSB:msb
    "set the 2-bytes starting at index from the signed Integer value.
     The stored value must be in the range -32768 .. +32676.
     The value is stored MSB-first, if the msb-arg is true;
     LSB-first otherwise.
     This may be worth a primitive."

    |v|

    value >= 0 ifTrue:[
	v := value
    ] ifFalse:[
	v := 16r10000 + value
    ].
    self wordAt:index put:v MSB:msb.
    ^ value

    "
     |b|
     b := ByteArray new:4.
     b signedWordAt:1 put:-1.
     b signedWordAt:3 put:-2.
     b inspect
    "

    "Modified: 1.7.1996 / 21:12:13 / cg"
!

stringAt:index size:count
    "extract a string, given initial index and number of characters (bytes)"

    ^ (self copyFrom:index to:(index + count - 1)) asString

    "Modified: 9.9.1996 / 15:28:08 / cg"
    "Created: 9.9.1996 / 15:28:48 / cg"
!

wordAt:index
    "return the 2-bytes starting at index as an (unsigned) Integer.
     The value is retrieved in the machines natural byte order
     Subclasses may redefine this for better performance."

    ^ self wordAt:index MSB:(UninterpretedBytes isBigEndian)
!

wordAt:index MSB:msb
    "return the 2-bytes starting at index as an (unsigned) Integer.
     The value is retrieved MSB (high 8 bits at lower index) if msb is true;
     LSB-first (i.e. low 8-bits at lower byte index) if its false.
     Question: should it be retrieve signed values ? (see ByteArray>>signedWordAt:)"

    |v|

    msb ifTrue:[
	v := self at:index.
	^ (v bitShift:8) bitOr:(self at:index+1)
    ].
    v := self at:index+1.
    ^ (v bitShift:8) bitOr:(self at:index)
!

wordAt:index put:value
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The stored value must be in the range 0 .. 16rFFFF. 
     The value is stored in the machines natural byteorder.
     Question: should it accept signed values ? (see ByteArray>>signedWordAt:put:)"

    ^ self wordAt:index put:value MSB:(UninterpretedBytes isBigEndian)

    "
     |b|
     b := ByteArray new:4.
     b wordAt:1 put:16r0102.
     b wordAt:3 put:16r0304.
     b inspect  
    "
!

wordAt:index put:value MSB:msb
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The stored value must be in the range 0 .. 16rFFFF. 
     The value is stored LSB-first (i.e. the low 8bits are stored at the
     lower index) if msb is false, MSB-first otherwise.
     Question: should it accept signed values ? (see ByteArray>>signedWordAt:put:)"

    ((value < 0) or:[value > 16rFFFF]) ifTrue:[
	^ self elementBoundsError
    ].
    msb ifTrue:[
	self at:index put:((value bitShift:-8) bitAnd:16rFF).
	self at:index+1 put:(value bitAnd:16rFF).
    ] ifFalse:[
	self at:index put:(value bitAnd:16rFF).
	self at:index+1 put:((value bitShift:-8) bitAnd:16rFF).
    ].
    ^ value

    "
     b := ByteArray new:8.
     b wordAt:1 put:16r0102 MSB:false.
     b wordAt:3 put:16r0304 MSB:false.
     b wordAt:5 put:16r0102 MSB:true.
     b wordAt:7 put:16r0304 MSB:true.
     b inspect  
    "
!

zeroByteStringAt:index maximumSize:count
    "extract a zeroByte-delimited string, given initial index and
     maximum number of characters (bytes)"

    |bytes idx|

    bytes := self copyFrom:index to:(index + count - 1).
    idx := bytes indexOf:0.
    idx ~~ 0 ifTrue:[ bytes := bytes copyTo:idx-1 ].
    ^ bytes asString

    "Created: 9.9.1996 / 15:28:34 / cg"
! !

!UninterpretedBytes class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Attic/UIBytes.st,v 1.18 1998-01-21 16:38:18 cg Exp $'
! !