UninterpretedBytes.st
author Claus Gittinger <cg@exept.de>
Mon, 18 May 1998 14:20:27 +0200
changeset 3459 6cb151c3950c
parent 3447 4009e251544b
child 3936 dd8cd28d4a9b
permissions -rw-r--r--
category changes

"
 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:'IsBigEndian'
	poolDictionaries:''
	category:'Collections-Abstract'
!

!UninterpretedBytes primitiveDefinitions!
%{
/*
 * Notice: I am abstract, and my subclasses may be anything.
 * Therefore, the code must always handle the fallback case
 * where the receiver is neither an ExternalBytes nor a ByteArray.
 * (which are, however, the most common)
 *
 * macro to fetch my byte address and size-in-bytes;
 * convenient for inline-C code.
 * (yes, C is bad ...)
 */
#define __fetchBytePointerAndSize__(o, pPtr, pSize) \
    {\
      if (__isNonNilObject(o)) { \
        if (__qClass(o) == ByteArray) { \
	  *(pPtr) = (char *)__ByteArrayInstPtr(o)->ba_element; \
	  *(pSize) = __byteArraySize(o); \
	} else if (__qClass(o) == ExternalBytes) { \
	  OBJ __sz__ = __externalBytesSize(o); \
	  if (__isSmallInteger(__sz__)) { \
	    *(pSize) = __intVal(__sz__); \
	    *(pPtr) = (char *)(__externalBytesAddress(o)); \
	  } else { \
	    *(pPtr) = (char *)0; \
	  } \
	} else { \
	    *(pPtr) = (char *)0; \
	} \
      } else { \
	*(pPtr) = (char *)0; \
      } \
    }

%}
! !

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

    [See also:]
        ByteArray String ExternalBytes

    [author:]
        Claus Gittinger

    [Notice:]
	Notice the confusion due to multiple methods with the same
        functionality (i.e. 'xxxx:MSB:' vs. 'xxxx:bigEndian:').
        The reason is that at the time this class was written,
        ST80 sid not offer protocol to specify the byteOrder, and
        ST/X provided methods ending in 'MSB:' for this.
        In the meanwhile, VW added protocol ending in 'bigEndian:',
	which has been added here for compatibility.
	(certainly a point, where an ansi-standard will help)
"
! !

!UninterpretedBytes class methodsFor:'initialization'!

checkByteOrder
    "initialize our current byteOrder.
     Must be called at system init time and on snapshot restart"

    IsBigEndian := self isBigEndian.

    "Created: / 5.3.1998 / 14:51:41 / stefan"
!

initialize
    "get the byte order"

    self checkByteOrder.

    "want to be informed when returning from snapshot"
    ObjectMemory dependents addDependent:self

    "Created: / 5.3.1998 / 14:46:31 / stefan"
    "Modified: / 5.3.1998 / 14:53:28 / stefan"
!

update:something with:aParameter from:changedObject
    "handle image restarts and reget the byte order"

    (something == #returnFromSnapshot) ifTrue:[
        self checkByteOrder.
    ]

    "Created: / 5.3.1998 / 14:55:13 / stefan"
! !

!UninterpretedBytes class methodsFor:'instance creation'!

from:aCollection
    ^ ByteArray from:aCollection

    "Created: / 3.4.1998 / 13:29:50 / cg"
    "Modified: / 3.4.1998 / 13:30:12 / cg"
! !

!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.
     * (also, there are CPUs around [mips], where the byteorder
     *  is programmable, and which come in different flavours)
     *
     * NOTICE: 
     *    both the JIT and stc may inline this to a 
     *    constant for systems where this is known.
     */
    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 UninterpretedBytes is the superclass of
     some builtIn classes (ByteArray & ExternalBytes)"

    ^ self == UninterpretedBytes

    "Modified: / 23.4.1996 / 15:56:25 / cg"
    "Modified: / 5.3.1998 / 14:56:22 / stefan"
! !

!UninterpretedBytes methodsFor:'accessing-bytes'!

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
!

signedByteAt:index
    "return the byte at index as a signed 8 bit value.
     The index is a smalltalk index (i.e. 1-based).
     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.
     The index is a smalltalk index (i.e. 1-based).
     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"
! !

!UninterpretedBytes methodsFor:'accessing-floats & doubles'!

doubleAt:index
    "return the 8-bytes starting at index as a Float.
     The index is a smalltalk index (i.e. 1-based).
     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|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
	char *cp;
	int sz;
	
	__fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
	    unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

	    if ((idx+(sizeof(double)-1)) < sz) {
		cp += idx;
		/*
		 * aligned
		 */
		if (((INT)cp & (sizeof(double)-1)) == 0) {
		    double dVal = ((double *)cp)[0];
		    OBJ f;

		    __qMKFLOAT(f, dVal);
                    RETURN (f);
		}
	    }
	}
    }
%}.

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

    "
     |b|

     b := ByteArray new:20.
     b doubleAt:1 put:(Float pi).
     Transcript showCR:b.
     Transcript showCR:(b doubleAt:1)
    "
!

doubleAt:index MSB:msb
    "return the 8-bytes starting at index as a Float.
     The index is a smalltalk index (i.e. 1-based).
     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|

    msb == UninterpretedBytes isBigEndian ifTrue:[
        ^ self doubleAt:index.
    ].

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

    "Created: / 15.5.1998 / 17:21:45 / cg"
!

doubleAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     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.
%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index) && __isFloat(flt)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(double)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(double)-1)) == 0) {
                    ((double *)cp)[0] = __floatVal(flt);
                    RETURN (aFloat);
                }
            }
        }
    }
%}.

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

doubleAt:index put:aFloat MSB:msb
    "store the value of the argument, aFloat into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     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|

    msb == UninterpretedBytes isBigEndian ifTrue:[
        ^ self doubleAt:index put:aFloat.
    ].

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

    "Created: / 15.5.1998 / 17:22:27 / cg"
    "Modified: / 15.5.1998 / 17:26:29 / cg"
!

floatAt:index
    "return the 4-bytes starting at index as a ShortFloat.
     The index is a smalltalk index (i.e. 1-based).
     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|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(float)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(float)-1)) == 0) {
                    float fVal = ((float *)cp)[0];
		    OBJ f;

		    __qMKSFLOAT(f, fVal);
                    RETURN (f);
                }
            }
        }
    }
%}.

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

floatAt:index MSB:msb
    "return the 4-bytes starting at index as a ShortFloat.
     The index is a smalltalk index (i.e. 1-based).
     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|

    msb == UninterpretedBytes isBigEndian ifTrue:[
        ^ self floatAt:index
    ].

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

    "Modified: / 15.5.1998 / 17:20:19 / cg"
    "Created: / 15.5.1998 / 17:20:35 / cg"
!

floatAt:index put:aFloat
    "store the 4 bytes of value of the argument, aFloat into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     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.
%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index) && __isShortFloat(sflt)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(float)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(float)-1)) == 0) {
                    ((float *)cp)[0] = __shortFloatVal(sflt);

                    RETURN (aFloat);
                }
            }
        }
    }
%}.

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

floatAt:index put:aFloat MSB:msb
    "store the 4 bytes of value of the argument, aFloat into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     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|

    msb == UninterpretedBytes isBigEndian ifTrue:[
        ^ self floatAt:index put:aFloat
    ].

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

    "Created: / 15.5.1998 / 17:20:41 / cg"
!

ieeeDoubleAt:index
    "retrieve the 8 bytes starting at index as a float.
     The index is a smalltalk index (i.e. 1-based).
     The 8 bytes are assumed to be in IEEE floating point single precision
     number format."

    "
     currently, we assume that the machines native number format is already
     IEEE 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 IEEE float numbers, so there should be
     no problem.
    "
    self isIEEEFormat ifFalse:[self error:'unsupported operation'].

    ^ self doubleAt:index

    "Created: / 5.3.1998 / 10:50:03 / stefan"
!

ieeeDoubleAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     The index is a smalltalk index (i.e. 1-based).
     starting at index. Storage is in IEEE floating point double precision format.
     (i.e. 8 bytes are stored)."

    "
     currently, we assume that the machines native number format is already
     IEEE 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 IEEE float numbers, so there should be
     no problem.
    "
    self isIEEEFormat ifFalse:[self error:'unsupported operation'].

    ^ self doubleAt:index put:aFloat

    "Created: / 5.3.1998 / 10:50:26 / stefan"
!

ieeeFloatAt:index
    "retrieve the 4 bytes starting at index as a float.
     The index is a smalltalk index (i.e. 1-based).
     The 4 bytes are assumed to be in IEEE floating point single precision
     number format."

    "
     currently, we assume that the machines native number format is already
     IEEE 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 IEEE float numbers, so there should be
     no problem.
    "
    self isIEEEFormat ifFalse:[self error:'unsupported operation'].

    ^ self floatAt:index

    "Created: / 5.3.1998 / 10:50:45 / stefan"
!

ieeeFloatAt:index put:aFloat
    "store the value of the argument, aFloat into the receiver
     starting at index, which is a smalltalk index (i.e. 1-based). 
     Storage is in IEEE 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
     IEEE 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 IEEE float numbers, so there should be
     no problem.
    "
    self isIEEEFormat ifFalse:[self error:'unsupported operation'].

    ^ self floatAt:index put:aFloat

    "Created: / 5.3.1998 / 10:51:11 / stefan"
! !

!UninterpretedBytes methodsFor:'accessing-longlongs'!

longLongAt:index
    "return the 8-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machines natural byte order.
     This may be worth a primitive."

    |w|

    w := self unsignedLongLongAt:index bigEndian:IsBigEndian.
    (w > (16r7FFFFFFFFFFFFFFF)) ifTrue:[
        ^ w - (16r10000000000000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:4.
     b unsignedLongLongAt:1 put:16rFFFFFFFFFFFFFFFF.
     (b longLongAt:1)    
    "

    "Modified: / 1.7.1996 / 21:11:28 / cg"
    "Created: / 5.3.1998 / 14:40:05 / stefan"
    "Modified: / 5.3.1998 / 14:58:32 / stefan"
!

longLongAt:index bigEndian:msb
    "return the 8-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the given byte order.
     This may be worth a primitive."

    |w|

    w := self unsignedLongLongAt:index bigEndian:msb.
    (w > (16r7FFFFFFFFFFFFFFF)) ifTrue:[
        ^ w - (16r10000000000000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:4.
     b unsignedLongLongAt:1 put:16rFFFFFFFFFFFFFFFF.
     (b longLongAt:1 msb:true)    
    "

    "Modified: / 5.3.1998 / 12:06:28 / stefan"
    "Created: / 5.3.1998 / 14:40:54 / stefan"
    "Modified: / 9.5.1998 / 01:10:59 / cg"
!

longLongAt:byteIndex put:anInteger
    "store a signed longLong (64bit) integer.
     The index is a smalltalk index (i.e. 1-based).
     Same as #signedQuadWordAt:put: - for ST80 compatibility."

    ^ self signedQuadWordAt:byteIndex put:anInteger

    "Modified: / 3.4.1998 / 13:33:14 / cg"
    "Created: / 3.4.1998 / 13:34:22 / cg"
!

longLongAt:byteIndex put:anInteger bigEndian:msb
    "store a signed longLong (64bit) integer.
     The index is a smalltalk index (i.e. 1-based).
     Same as #signedQuadWordAt:put: - for ST80 compatibility."

    |v|

    v := anInteger.
    anInteger < 0 ifTrue:[
        v := v + 16r10000000000000000
    ].
    ^ self unsignedLongLongAt:byteIndex put:v bigEndian:msb

    "Created: / 9.5.1998 / 01:10:24 / cg"
    "Modified: / 9.5.1998 / 01:13:34 / cg"
!

quadWordAt:index MSB:msb
    "return the 8-bytes starting at index as an (unsigned) Integer.
     The index is a smalltalk index (i.e. 1-based).
     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 index is a smalltalk index (i.e. 1-based).
     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
    "
!

unsignedLongLongAt:index bigEndian:msb
    "return the 8-bytes starting at index as an (unsigned) Integer.
     The index is a smalltalk index (i.e. 1-based).
     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 unsignedLongLongAt:1 bigEndian:false) printStringRadix:16  
    "

    "Modified: / 5.11.1996 / 14:06:21 / cg"
    "Modified: / 5.3.1998 / 14:04:44 / stefan"
!

unsignedLongLongAt:index put:anInteger
    "set the 8-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     The value must be in the range 0 to 16rFFFFFFFFFFFFFFFF.
     The value is stored in natural byte order."

    ^ self unsignedLongLongAt:index put:anInteger bigEndian:IsBigEndian

    "Created: / 5.3.1998 / 14:44:00 / stefan"
    "Modified: / 5.3.1998 / 15:02:32 / stefan"
!

unsignedLongLongAt:index put:anInteger bigEndian:msb
    "set the 8-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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 unsignedLongLongAt:1 put:16r0807060504030201 bigEndian:false.
     b inspect
    "

    "Created: / 5.3.1998 / 14:06:02 / stefan"
! !

!UninterpretedBytes methodsFor:'accessing-longs'!

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

     OBSOLETE: please use longAt: / unsignedLongAt:"

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(int)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(int)-1)) == 0) {
                    int iVal = ((int *)cp)[0];

                    RETURN (__MKUINT(iVal));
                }
            }
        }
    }
%}.

    ^ self doubleWordAt:index MSB:IsBigEndian

    "
     |b|

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

    "Modified: / 5.3.1998 / 14:57:35 / stefan"
!

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

    |val 
     ival "{ XXClass: SmallInteger }"
     i    "{ Class: SmallInteger }"
     b1   "{ Class: SmallInteger }"
     b2   "{ Class: SmallInteger }"
     b3   "{ Class: SmallInteger }"
     b4   "{ Class: SmallInteger }"|

    i := index.
    b1 := self at:i.
    b2 := self at:(i+1).
    b3 := self at:(i+2).
    b4 := self at:(i+3).

    msb ifTrue:[
        ival := b1.
        ival := (ival bitShift:8) + b2.
        ival := (ival bitShift:8) + b3.
        val := (ival bitShift:8) + b4.
    ] ifFalse:[
        ival := b4.
        ival := (ival bitShift:8) + b3.
        ival := (ival bitShift:8) + b2.
        val := (ival bitShift:8) + b1.
    ].
    ^ val

    "
     |b|

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

    "Modified: / 21.1.1998 / 17:42:30 / cg"
!

doubleWordAt:index put:value
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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:IsBigEndian

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

    "Modified: / 5.3.1998 / 14:57:48 / stefan"
!

doubleWordAt:index put:aNumber MSB:msb
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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."

    |i "{ Class: SmallInteger }" |

    ((aNumber < 0) or:[aNumber > 16rFFFFFFFF]) ifTrue:[
        ^ self elementBoundsError
    ].

    i := index.
    msb ifTrue:[
        self at:i     put:(aNumber digitAt:4).
        self at:(i+1) put:(aNumber digitAt:3).
        self at:(i+2) put:(aNumber digitAt:2).
        self at:(i+3) put:(aNumber digitAt:1).
    ] ifFalse:[
        self at:i     put:(aNumber digitAt:1).
        self at:(i+1) put:(aNumber digitAt:2).
        self at:(i+2) put:(aNumber digitAt:3).
        self at:(i+3) put:(aNumber digitAt:4).
    ].
    ^ aNumber

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

    "Modified: / 21.1.1998 / 17:43:34 / cg"
    "Modified: / 5.3.1998 / 11:42:17 / stefan"
!

doubleWordAtDoubleWordIndex:index
    "return the unsigned long at index, anInteger. 
     Fetching in the machines natural byte order.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of doubleWord entries.
     (i.e. indices are 1, 2, ...)"

    ^ self doubleWordAtDoubleWordIndex:index MSB:IsBigEndian

    "Created: / 21.1.1998 / 17:43:53 / cg"
    "Modified: / 5.3.1998 / 14:58:06 / stefan"
!

doubleWordAtDoubleWordIndex:index MSB:msb
    "return the unsigned long at index, anInteger. 
     Fetching is MSB if msb is true, LSB otherwise.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of doubleWord entries.
     (i.e. indices are 1, 2, ...)"

    ^ self doubleWordAt:(index - 1 * 4 + 1) MSB:msb

    "Created: / 21.1.1998 / 17:44:07 / cg"
!

doubleWordAtDoubleWordIndex:index put:value
    "set the long at index, anInteger. 
     Storing in the machines natural byte order.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of doubleWord entries.
     (i.e. indices are 1, 2, ...)"

    ^ self doubleWordAtDoubleWordIndex:index put:value MSB:IsBigEndian

    "Created: / 21.1.1998 / 17:44:13 / cg"
    "Modified: / 5.3.1998 / 14:58:19 / stefan"
!

doubleWordAtDoubleWordIndex:index put:value MSB:msb
    "set the long at index, anInteger. 
     Storing is MSB if msb is true, LSB otherwise.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of doubleWord entries.
     (i.e. indices are 1, 2, ...)"

    ^ self doubleWordAt:(index - 1 * 4 + 1) put:value MSB:msb

    "Created: / 21.1.1998 / 17:44:19 / cg"
!

longAt:index
    "return the 4-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machines natural byte order.
     This may be worth a primitive."

    |w|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(float)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(float)-1)) == 0) {
                    INT iVal = ((int *)cp)[0];

                    RETURN (__MKINT(iVal));
                }
            }
        }
    }
%}.

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

    "
     |b|
     b := ByteArray new:4.
     b unsignedLongAt:1 put:16rFFFFFFFF.
     (b longAt:1)    
    "

    "Modified: / 1.7.1996 / 21:11:28 / cg"
    "Modified: / 5.3.1998 / 12:06:28 / stefan"
!

longAt:index bigEndian:msb
    "return the 4-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     Depending on msb, the value is retrieved MSB-first or LSB-first.
     This may be worth a primitive."

    |w|

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

    "
     |b|
     b := ByteArray new:4.
     b unsignedLongAt:1 put:16rFFFFFFFF.
     (b longAt:1)    
    "

    "Modified: / 1.7.1996 / 21:11:33 / cg"
    "Created: / 5.3.1998 / 14:02:03 / stefan"
!

longAt:index put:value
    "set the 4-bytes starting at index from the signed Integer value.
     The index is a smalltalk index (i.e. 1-based).
     The value is stored in the machines natural byte order.
     This may be worth a primitive.

     This is the ST80 version of #signedDoubleWordAt:put:"

    |v|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
        char *cp;
        int sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;

            if ((idx+(sizeof(float)-1)) < sz) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(float)-1)) == 0) {
		    int __v;

    		    if (__isSmallInteger(value)) {
                        ((int *)cp)[0] = __intVal(value);
                        RETURN (value);
		    }
		    if (__v = __signedLongIntVal(value)) {
			((int *)cp)[0] = __v;
			RETURN (value);
		    }
                }
            }
        }
    }
%}.

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

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

    "Modified: / 1.7.1996 / 21:11:39 / cg"
    "Created: / 5.3.1998 / 10:57:18 / stefan"
!

longAt:byteIndex put:anInteger bigEndian:msb
    "store a signed long (32bit) integer.
     The index is a smalltalk index (i.e. 1-based).
     Same as #signedQuadWordAt:put: - for ST80 compatibility."

    |v|

    v := anInteger.
    anInteger < 0 ifTrue:[
        v := v + 16r100000000
    ].
    ^ self unsignedLongAt:byteIndex put:v bigEndian:msb

    "Created: / 9.5.1998 / 01:10:24 / cg"
    "Modified: / 9.5.1998 / 01:13:34 / cg"
!

signedDoubleWordAt:index
    "return the 4-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     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.
     The index is a smalltalk index (i.e. 1-based).
     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 index is a smalltalk index (i.e. 1-based).
     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.
     The index is a smalltalk index (i.e. 1-based).
     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"
!

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

    ^ self unsignedLongAt:index bigEndian:IsBigEndian

    "
     |b|

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

    "Created: / 5.3.1998 / 11:56:53 / stefan"
    "Modified: / 5.3.1998 / 14:58:48 / stefan"
!

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

    |val 
     ival "{ Class: SmallInteger }"
     i    "{ Class: SmallInteger }"
     b1   "{ Class: SmallInteger }"
     b2   "{ Class: SmallInteger }"
     b3   "{ Class: SmallInteger }"
     b4   "{ Class: SmallInteger }"|

    i := index.
    b1 := self at:i.
    b2 := self at:(i+1).
    b3 := self at:(i+2).
    b4 := self at:(i+3).

    msb ifTrue:[
        ival := b1.
        ival := (ival bitShift:8) + b2.
        ival := (ival bitShift:8) + b3.
        val := (ival * 256) + b4.
    ] ifFalse:[
        ival := b4.
        ival := (ival bitShift:8) + b3.
        ival := (ival bitShift:8) + b2.
        val := (ival * 256) + b1.
    ].
    ^ val

    "
     |b|

     b := ByteArray withAll:#(1 2 3 4).
     (b unsignedLongAt:1 bigEndian:true) printStringRadix:16.   
     (b unsignedLongAt:1 bigEndian:false) printStringRadix:16   
    "

    "Modified: / 21.1.1998 / 17:42:30 / cg"
    "Created: / 5.3.1998 / 11:46:05 / stefan"
!

unsignedLongAt:index put:value
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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 unsignedLongAt:index put:value bigEndian:IsBigEndian

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

    "Created: / 5.3.1998 / 11:57:44 / stefan"
    "Modified: / 5.3.1998 / 14:58:59 / stefan"
!

unsignedLongAt:index put:aNumber bigEndian:msb
    "set the 4-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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."

    |i "{ Class: SmallInteger }" |

    ((aNumber < 0) or:[aNumber > 16rFFFFFFFF]) ifTrue:[
        ^ self elementBoundsError
    ].

    i := index.
    msb ifTrue:[
        self at:i     put:(aNumber digitAt:4).
        self at:(i+1) put:(aNumber digitAt:3).
        self at:(i+2) put:(aNumber digitAt:2).
        self at:(i+3) put:(aNumber digitAt:1).
    ] ifFalse:[
        self at:i     put:(aNumber digitAt:1).
        self at:(i+1) put:(aNumber digitAt:2).
        self at:(i+2) put:(aNumber digitAt:3).
        self at:(i+3) put:(aNumber digitAt:4).
    ].
    ^ aNumber

    "
     |b|
     b := ByteArray new:8.
     b unsignedLongAt:1 put:16r04030201 bigEndian:true.
     (b unsignedLongAt:1 bigEndian:false) printStringRadix:16
    "

    "Modified: / 21.1.1998 / 17:43:34 / cg"
    "Created: / 5.3.1998 / 11:43:53 / stefan"
    "Modified: / 5.3.1998 / 11:47:30 / stefan"
! !

!UninterpretedBytes methodsFor:'accessing-shorts'!

shortAt:index
    "return the 2-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machines natural byte order.
     This may be worth a primitive.
     This is the ST80 equivalent of #signedWordAt:"

    ^ (self unsignedShortAt:index) signExtendedShortValue

    "
     |b|
     b := ByteArray new:2.
     b unsignedShortAt:1 put:16rFFFF.
     b shortAt:1  
    "

    "Modified: / 1.7.1996 / 21:14:38 / cg"
    "Created: / 5.3.1998 / 10:59:57 / stefan"
    "Modified: / 5.3.1998 / 23:39:38 / stefan"
!

shortAt:index bigEndian:msb
    "return the 2-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved MSB-first, if the msb-arg is true;
     LSB-first otherwise.
     This is the ST80 equivalent of #signedWordAt:"

    ^ (self unsignedShortAt:index bigEndian:msb) signExtendedShortValue

    "
     |b|
     b := ByteArray new:2.
     b unsignedShortAt:1 put:16rFFFF.
     b shortAt:1  
    "

    "Modified: / 1.7.1996 / 21:14:38 / cg"
    "Created: / 5.3.1998 / 23:41:21 / stefan"
!

shortAt:index put:value
    "set the 2-bytes starting at index from the signed Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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.
     This is the ST80 equivalent of #signedWordAt:put:"


    |v|

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

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

    "Modified: / 1.7.1996 / 21:12:07 / cg"
    "Created: / 5.3.1998 / 11:02:05 / stefan"
!

signedWordAt:index
    "return the 2-bytes starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     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 index is a smalltalk index (i.e. 1-based).
     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 index is a smalltalk index (i.e. 1-based).
     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.
     This is the ST80 equivalent of #signedWordAt:put:"


    |v|

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

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

    "Modified: / 1.7.1996 / 21:12:07 / cg"
    "Modified: / 5.3.1998 / 11:01:30 / stefan"
!

signedWordAt:index put:value MSB:msb
    "set the 2-bytes starting at index from the signed Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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"
!

unsignedShortAt:index
    "return the 2-bytes starting at index as an (unsigned) Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machines natural byte order
     Subclasses may redefine this for better performance.
     This is the ST80 equivalent of #wordAt:"


    ^ self unsignedShortAt:index bigEndian:IsBigEndian

    "Created: / 5.3.1998 / 11:38:25 / stefan"
    "Modified: / 5.3.1998 / 14:59:25 / stefan"
!

unsignedShortAt:index bigEndian:msb
    "return the 2-bytes starting at index as an (unsigned) Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved MSB-first (high 8 bits at lower index) if msb is true;
     LSB-first (i.e. low 8-bits at lower byte index) if its false)"

    |b1 "{ Class: SmallInteger }" 
     b2 "{ Class: SmallInteger }"|

    b1 := self at:index.
    b2 := self at:(index + 1).
    msb ifTrue:[
        ^ (b1 bitShift:8) + b2
    ].
    ^ (b2 bitShift:8) + b1

    "Modified: / 21.1.1998 / 17:46:07 / cg"
    "Created: / 5.3.1998 / 11:49:29 / stefan"
!

unsignedShortAt:index put:value
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     The stored value must be in the range 0 .. 16rFFFF. 
     The value is stored in the machines natural byteorder."

    ^ self unsignedShortAt:index put:value bigEndian:IsBigEndian

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

    "Created: / 5.3.1998 / 11:54:52 / stefan"
    "Modified: / 5.3.1998 / 14:59:38 / stefan"
!

unsignedShortAt:index put:value bigEndian:msb
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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"

    |b1 b2
     iVal "{ Class: SmallInteger }"|

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

    "
     |b|
     b := ByteArray new:8.
     b unsignedShortAt:1 put:16r0102 bigEndian:false.
     b unsignedShortAt:3 put:16r0304 bigEndian:false.
     b unsignedShortAt:5 put:16r0102 bigEndian:true.
     b unsignedShortAt:7 put:16r0304 bigEndian:true.
     b inspect  
    "

    "Modified: / 21.1.1998 / 17:48:15 / cg"
    "Modified: / 5.3.1998 / 11:52:28 / stefan"
!

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

    ^ self wordAt:index MSB:IsBigEndian

    "Modified: / 5.3.1998 / 14:59:51 / stefan"
!

wordAt:index MSB:msb
    "return the 2-bytes starting at index as an (unsigned) Integer.
     The index is a smalltalk index (i.e. 1-based).
     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:)"

    |b1 "{ Class: SmallInteger }" 
     b2 "{ Class: SmallInteger }"|

    b1 := self at:index.
    b2 := self at:(index + 1).
    msb ifTrue:[
        ^ (b1 bitShift:8) + b2
    ].
    ^ (b2 bitShift:8) + b1

    "Modified: / 21.1.1998 / 17:46:07 / cg"
!

wordAt:index put:value
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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:IsBigEndian

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

    "Modified: / 5.3.1998 / 15:00:03 / stefan"
!

wordAt:index put:value MSB:msb
    "set the 2-bytes starting at index from the (unsigned) Integer value.
     The index is a smalltalk index (i.e. 1-based).
     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:)"

    |b1 b2
     iVal "{ Class: SmallInteger }"|

    iVal := value.
    ((iVal < 0) or:[iVal > 16rFFFF]) ifTrue:[
        ^ self elementBoundsError
    ].
    msb ifTrue:[
        b1 := ((iVal bitShift:-8) bitAnd:16rFF).
        b2 := (iVal bitAnd:16rFF).
    ] ifFalse:[
        b1 := (iVal bitAnd:16rFF).
        b2 := ((iVal bitShift:-8) bitAnd:16rFF).
    ].
    self at:index   put:b1.
    self at:index+1 put:b2.
    ^ 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  
    "

    "Modified: / 21.1.1998 / 17:48:15 / cg"
!

wordAtWordIndex:index
    "return the unsigned short at index, anInteger. 
     Fetching in the machines natural byte order.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of word entries.
     (i.e. indices are 1, 2, ...)"

    ^ self wordAtWordIndex:index MSB:IsBigEndian

    "Created: / 21.1.1998 / 17:48:26 / cg"
    "Modified: / 5.3.1998 / 15:00:16 / stefan"
!

wordAtWordIndex:index MSB:msb
    "return the unsigned short at index, anInteger. 
     Fetching is MSB if msb is true, LSB otherwise.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of word entries.
     (i.e. indices are 1, 2, ...)"

    ^ self wordAt:(index - 1 * 2 + 1) MSB:msb

    "Created: / 21.1.1998 / 17:48:30 / cg"
!

wordAtWordIndex:index put:value
    "set the short at index, anInteger. 
     Storing in the machines natural byte order.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of word entries.
     (i.e. indices are 1, 2, ...)"

    ^ self wordAtWordIndex:index put:value MSB:IsBigEndian

    "Created: / 21.1.1998 / 17:48:34 / cg"
    "Modified: / 5.3.1998 / 15:00:27 / stefan"
!

wordAtWordIndex:index put:value MSB:msb
    "set the short at index, anInteger. 
     Storing is MSB if msb is true, LSB otherwise.
     Indices are 1-based and scaled as appropriate to allow
     accessing the memory as an array of word entries.
     (i.e. indices are 1, 2, ...)"

    ^ self wordAt:(index - 1 * 2 + 1) put:value MSB:msb

    "Created: / 21.1.1998 / 17:48:38 / cg"
! !

!UninterpretedBytes methodsFor:'accessing-strings'!

stringAt:index
    "return a string starting at index up to the 0-byte.
     The index is a smalltalk index (i.e. 1-based)."

    |stream i "{ Class: SmallInteger }" c|

    stream := WriteStream on:''.
    i := index.
    [(c := self basicAt:i) ~~ 0] whileTrue:[
        stream nextPut:(Character value:c).
        i := i + 1.
    ].
    ^ stream contents

    "Created: / 21.1.1998 / 17:44:50 / cg"
!

stringAt:index put:aString
    "copy aString to the externalBytes, starting at index up to
     (and including) the 0-byte.
     The index is a smalltalk index (i.e. 1-based)."

    |i "{ Class: SmallInteger }"|

    i := index.
    aString do:[:aChar |
        self basicAt:i put:aChar asciiValue.
        i := i + 1.
    ].
    self basicAt:i put:0.
    ^ aString

    "
     |bytes|

     bytes := ExternalBytes new:10.
     bytes stringAt:1 put:'hello'.
     1 to:bytes size do:[:i |
        Transcript showCR:(bytes at:i)
     ]
    "

    "Created: / 21.1.1998 / 17:45:02 / cg"
!

stringAt:index size:maxSize
    "return a string starting at index up to maxSize, or a 0-byte.
     The index is a smalltalk index (i.e. 1-based)."

    |stream c i "{ Class: SmallInteger }"|

    stream := WriteStream on:(String new:maxSize).
    i := index.
    [(i <= maxSize)
     and:[(c := self basicAt:i) ~~ 0]] whileTrue:[
        stream nextPut:(Character value:c).
        i := i + 1.
    ].
    ^ stream contents

    "Modified: / 21.1.1998 / 17:45:23 / cg"
!

zeroByteStringAt:index maximumSize:count
    "extract a zeroByte-delimited string, given initial index and
     maximum number of characters (bytes).
     The index is a smalltalk index (i.e. 1-based)."

    |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 methodsFor:'misc'!

swapLongAt:byteIndex 
    "swap the byteOrder of a long.
     The index is a smalltalk index (i.e. 1-based)."

    |t|

    t := self byteAt:byteIndex.
    self byteAt:byteIndex put:(self byteAt:(byteIndex + 3)).
    self byteAt:(byteIndex + 3) put:t.
    t := self byteAt:(byteIndex + 1).
    self byteAt:(byteIndex + 1) put:(self byteAt:(byteIndex + 2)).
    self byteAt:(byteIndex + 2) put:t

    "Created: / 3.4.1998 / 13:37:01 / cg"
! !

!UninterpretedBytes methodsFor:'queries'!

sizeInBytes
    "return the number of 8-bit bytes in the receiver.
     This is needed since subclasse may redefine #size (TwoByteString)"

    ^ super size

    "Created: / 5.3.1998 / 10:41:13 / stefan"
! !

!UninterpretedBytes class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/UninterpretedBytes.st,v 1.30 1998-05-18 12:20:27 cg Exp $'
! !
UninterpretedBytes initialize!