UninterpretedBytes.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:55:17 +0200
changeset 24417 03b083548da2
parent 24040 cbf03fb244e9
child 24450 8a439196334f
permissions -rw-r--r--
#REFACTORING by exept class: Smalltalk class changed: #recursiveInstallAutoloadedClassesFrom:rememberIn:maxLevels:noAutoload:packageTop:showSplashInLevels: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"{ Encoding: utf8 }"

"
 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:libbasic' }"

"{ NameSpace: Smalltalk }"

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 (__isByteArrayLike(o)) { \
	  *(pPtr) = (unsigned char *)__ByteArrayInstPtr(o)->ba_element; \
	  *(pSize) = __byteArraySize(o); \
	} else if (__qIsExternalBytesLike(o)) { \
	  OBJ __sz__ = __externalBytesSize(o); \
	  if (__isSmallInteger(__sz__)) { \
	    *(pSize) = __intVal(__sz__); \
	    *(pPtr) = (unsigned char *)(__externalBytesAddress(o)); \
	  } else { \
	    *(pSize) = 0; \
	    *(pPtr) = (unsigned char *)0; \
	  } \
	} else { \
		/* here we need to differ 32bit and 64bit */ \
        /* because on 32bit machines we need to take care about the alignment */ \
        /* but sadly, the same code is wrong for 64bit machines */ \
		if (__POINTER_SIZE__ == 8) {\
			*(pSize) /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(o))->c_ninstvars)); \
		  } else { \
	    if (__isFloatArray(o)) { \
		*(pSize) = sizeof(struct __FloatArray) - sizeof(float) + __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(o))->c_ninstvars)); \
	    } else { \
		if (__isDoubleArray(o)) { \
		    *(pSize) = sizeof(struct __DoubleArray) - sizeof(double) + __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(o))->c_ninstvars)); \
		} else { \
		    if (__isLongLongsOrSignedLongLongs(o)) { \
			*(pSize) = sizeof(struct __LongIntegerArray) - sizeof(__uint64__) + __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(o))->c_ninstvars)); \
		    } else { \
			*(pSize) /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(o))->c_ninstvars)); \
		    } \
		} \
	    } \
	    } \
	    *(pPtr) = (char *)(__InstPtr(self)) + *(pSize) /* nInstBytes */; \
	    *(pSize) = __qSize(self) - *(pSize) /* nInstBytes */; \
	} \
      } else { \
	*(pSize) = 0; \
	*(pPtr) = (unsigned 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)
	String    (knows that the bytes represent characters)
    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 did 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'!

initialize
    IsBigEndian := self isBigEndian.
! !

!UninterpretedBytes class methodsFor:'instance creation'!

from:aByteArray
    "return new instance which is a copy of aByteArray"

    |len bytes|

    len := aByteArray size.
    bytes := self new:len.
    bytes replaceBytesFrom:1 to:len with:aByteArray startingAt:1.
    ^ bytes

    "
      String from:#[40 41 42]
      String with:#[40 41 42 43 44 45 46 47 48 49 50] from:2 to:5
    "
!

fromHexString:aString
    "decode a byteArray from a hex string (as generated by hexPrintOn:).
     aString should not contain whitespace (only hex chars);
     see fromHexStringWithSeparators: for an alternative"

    | sz bytes s hi lo |

    sz := aString size.
    sz == 0 ifTrue:[^ self new].
    sz odd ifTrue:[ ConversionError raiseWith:aString errorString:'invalid hex string (odd size)' ].

    bytes := self new: sz // 2.
    s := aString readStream.
    1 to: sz // 2 do: [ :idx |
        hi := s next digitValue.
        lo := s next digitValue.
        bytes at:idx put: ((hi bitShift:4) bitOr: lo)
    ].
    ^ bytes

    "
     ByteArray fromHexString:'1234FEFF'
     ExternalBytes fromHexString:'1234FEFF'
    "
    "
     |s|
     s := String streamContents:[:s | #[1 2 3] hexPrintOn:s].
     ByteArray fromHexString:s
    "
    "
     Time millisecondsToRun:[
        1000000 timesRepeat:[ ByteArray fromHexString:'1234FEFF1234FEFF1234FEFF1234FEFF' ]
     ].
    "

    "Modified (comment): / 28-08-2013 / 20:40:04 / cg"
    "Modified (comment): / 22-03-2019 / 12:27:13 / Claus Gittinger"
!

fromHexStringWithSeparators:aString
    "read a bytearray from a printed string representation, where
     individual bytes are encoded as two hex digits, optionally separated by whiteSpace.
     See also fromHexString:, which does something similar, but does not allow for spaces"

    ^ self streamContents:[:outStream |
	|inStream h|

	inStream := aString readStream.

	[
	    inStream skipSeparators.
	    inStream atEnd
	] whileFalse:[
	    h := inStream next:2.
	    outStream nextPut:(Integer readFrom:h base:16).
	].
    ].

    "
     ByteArray fromHexString:'1234FEFF'
     ByteArray fromHexStringWithSeparators:'   12  34 FE FF'
    "
!

fromPackedString:aString
    "ST-80 compatibility: decode a byteArray from a packed string in which
     6bits are encoded per character. The argument, aString must be a multiple
     of 4 in size (since 24 is the lcm of 6 and 8).
     Every 6 bit packet is encoded as a character in 32..95.
     Characters below 32 are ignored (so line breaks can be inserted at any place).
     An addition final byte defines how many bytes of the last triple are valid.
     This is somewhat like the radix-encoding used in good old PDP11 times ;-)
     ST-80 uses this encoding for Images ...
     This is a base64 encoding, very similar (but not equal) to the algorithm used in RFC1421.
     PS: It took a while to figure that one out ...
     PPS: I don't like it ;-)"

    |index    "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     stop     "{ Class: SmallInteger }"
     sixBits  "{ Class: SmallInteger }"
     n        "{ Class: SmallInteger }"
     sz       "{ Class: SmallInteger }"
     last bytes|

    sz := aString size.
    sz == 0 ifTrue:[^ self new].
    sz := sz - (aString count:[:ch | ch codePoint < 32]).

    stop := sz // 4 * 3.
    "the size modulo 3 is encoded in the last character, if it is in the
     range 97 .. otherwise, its exact."

    last := aString last codePoint.
    last > 96 ifTrue:[
	stop := stop - 3 + (last - 96)
    ].
    bytes := self new:stop.

    index := 1. dstIndex := 1.
    [dstIndex <= stop] whileTrue:[
	"/ take 4 characters ...
	"/ allow a line break before each group of 4
	sixBits := (aString at:index) codePoint.
	[sixBits < 32] whileTrue:[
	    index := index + 1.
	    sixBits := (aString at:index) codePoint.
	].
	sixBits := sixBits bitAnd:16r3F.
	n := sixBits.

	"/ self assert:(aString at:index+1) codePoint >= 32.
	sixBits := (aString at:index+1) codePoint bitAnd:16r3F.
	n := (n bitShift:6) + sixBits.

	"/ self assert:(aString at:index+2) codePoint >= 32.
	sixBits := (aString at:index+2) codePoint bitAnd:16r3F.
	n := (n bitShift:6) + sixBits.

	"/ self assert:(aString at:index+3) codePoint >= 32.
	sixBits := (aString at:index+3) codePoint bitAnd:16r3F.
	n := (n bitShift:6) + sixBits.

	index := index + 4.

	"/ now have 24 bits in n

	bytes at:dstIndex put:(n bitShift:-16).

	dstIndex < stop ifTrue:[
	    bytes at:dstIndex+1 put:((n bitShift:-8) bitAnd:16rFF).
	    dstIndex+2 <= stop ifTrue:[
		bytes at:dstIndex+2 put:(n bitAnd:16rFF).
	    ]
	].
	dstIndex := dstIndex + 3.
    ].
    ^ bytes

    "
     ByteArray fromPackedString:(#[1 1 1 1] asPackedString)
     ByteArray fromPackedString:(#[1 1 1 1 1] asPackedString)
     ByteArray fromPackedString:(#[1 1 1 1 1 1] asPackedString)
     ByteArray fromPackedString:(#[1 1 1 1 1 1 1] asPackedString)
     ByteArray fromPackedString:(#[1 1 1 1 1 1 1 1] asPackedString)
     ByteArray fromPackedString:((ByteArray new:256) asPackedString)
     ByteArray fromPackedString:((ByteArray new:128) asPackedString)
     ByteArray fromPackedString:((ByteArray new:129) asPackedString)
     ByteArray fromPackedString:((ByteArray new:130) asPackedString)
     ByteArray fromPackedString:((ByteArray new:131) asPackedString)
     ByteArray fromPackedString:((ByteArray new:132) asPackedString)
     ByteArray fromPackedString:((ByteArray new:64) asPackedString)

     0 to:256 do:[:l |
	|orig copy|

	0 to:255 do:[:fill |
	    orig := ByteArray new:l withAll:fill.
	    copy := ByteArray fromPackedString:(orig asPackedString).
	    self assert:(orig = copy).
	 ]
     ]
    "

    "Modified: / 6.3.1997 / 15:28:52 / cg"
    "Modified: / 18.12.1997 / 17:17:11 / stefan"
!

uninitializedNew:anInteger
    "return a new instance of the receiver with uninitialized
     (i.e. undefined) contents. The indexed elements have any random
     value. However, any named instance variables are still nilled.
     For use, when contents will be set anyway shortly after - this
     is a bit faster than the regular basicNew:, which clears the bytes.
     Of course, it only makes a difference for very big ByteArrays, such
     as used for images/bitmaps.

     Notice: if you want to port code using uninitializedNew: to another
     smalltalk, you have to add an 'uninitializedNew: -> basicNew:'-calling
     method to the ByteArray class of the other smalltalk."

%{  /* NOCONTEXT */
    OBJ newobj;
    INT instsize, nInstVars, nindexedinstvars;
    REGISTER OBJ *op;

    if (__isSmallInteger(anInteger)) {
	nindexedinstvars = __intVal(anInteger);
	if (nindexedinstvars >= 0) {
	    if (self == ByteArray) {
		/*
		 * the most common case
		 */
		instsize = OHDR_SIZE + nindexedinstvars;
		if (__CanDoQuickNew(instsize)) {        /* OBJECT ALLOCATION */
		    __qCheckedNew(newobj, instsize);
		    __InstPtr(newobj)->o_class = self;
		    __qSTORE(newobj, self);
		    RETURN (newobj );
		}
	    } else {
		/*
		 * Take care for subclasses like TwoByteString
		 */
		switch (__smallIntegerVal(__ClassInstPtr(self)->c_flags) & ARRAYMASK) {
		case BYTEARRAY:
		    break;

		case WORDARRAY:
		case SWORDARRAY:
		    nindexedinstvars *= 2;
		    break;

		case LONGARRAY:
		case SLONGARRAY:
		    nindexedinstvars *= 4;
		    break;

		default:
		    /* don't know about this array type, delegate to super */
		    goto out;
		}
	    }
	    nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);
	    instsize = OHDR_SIZE + __OBJS2BYTES__(nInstVars) + nindexedinstvars;
	    __PROTECT_CONTEXT__
	    __qNew(newobj, instsize);   /* OBJECT ALLOCATION */
	    __UNPROTECT_CONTEXT__
	    if (newobj != nil) {
		__InstPtr(newobj)->o_class = self;
		__qSTORE(newobj, self);
		if (nInstVars) {
		    /*
		     * still have to nil out named instvars ...
		     */
#if defined(memset4) && defined(FAST_OBJECT_MEMSET4)
		    memset4(__InstPtr(newobj)->i_instvars, nil, nInstVars);
#else
# if defined(FAST_MEMSET) && !defined(NEGATIVE_ADDRESSES)
		    /*
		     * knowing that nil is 0
		     */
		    memset(__InstPtr(newobj)->i_instvars, 0, instsize - OHDR_SIZE);
# else
		    op = __InstPtr(newobj)->i_instvars;
		    while (nInstVars--)
			*op++ = nil;
# endif
#endif
		}
		RETURN ( newobj );
	    }
	}
    }
out:;
%}.
    ^ self basicNew:anInteger
!

with:aByteArray from:start to:stop
    "return new instance with a copy of aByteArray
     beginning at index start up to and including index stop"

    |len bytes|

    len := stop-start+1.
    bytes := self new:len.
    bytes replaceBytesFrom:1 to:len with:aByteArray startingAt:start.
    ^ bytes

    "
      String with:#[40 41 42 43 44 45 46 47 48 49 50] from:2 to:5
    "
! !

!UninterpretedBytes class methodsFor:'Compatibility-Squeak'!

readHexFrom:aString
    "same as fromHexString: for squeak/Pharo compatibility"

    ^ self fromHexString:aString

    "
     (ByteArray readHexFrom: 'C3A1C3A5C3A6C3B1C386C2A5C3BC')
    "

    "Created: / 18-06-2017 / 18:01:18 / cg"
! !

!UninterpretedBytes class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned for UninterpretedBytes here; false for subclasses.
     Abstract subclasses must redefine this again."

    ^ self == UninterpretedBytes
!

isBigEndian
    "return true, if words/shorts store the most-significant
     byte first (MSB), false if least-sign.-first (LSB).
     Returns 
        false for vax, intel, 
        true for m68k, m88k, power, sparc.

     Notice: UninterpretedBytes isBigEndian
             this is inlined both by stc and the jit compiler"

%{  /* NOCONTEXT */

#if defined(__MSBFIRST__)
    RETURN (true);
#else
# if defined(__LSBFIRST__)
    RETURN (false);
# else
    /*
     * I don't 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);
# endif
#endif
%}.
    ^ false     "/ an arbitrary default

    "
     UninterpretedBytes isBigEndian
    "

    "Modified (comment): / 17-03-2019 / 13:02:29 / Claus Gittinger"
!

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:'Compatibility'!

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 machine's natural byte order."

    ^ self unsignedInt32At:index MSB:IsBigEndian

    "
     |b|

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

    "Modified: / 05-03-1998 / 14:57:35 / stefan"
    "Modified (comment): / 04-08-2017 / 11:15:29 / cg"
!

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

    ^ self unsignedInt32At:index MSB:msb

    "
     |b|

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

doubleWordAt:byteIndex put:anInteger
    "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 machine's natural byte order."

   ^ self unsignedInt32At:byteIndex put:anInteger MSB:IsBigEndian

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

    "Modified: / 05-03-1998 / 14:57:48 / stefan"
    "Modified (comment): / 04-08-2017 / 11:15:38 / cg"
!

doubleWordAt:byteIndex put:anInteger 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."

   ^ self unsignedInt32At:byteIndex put:anInteger MSB:msb

    "
     |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:int32Index
    "return the unsigned long (int32) at index, anInteger.
     Fetching in the machine's 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:int32Index MSB:IsBigEndian

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

doubleWordAtDoubleWordIndex:int32Index MSB:msb
    "return the unsigned long (int32) 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 unsignedInt32At:((int32Index - 1) * 4 + 1) MSB:msb

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

doubleWordAtDoubleWordIndex:int32Index put:anInteger
    "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:int32Index put:anInteger MSB:IsBigEndian

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

doubleWordAtDoubleWordIndex:int32Index put:anInteger 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 unsignedInt32At:((int32Index - 1) * 4 + 1) put:anInteger MSB:msb

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

int16At:byteIndex
    "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 machine's natural byte order.
     This may be worth a primitive."

    ^ self signedInt16At:byteIndex

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

    "Modified: / 01-07-1996 / 21:14:38 / cg"
    "Modified (comment): / 04-08-2017 / 11:15:48 / cg"
!

int16At:byteIndex 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 in the machines natural byte order.
     This may be worth a primitive."

    ^ self signedInt16At:byteIndex MSB:msb

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

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

int16At:index put:anInteger
    "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 machine's natural byteorder"

    ^ self signedInt16At:index put:anInteger MSB:IsBigEndian

    "
     |b|
     b := ByteArray new:4.
     b shortAt:1 put:1 bigEndian:true.
     b shortAt:3 put:1 bigEndian:false.
     b inspect
    "

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

int16At:index put:anInteger MSB:bigEndian
    "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 byteorder given by bigEndian.
     This may be worth a primitive."


    ^ self signedInt16At:index put:anInteger MSB:bigEndian

    "
     |b|
     b := ByteArray new:4.
     b shortAt:1 put:1 bigEndian:true.
     b shortAt:3 put:1 bigEndian:false.
     b inspect
    "

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

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 machine's natural byte order,
     therefore, this should only be used for byte-data which is
     only used inside this machine.
     To setup data packets which are to be sent to other machines,
     or stored into a file, always use longAt:MSB: and specify
     a definite byteOrder."

    ^ self signedInt32At:index

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

    "Modified: / 01-07-1996 / 21:11:28 / cg"
    "Modified: / 05-03-1998 / 12:06:28 / stefan"
    "Modified (comment): / 04-08-2017 / 11:15:58 / cg"
!

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

    ^ self signedInt32At:index MSB:msb

    "
     |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 machine's natural byte order."

    ^ self signedInt32At:index put:value MSB:IsBigEndian

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

    ^ self signedInt32At:byteIndex put:anInteger MSB:msb

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

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 machine's natural byte order.
     This may be worth a primitive."

    ^ self signedInt64At:index MSB:IsBigEndian

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

    "Modified: / 01-07-1996 / 21:11:28 / cg"
    "Created: / 05-03-1998 / 14:40:05 / stefan"
    "Modified (comment): / 04-08-2017 / 11:16:06 / cg"
!

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

    ^ self signedInt64At:index MSB:msb

    "
     |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).
     The value is stored in the machine's natural byte order.
     Same as #signedQuadWordAt:put: - for ST80 compatibility."

    ^ self signedInt64At:byteIndex put:anInteger MSB:IsBigEndian

    "Modified (comment): / 04-08-2017 / 11:16:36 / 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."

    ^ self signedInt64At:byteIndex put:anInteger MSB: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."

   ^ self unsignedInt64At:index MSB:msb

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

    ^ self unsignedInt64At:index put:anInteger MSB:msb

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

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 machine's natural byte order.
     This may be worth a primitive.
     This is the ST80 equivalent of #signedWordAt:"

    ^ self signedInt16At:index MSB:IsBigEndian

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

    "Modified: / 01-07-1996 / 21:14:38 / cg"
    "Created: / 05-03-1998 / 10:59:57 / stefan"
    "Modified: / 05-03-1998 / 23:39:38 / stefan"
    "Modified (comment): / 04-08-2017 / 11:16:20 / cg"
!

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 signedInt16At:index MSB:msb

    "
     |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 machine's natural byteorder.
     This may be worth a primitive.
     This is the ST80 equivalent of #signedWordAt:put:"

    ^ self signedInt16At:index put:value MSB:IsBigEndian

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

    "Modified: / 01-07-1996 / 21:12:07 / cg"
    "Created: / 05-03-1998 / 11:02:05 / stefan"
    "Modified (comment): / 04-08-2017 / 11:16:46 / cg"
!

shortAt:index put:value bigEndian:bigEndian
    "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 byteorder given by bigEndian.
     This may be worth a primitive."

    ^ self signedInt16At:index put:value MSB:IsBigEndian

    "
     |b|
     b := ByteArray new:4.
     b shortAt:1 put:1 bigEndian:true.
     b shortAt:3 put:1 bigEndian:false.
     b inspect
    "

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

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 machine's natural byte order.
     This may be worth a primitive."

    ^ self signedInt32At:index MSB:IsBigEndian

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

    "Modified: / 01-07-1996 / 21:11:28 / cg"
    "Modified (comment): / 04-08-2017 / 11:16:52 / 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).
     The value is retrieved MSB-first, if the msb-arg is true;
     LSB-first otherwise."

    ^ self signedInt32At:index MSB:msb

    "
     |b|

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

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 machine's natural byte order.
     This may be worth a primitive."

    ^ self signedInt32At:index put:value MSB:IsBigEndian

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

    "Modified: / 01-07-1996 / 21:11:39 / cg"
    "Modified (comment): / 04-08-2017 / 11:16:56 / 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."

    ^ self signedInt32At:index put:value MSB:msb

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

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

signedLongAt: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 machine's natural byte order."

    ^ self signedInt32At:index

    "
     |b|
     b := ByteArray new:4.
     b unsignedLongAt:1 put:16rFFFFFFFF.
     b signedLongAt:1
    "

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

signedLongAt:index put:newValue
    "store a 4-bytes signed value starting at index.
     The index is a smalltalk index (i.e. 1-based).
     The value is in the machine's natural byte order."

    ^ self signedInt32At:index put:newValue

    "
     |b|
     b := ByteArray new:4.
     b signedLongAt:1 put:-1.
     b unsignedLongAt:1
    "

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

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 machine's natural byte order.
     This may be worth a primitive."

    ^ (self unsignedInt16At:index MSB:IsBigEndian) signExtendedShortValue

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

    "Modified: / 01-07-1996 / 21:14:38 / cg"
    "Modified (comment): / 04-08-2017 / 11:17:02 / 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 unsignedInt16At: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:byteIndex put:anInteger
    "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 machine's natural byteorder."

    ^ self signedInt16At:byteIndex put:anInteger MSB:IsBigEndian

    "
     |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:byteIndex put:anInteger 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."

    ^ self signedInt16At:byteIndex put:anInteger MSB:msb

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

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 machine's natural byte order.
     Subclasses may redefine this for better performance.
     Same as doubleWordAt: for protocol completeness"

    ^ self unsignedInt32At:index MSB: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.
     Same as doubleWordAt:MSB: for protocol completeness"

    ^ self unsignedInt32At:index MSB:msb

    "
     |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 machine's natural byte order.
     Subclasses may redefine this for better performance.
     Same as doubleWordAt:put: for protocol completeness"

    ^ self unsignedInt32At:index put:value MSB:IsBigEndian

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

    "Created: / 05-03-1998 / 11:57:44 / stefan"
    "Modified: / 05-03-1998 / 14:58:59 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:11 / cg"
!

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.
     Same as doubleWordAt:put:MSB: for protocol completeness"

    ^ self unsignedInt32At:index put:aNumber MSB:msb

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

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

    ^ self unsignedInt64At:index MSB:msb

    "
     |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 the machine's natural byte order."

    ^ self unsignedInt64At:index put:anInteger MSB:IsBigEndian

    "Created: / 05-03-1998 / 14:44:00 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:23 / cg"
!

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

    ^ self unsignedInt64At:index put:anInteger MSB:msb

    "
     |b|
     b := ByteArray new:8.
     b unsignedLongLongAt:1 put:16r0807060504030201 bigEndian:false.
     b inspect
    "

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

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 machine's natural byte order
     Subclasses may redefine this for better performance.
     This is the ST80 equivalent of #wordAt:"


    ^ self unsignedInt16At:index MSB:IsBigEndian

    "Created: / 05-03-1998 / 11:38:25 / stefan"
    "Modified: / 05-03-1998 / 14:59:25 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:28 / cg"
!

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 it's false)"

    ^ self unsignedInt16At:index MSB:msb

    "Modified: / 21-01-1998 / 17:46:07 / cg"
    "Created: / 05-03-1998 / 11:49:29 / stefan"
    "Modified (comment): / 13-02-2017 / 20:34:05 / cg"
!

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 machine's natural byteorder."

    ^ self unsignedInt16At:index put:value

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

    "Created: / 05-03-1998 / 11:54:52 / stefan"
    "Modified: / 05-03-1998 / 14:59:38 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:31 / cg"
!

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"

    ^ self unsignedInt16At:index put:value MSB:msb

    "
     |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 machine's natural byte order
     Subclasses may redefine this for better performance."

    ^ self unsignedInt16At:index MSB:IsBigEndian

    "Modified: / 05-03-1998 / 14:59:51 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:35 / cg"
!

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 it's false.
     Notice:
	the index is a byte index; thus, this allows for unaligned access to
	words on any boundary.
     Question: should it be retrieve signed values ? (see ByteArray>>signedWordAt:)"

    ^ self unsignedInt16At:index MSB:msb

    "Modified (comment): / 13-02-2017 / 20:34:09 / 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 machine's natural byteorder.
     Question: should it accept signed values ? (see ByteArray>>signedWordAt:put:)"

    ^ self unsignedInt16At:index put:value MSB:IsBigEndian

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

    "Modified: / 05-03-1998 / 15:00:03 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:39 / cg"
!

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:)"

    ^ self unsignedInt16At:index put:value MSB:msb

    "
     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:int16Index
    "return the unsigned short (uint16) at index, anInteger.
     Fetching in the machine's 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 unsignedInt16At:int16Index MSB:IsBigEndian

    "Created: / 21-01-1998 / 17:48:26 / cg"
    "Modified: / 05-03-1998 / 15:00:16 / stefan"
    "Modified (comment): / 04-08-2017 / 11:17:43 / cg"
!

wordAtWordIndex:int16Index MSB:msb
    "return the unsigned short (uint16) 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 unsignedInt16At:((int16Index - 1) * 2 + 1) MSB:msb

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

wordAtWordIndex:int16Index put:anInteger
    "set the unsigned short (uint16) at index, anInteger.
     Storing in the machine's 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 unsignedInt16At:int16Index put:anInteger MSB:IsBigEndian

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

wordAtWordIndex:int16Index put:anInteger 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 unsignedInt16At:((int16Index - 1) * 2 + 1) put:anInteger MSB:msb

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

!UninterpretedBytes methodsFor:'Compatibility-Squeak'!

copyFromByteArray:aByteArray
    "copy as much as possible from aByteArray"

    self replaceBytesFrom:1 to:(self size min:aByteArray size) with:aByteArray startingAt:1
! !

!UninterpretedBytes methodsFor:'Compatibility-V''Age'!

uint32At:zeroBasedIndex
    "return the 4-bytes starting at index as (unsigned) Integer.
     WARNING: The index is a C index (i.e. 0-based).
     The value is retrieved in the machine's natural byte order.
     Similar to unsignedInt32At:, except for the index base"

    ^ self unsignedInt32At:zeroBasedIndex+1

    "
     |b|

     b := ByteArray withAll:#(0 0 0 0).
     b uint32At:0 put:16r12345678.
     b uint32At:0.
     b
    "
!

uint32At:zeroBasedIndex put:anInteger
    "set the 4-bytes starting at index to the value given by (unsigned) Integer.
     WARNING: The index is a C index (i.e. 0-based).
     The value is stored in the machine's natural byte order.
     Similar to unsignedInt32At:put:, except for the index base"

    ^ self unsignedInt32At:zeroBasedIndex+1 put:anInteger

    "
     |b|

     b := ByteArray withAll:#(0 0 0 0).
     b uint32At:0 put:16r12345678.
     b
    "
! !

!UninterpretedBytes methodsFor:'accessing-128bit ints'!

signedInt128At:index MSB:msb
    "return the 16-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 unsignedInt128At:index MSB:msb.
    (w > (16r7FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)) ifTrue:[
	^ w - (16r100000000000000000000000000000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:16.
     b unsignedInt128At:1 put:16rFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF MSB:true.
     (b signedInt128At:1 MSB:true)
    "

    "Created: / 04-08-2017 / 11:27:31 / cg"
!

signedInt128At:byteIndex put:anInteger MSB:msb
    "store a signed 128bit integer.
     The index is a smalltalk index (i.e. 1-based)."

    |v|

    v := anInteger.
    anInteger < 0 ifTrue:[
	v := v + 16r100000000000000000000000000000000
    ].
    self unsignedInt128At:byteIndex put:v MSB:msb.
    ^ anInteger

    "
     |b|
     b := ByteArray new:16.
     b signedInt128At:1 put:-1 MSB:true.
     (b unsignedInt128At:1 MSB:true)
    "

    "Created: / 04-08-2017 / 11:08:59 / cg"
!

unsignedInt128At:byteIndex MSB:msb
    "return the 16-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:16.
    msb ifTrue:[
	bIdx := byteIndex + 15.
	delta := -1
    ] ifFalse:[
	bIdx := byteIndex.
	delta := 1
    ].
    1 to:16 do:[:i |
	l digitAt:i put:(self byteAt:bIdx).
	bIdx := bIdx + delta
    ].
    ^ l compressed

    "
     |b|

     b := ByteArray withAll:#(1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16).
     (b unsignedInt128At:1 MSB:false) printStringRadix:16
    "

    "Created: / 04-08-2017 / 11:12:22 / cg"
!

unsignedInt128At:byteIndex put:anInteger MSB:msb
    "set the 18-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 16rFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF.
     Depending on msb, the value is stored MSB-first or LSB-first."

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

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

    msb ifTrue:[
	bIdx := byteIndex + 15.
	delta := -1
    ] ifFalse:[
	bIdx := byteIndex.
	delta := 1
    ].
    1 to:16 do:[:i |
	self byteAt:bIdx put:(anInteger digitAt:i).
	bIdx := bIdx + delta.
    ].
    ^ anInteger

    "
     |b|
     b := ByteArray new:16.
     b unsignedInt128At:1 put:16r100F0E0D0C0B0A090807060504030201 MSB:false.
     b inspect
    "

    "Created: / 04-08-2017 / 11:11:02 / cg"
! !

!UninterpretedBytes methodsFor:'accessing-arbitrary-long ints'!

nativeIntAt:index
    "return the 4- or 8-bytes (depending on the native integer/pointer size)
     starting at index as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machine's natural byte order,
     therefore, this should only be used for byte-data which is
     only used inside this machine."

    |w|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
	unsigned 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;
#if defined(__i386__)
		/*
		 * aligned or not, we don't care (i386 can do both)
		 */
		{
		    INT iVal = ((INT *)cp)[0];

		    RETURN (__MKINT(iVal));
		}
#else
		/*
		 * aligned
		 */
		if (((INT)cp & (sizeof(INT)-1)) == 0) {
		    INT iVal = ((INT *)cp)[0];

		    RETURN (__MKINT(iVal));
		}
#endif
	    }
	}
    }
%}.
    SmallInteger maxBytes == 8 ifTrue:[
	^ self signedInt64At:index
    ].
    ^ self signedInt32At:index

    "
     |b|
     b := ByteArray new:8.
     b nativeIntAt:1 put:SmallInteger maxVal.
     b nativeIntAt:1
    "

    "Modified (comment): / 04-08-2017 / 11:18:01 / cg"
!

nativeIntAt:index put:value
    "set the 4- or 8-bytes (depending on INT-/pointer size) starting at index from the signed Integer value.
     The index is a smalltalk index (i.e. 1-based).
     The value is stored in the machine's natural byte order."

%{  /* NOCONTEXT */
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(index)) {
	unsigned 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 __v;

		    if (__isSmallInteger(value)) {
			// how about a range check?
			((INT *)cp)[0] = (INT)(__intVal(value));
			RETURN (value);
		    }
		    if ((__v = __signedLongIntVal(value)) != 0) {
			// how about a range check?
			((INT *)cp)[0] = (INT)(__v);
			RETURN (value);
		    }
		}
	    }
	}
    }
%}.
    SmallInteger maxBytes == 8 ifTrue:[
	^ self signedInt64At:index put:value MSB:IsBigEndian
    ].
    ^ self signedInt32At:index put:value MSB:IsBigEndian

    "
     |b|
     b := ByteArray new:8.
     b nativeIntAt:1 put:SmallInteger maxVal.
     (b nativeIntAt:1)
    "
!

signedIntegerAt:index length:len bigEndian:bigEndian
    "return the n-byte signed integer starting at index.
     With n=1, this returns the single signed byte's value,
     n=2, a signed short, n=4 a signed int etc.
     Useful to extract arbitrary long integers"

    |val highByte
     iIndex "{ Class:SmallInteger }"
     last "{ Class:SmallInteger }"|

    iIndex := index.
    last := iIndex + len - 1.

    val := 0.
    bigEndian ifTrue:[
	highByte := self at:iIndex.
	iIndex to:last do:[:i |
	    val := (val<<8) + (self byteAt:i)
	]
    ] ifFalse:[
	highByte := self at:last.
	last to:iIndex by:-1 do:[:i |
	    val := (val<<8) + (self byteAt:i)
	]
    ].
    (highByte bitTest:16r80) ifTrue:[
	^ val - (1 bitShift:(len*8))
    ].
    ^ val

    "
     |b|
     b := #[ 16r01 16rFF 16r00 16r04 16r05 ].
     (b signedIntegerAt:2 length:2 bigEndian:false). ' -> 255 (00FF) '.
     (b signedIntegerAt:2 length:2 bigEndian:true).  ' -> -256 (FF00) '.

     b := #[ 16r01 16r00 16rFF 16r04 16r05 ].
     (b signedIntegerAt:2 length:2 bigEndian:false). ' -> -256 (FF00) '.
     (b signedIntegerAt:2 length:2 bigEndian:true).  ' -> 255 (00FF) '.

     b := #[ 16r01 16r7F 16r00 16r04 16r05 ].
     (b signedIntegerAt:2 length:2 bigEndian:false). ' -> 127 (007F) '.
     (b signedIntegerAt:2 length:2 bigEndian:true).  ' -> 32512 (7F00) '.
    "

    "
     |b|
     b := #[ 16r01 16r02 16r03 16r04 16r05 ].
     (b signedIntegerAt:2 length:4 bigEndian:false).
     (b signedIntegerAt:2 length:4 bigEndian:true).

     b := #[ 16r01 16r82 16r03 16r04 16r05 ].
     (b signedIntegerAt:2 length:4 bigEndian:false).
     (b signedIntegerAt:2 length:4 bigEndian:true).

     b := #[ 16r01 16r82 16r03 16r04 16r85 ].
     (b signedIntegerAt:2 length:4 bigEndian:false).
     (b signedIntegerAt:2 length:4 bigEndian:true).
    "
!

unsignedIntegerAt:index length:len bigEndian:bigEndian
    "return the n-byte unsigned integer starting at index.
     With n=1, this returns the single byte's value,
     n=2, an unsigned short, n=4 an unsigned int32 etc.
     Useful to extract arbitrary long integers"

    |val
     iIndex "{ Class:SmallInteger }"
     last "{ Class:SmallInteger }"|

    iIndex := index.
    last := iIndex + len - 1.

    val := 0.
    bigEndian ifTrue:[
	iIndex to:last do:[:i |
	    val := (val<<8) + (self byteAt:i)
	]
    ] ifFalse:[
	last to:iIndex by:-1 do:[:i |
	    val := (val<<8) + (self byteAt:i)
	]
    ].
    ^ val

    "
     |b|
     b := #[ 16r01 16r02 16r03 16r04 16r05 ].
     (b unsignedIntegerAt:2 length:4 bigEndian:false).
     (b unsignedIntegerAt:2 length:4 bigEndian:true).
    "

    "Modified (comment): / 04-08-2017 / 11:14:21 / cg"
!

unsignedIntegerAt:index put:newValue length:len bigEndian:bigEndian
    "store the n-byte unsigned integer starting at index.
     With n=1, this stores a single byte's value,
     n=2, an unsigned short, n=4 an unsigned int32 etc.
     Useful to replace arbitrary long integers"

    |val
     iIndex "{ Class:SmallInteger }"
     last "{ Class:SmallInteger }"|

    iIndex := index.
    last := iIndex + len - 1.

    val := newValue.
    bigEndian ifTrue:[
	iIndex to:last do:[:i |
	    self byteAt:i put:(val bitAnd:16rFF).
	    val := val bitShift:-8.
	]
    ] ifFalse:[
	last to:iIndex by:-1 do:[:i |
	    self byteAt:i put:(val bitAnd:16rFF).
	    val := val bitShift:-8.
	]
    ].

    "
     |b|
     b := #[ 16r01 16r02 16r03 16r04 16r05 ] copy.
     (b unsignedIntegerAt:2 put:16r11223344 length:3 bigEndian:false). b.
     (b unsignedIntegerAt:2 put:16r11223344 length:3 bigEndian:true). b.
    "

    "Modified (comment): / 04-08-2017 / 11:14:32 / cg"
! !

!UninterpretedBytes methodsFor:'accessing-bytes'!

bcdByteAt:index
    "return the bcd-value for a byte at index in the range 0..99.
     BCD treats nibbles (4-bit) as an encoded decimal number's digits
     (i.e. the value n is encoded as: ((n // 10) * 16) + (n \\ 10)"

    ^ (self byteAt:index) decodeFromBCD

    "
     #[ 16r55 ] bcdByteAt:1
     #[ 16r99 ] bcdByteAt:1
     #[ 16rAA ] bcdByteAt:1
    "

    "Modified (comment): / 26-09-2011 / 11:57:33 / cg"
!

bcdByteAt:index put:aNumber
    "set the byte at index as bcd-value in the range 0..99.
     BCD treats nibbles (4-bit) as an encoded decimal number's digits
     (i.e. the value n is encoded as: ((n // 10) * 16) + (n \\ 10)"

    (aNumber between:0 and:99) ifFalse:[
	self elementBoundsError:aNumber.
    ].
    ^ self byteAt:index put:aNumber encodeAsBCD

    "
     (((ByteArray new:1) bcdByteAt:1 put:55; yourself) at:1) hexPrintString
     (((ByteArray new:1) bcdByteAt:1 put:99; yourself) at:1) hexPrintString
     (((ByteArray new:1) bcdByteAt:1 put:100; yourself) at:1) hexPrintString
     (((ByteArray new:1) bcdByteAt:1 put:-1; yourself) at:1) hexPrintString
    "

    "Modified (comment): / 26-09-2011 / 11:57:36 / cg"
    "Modified: / 07-02-2017 / 20:12:04 / stefan"
!

byteAt:byteIndex
    "return the byte at byteIndex as an unsigned 8 bit value in the range 0..255.
     The index is a smalltalk index (i.e. 1-based)."

%{ /* NOCONTEXT */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if (idx < sz) {
		unsigned char ch = cp[idx] & 0xFF;
		RETURN (__mkSmallInteger( ch ));
	    }
	}
    }
%}.

    ^ self at:byteIndex

    "
     |b|
     b := String new:3.
     b byteAt:1 put:16rFF.
     b byteAt:2 put:16r7F.
     b byteAt:3 put:16r80.
     b byteAt:1.
     b byteAt:2.
     b byteAt:3.

     |b|
     b := ExternalBytes new:3.
     b byteAt:1 put:16rFF.
     b byteAt:2 put:16r7F.
     b byteAt:3 put:16r80.
     b byteAt:1.
     b byteAt:2.
     b byteAt:3.
    "

    "Modified: / 01-07-1996 / 21:13:53 / cg"
    "Modified (comment): / 26-09-2011 / 11:57:14 / cg"
    "Modified (comment): / 07-02-2017 / 19:49:13 / stefan"
!

byteAt:byteIndex put:anInteger
    "set the byte at byteIndex as an unsigned 8 bit value in the range 0..255.
     The index is a smalltalk index (i.e. 1-based)."

%{ /* NOCONTEXT */
    if (__isSmallInteger(byteIndex) && __isSmallInteger(anInteger)) {
	unsigned char *cp;
	INT sz;
	INT val = __intVal(anInteger);

	if ( ((unsigned INT)val) <= 0xFF ) {
	    __fetchBytePointerAndSize__(self, &cp, &sz);
	    if (cp) {
		unsigned INT idx = ((unsigned INT)__intVal(byteIndex)) - 1;

		if (idx < sz) {
		    cp[idx] = val & 0xFF;
		    RETURN (anInteger);
		}
	    }
	}
    }
%}.

    ^ self at:byteIndex put:anInteger

    "
     |b|
     b := String new:3.
     b byteAt:1 put:16rFF.
     b byteAt:2 put:16r7F.
     b byteAt:3 put:16r80.
     b byteAt:1.
     b byteAt:2.
     b byteAt:3.
    "

    "Modified (comment): / 07-02-2017 / 19:32:26 / stefan"
!

signedByteAt:byteIndex
    "return the byte at byteIndex as a signed 8 bit value in the range -128..+127.
     The index is a smalltalk index (i.e. 1-based).
     This may be worth a primitive."

%{ /* NOCONTEXT */
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if (idx < sz) {
		cp += idx;
		ch = cp[0];
# ifndef HAS_SIGNED_CHAR
		if ( (unsigned int)ch >= 0x80 ) {
		    ch = ch - 0x100;
		}
#endif
		RETURN (__mkSmallInteger( ch ));
	    }
	}
    }
%}.

    ^ (self byteAt:byteIndex) signExtendedByteValue

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

    "Modified: / 01-07-1996 / 21:13:53 / cg"
    "Modified (comment): / 26-09-2011 / 11:57:14 / cg"
    "Modified: / 07-02-2017 / 19:25:03 / stefan"
!

signedByteAt:byteIndex put:aSignedByteValue
    "set the byte at byteIndex to aSignedByteValue in the range -128 .. 255
     The index is a smalltalk index (i.e. 1-based).
     Return the signedByteValue argument."

    |b|

    b := aSignedByteValue.
    b < 0 ifTrue:[
	b := 16r100 + b
    ].
    self byteAt:byteIndex put:b.
    ^ aSignedByteValue

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

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

    "Modified: / 01-07-1996 / 21:12:37 / cg"
    "Modified (comment): / 26-09-2011 / 11:57:18 / cg"
    "Modified (comment): / 07-02-2017 / 20:03:46 / stefan"
! !

!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 machine's
     float representation and byte order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

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

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

	    if ((idx >= 0) && ((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 byteAt:(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 == IsBigEndian ifTrue:[
	^ self doubleAt:index.
    ].

    newFloat := Float basicNew.
    1 to:8 do:[:destIndex|
	newFloat basicAt:(9-destIndex) put:(self byteAt:(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 machine's
     float representation and byte order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |flt|

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

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

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

    flt := aFloat asFloat.
    1 to:8 do:[:srcIndex|
	self byteAt:(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 machine's
     float representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |flt|

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

    flt := aFloat asFloat.
    1 to:8 do:[:srcIndex|
	self byteAt:(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 machine's
     float representation and byte order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

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

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

	    if ((idx >= 0) && ((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 byteAt:(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 machine's
     float representation and order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

    msb == IsBigEndian ifTrue:[
	^ self floatAt:index
    ].

    newFloat := ShortFloat basicNew.
    1 to:4 do:[:destIndex|
	newFloat basicAt:(5-destIndex) put:(self byteAt:(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 and byte order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |sflt|

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

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

	    if ((idx >= 0) && ((idx+(sizeof(float)-1)) < sz)) {
		cp += idx;
		/*
		 * aligned
		 */
		if (((INT)cp & (sizeof(float)-1)) == 0) {
		    if (__isShortFloat(aFloat)) {
			((float *)cp)[0] = __shortFloatVal(aFloat);
			RETURN (self);
		    }
		    if (__isFloat(aFloat)) {
			((float *)cp)[0] = (float)__floatVal(aFloat);
			RETURN (self);
		    }
		    if (__isSmallInteger(aFloat)) {
			((float *)cp)[0] = (float)__intVal(aFloat);
			RETURN (self);
		    }
		    // bail out to smalltalk code
		}
	    }
	}
    }
%}.

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

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 == IsBigEndian ifTrue:[
	self floatAt:index put:aFloat.
	^ self.
    ].

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

    "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 in the native byte order."

    "
     currently, we assume that the machine's 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.
    "
    Float 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 in the native byte order)."

    "
     currently, we assume that the machine's 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.
    "
    Float 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 in the native byte order."

    "
     currently, we assume that the machine's 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.
    "
    ShortFloat 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 in the native byte order).
     Since ST/X floats are really doubles,
     the low- order 4 bytes of the precision are lost."

    "
     currently, we assume that the machine's 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.
    "
    ShortFloat isIEEEFormat ifFalse:[self error:'unsupported operation'].

    self floatAt:index put:aFloat

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

longDoubleAt:index
    "return the 16-bytes starting at index as a LongDouble.
     The index is a smalltalk index (i.e. 1-based).

     Notice, that the C-type long double might have different sizes on different
     machines and may only use part of the 16 bytes;
     i.e. 10bytes (80bit) as on intel CPUS, 12 bytes (96bits) or 16 bytes (128bits).

     Notice also, that the bytes are expected to be in this machine's
     long double representation and byte order
     - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

    newFloat := LongFloat basicNew.
    1 to:16 do:[:destIndex|
	newFloat basicAt:destIndex put:(self byteAt:(index - 1 + destIndex))
    ].
    ^ newFloat.

    "
     |b|

     b := ByteArray new:20.
     b longDoubleAt:1 put:(LongFloat pi).
     Transcript showCR:b.
     Transcript showCR:(b longDoubleAt:1)
    "

    "Created: / 18-07-2017 / 11:31:27 / cg"
!

longDoubleAt:index MSB:msb
    "return the 16-bytes starting at index as a LongDouble.
     The index is a smalltalk index (i.e. 1-based).

     Notice, that the C-type long double has different sizes on different
     machines and may only use part of the 16 bytes;
     i.e. 10bytes (80bit) as on intel CPUS, 12 bytes (96bits) or 16 bytes (128bits).

     Notice also, that the bytes are expected to be in this machine's
     long double representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |newFloat|

    msb == IsBigEndian ifTrue:[
	^ self longDoubleAt:index.
    ].

    newFloat := LongFloat basicNew.
    1 to:16 do:[:destIndex|
	newFloat basicAt:(17-destIndex) put:(self byteAt:(index - 1 + destIndex))
    ].
    ^ newFloat.

    "Created: / 18-07-2017 / 11:30:42 / cg"
!

longDoubleAt:index put:aLongFloat
    "store the value of the argument, aLongFloat as 16 bytes into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     LongFloats are the machine's long double numbers.

     Notice that the bytes are expected to be in this machine's
     float representation and byte order - if the bytearray originated from another
     machine, some conversion is usually needed."

    |flt|

    flt := aLongFloat asLongFloat.
    1 to:16 do:[:srcIndex|
	self byteAt:(index - 1 + srcIndex) put:(flt basicAt:srcIndex)
    ].
    ^ aLongFloat

    "Created: / 18-07-2017 / 11:33:17 / cg"
!

longDoubleAt:index put:aLongFloat MSB:msb
    "store the value of the argument, aLongFloat as 16 bytes into the receiver
     starting at index.
     The index is a smalltalk index (i.e. 1-based).
     Notice that the bytes are expected to be in this machine's
     float representation - if the bytearray originated from another
     machine, some conversion is usually needed."

    |flt|

    msb == IsBigEndian ifTrue:[
	^ self longDoubleAt:index put:aLongFloat.
    ].

    flt := aLongFloat asLongFloat.
    1 to:16 do:[:srcIndex|
	self byteAt:(index - 1 + srcIndex) put:(flt basicAt:(17-srcIndex))
    ].
    ^ aLongFloat

    "Created: / 18-07-2017 / 11:33:59 / cg"
! !

!UninterpretedBytes methodsFor:'accessing-longlongs (64bit)'!

signedInt64At: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 machine's natural byte order.
     This may be worth a primitive."

    |w|

    w := self unsignedInt64At:index MSB:(UninterpretedBytes isBigEndian).
    (w > (16r7FFFFFFFFFFFFFFF)) ifTrue:[
	^ w - (16r10000000000000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:8.
     b unsignedInt64At:1 put:16rFFFFFFFFFFFFFFFF MSB:true.
     (b signedInt64At:1 MSB:true)
    "

    "Modified: / 01-07-1996 / 21:11:28 / cg"
    "Created: / 05-03-1998 / 14:40:05 / stefan"
    "Modified (comment): / 04-08-2017 / 11:29:37 / cg"
!

signedInt64At:index MSB: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 unsignedInt64At:index MSB:msb.
    (w > (16r7FFFFFFFFFFFFFFF)) ifTrue:[
	^ w - (16r10000000000000000)
    ].
    ^ w

    "
     |b|
     b := ByteArray new:8.
     b unsignedInt64At:1 put:16rFFFFFFFFFFFFFFFF MSB:true.
     (b signedInt64At:1 MSB:true)
    "

    "Modified: / 05-03-1998 / 12:06:28 / stefan"
    "Created: / 05-03-1998 / 14:40:54 / stefan"
    "Modified: / 09-05-1998 / 01:10:59 / cg"
    "Modified (comment): / 04-08-2017 / 11:29:59 / cg"
!

signedInt64At:byteIndex put:anInteger
    "store a signed longLong (64bit) integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is stored in the machine's natural byte order.
     Same as #signedQuadWordAt:put: - for ST80 compatibility."

    ^ self signedInt64At:byteIndex put:anInteger MSB:(UninterpretedBytes isBigEndian)

    "Modified (comment): / 04-08-2017 / 11:19:09 / cg"
!

signedInt64At:byteIndex put:anInteger MSB: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 unsignedInt64At:byteIndex put:v MSB:msb.
    ^ anInteger

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

signedInt64AtLSB:byteIndex
    "return the 8-bytes starting at index as a signed 64bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with least significant byte first"

    ^ self signedInt64At:byteIndex MSB:false
!

signedInt64AtLSB:byteIndex put:anInteger
    "set the 8-bytes starting at index from the signed Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self signedInt64At:byteIndex put:anInteger MSB:false
!

signedInt64AtMSB:byteIndex
    "return the 8-bytes starting at index as a signed 64bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with most significant byte first"

    ^ self signedInt64At:byteIndex MSB:true
!

signedInt64AtMSB:byteIndex put:anInteger
    "set the 8-bytes starting at index from the signed Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self signedInt64At:byteIndex put:anInteger MSB:true
!

unsignedInt64At:byteIndex
    "return the 8-bytes starting at index in the machine's native
     byteorder as an unsigned integer.
     The value is retrieved in the machine's natural byte order.
     The index is a smalltalk index (i.e. 1-based)"

   ^ self unsignedInt64At:byteIndex MSB:(UninterpretedBytes isBigEndian)

    "
     |b|

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

    "Modified: / 05-11-1996 / 14:06:21 / cg"
    "Modified: / 05-03-1998 / 14:04:44 / stefan"
    "Modified (comment): / 04-08-2017 / 11:19:21 / cg"
!

unsignedInt64At:byteIndex 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 := byteIndex + 7.
	delta := -1
    ] ifFalse:[
	bIdx := byteIndex.
	delta := 1
    ].
    1 to:8 do:[:i |
	l digitAt:i put:(self byteAt:bIdx).
	bIdx := bIdx + delta
    ].
    ^ l compressed

    "
     |b|

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

    "
     |b|
     b := ByteArray new:8.
     b signedInt64At:1 put:-1 MSB:true.
     (b unsignedInt64At:1 MSB:true)
    "

    "Modified: / 05-11-1996 / 14:06:21 / cg"
    "Modified: / 05-03-1998 / 14:04:44 / stefan"
    "Modified (comment): / 04-08-2017 / 11:30:34 / cg"
!

unsignedInt64At:byteIndex 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 the machine's natural byteorder."

    ^ self unsignedInt64At:byteIndex put:anInteger MSB:(UninterpretedBytes isBigEndian)

    "
     |b|
     b := ByteArray new:10.
     b unsignedInt64At:1 put:16r0807060504030201 MSB:false.
     b unsignedInt64At:1 put:16r0807060504030201 MSB:true.
     b inspect
    "

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

unsignedInt64At:byteIndex 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 class ~~ SmallInteger
	 and:[anInteger > 16rFFFFFFFFFFFFFFFF]]) ifTrue:[
	^ self elementBoundsError:anInteger
    ].

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

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

    "Created: / 05-03-1998 / 14:06:02 / stefan"
    "Modified (comment): / 04-08-2017 / 11:13:59 / cg"
!

unsignedInt64AtLSB:byteIndex
    "return the 8-bytes starting at index as an unsigned 64bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with most significant byte first"

    ^ self unsignedInt64At:byteIndex MSB:false
!

unsignedInt64AtLSB:byteIndex put:anInteger
    "set the 8-bytes starting at index from the unsigned Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self unsignedInt64At:byteIndex put:anInteger MSB:false
!

unsignedInt64AtMSB:byteIndex
    "return the 8-bytes starting at index as an unsigned 64bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with most significant byte first"

    ^ self unsignedInt64At:byteIndex MSB:true
!

unsignedInt64AtMSB:byteIndex put:anInteger
    "set the 8-bytes starting at index from the unsigned Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self unsignedInt64At:byteIndex put:anInteger MSB:true
! !

!UninterpretedBytes methodsFor:'accessing-longs (32bit)'!

signedInt32At:byteIndex
    "return the 4-bytes starting at byteIndex as a signed Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved in the machine's natural byte order,
     therefore, this should only be used for byte-data which is
     only used inside this machine.
     To setup binary data packets which are to be sent to other machines,
     or stored into a file, always use the corresponding xxx:MSB: method
     and specify a definite byteOrder."

    |w|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+(4-1)) < sz)) {
		int iVal;

		cp += idx;
#if defined(__i386__)
		/*
		 * aligned or not, we don't care (i386 can do both)
		 */
		{
		    iVal = ((int *)cp)[0];
		    RETURN (__MKINT(iVal));
		}
#else
# if defined(__x86_64__)
		/*
		 * aligned or not, we don't care (i386 can do both)
		 */
		{
		    iVal = ((int *)cp)[0];
		    RETURN (__mkSmallInteger(iVal));
		}
# else
		/*
		 * aligned ?
		 */
		if (((INT)cp & (sizeof(int)-1)) == 0) {
		    iVal = ((int *)cp)[0];
		} else {
#  ifdef __LSBFIRST__
		    iVal = cp[0] & 0xFF;
		    iVal += (cp[1] & 0xFF)<<8;
		    iVal += (cp[2] & 0xFF)<<16;
		    iVal += (cp[3] & 0xFF)<<24;
#  else
#   ifdef __MSBFIRST__
		    iVal = cp[0] & 0xFF;
		    iVal = (iVal<<8)+(cp[1] & 0xFF);
		    iVal = (iVal<<8)+(cp[2] & 0xFF);
		    iVal = (iVal<<8)+(cp[3] & 0xFF);
#   else
		    {
			union {
			    int i;
			    char c[4];
			} u;
			u.c[0] = cp[0];
			u.c[1] = cp[1];
			u.c[2] = cp[2];
			u.c[3] = cp[3];
			iVal = u.i;
		    }
#   endif
#  endif

#  if __POINTER_SIZE__ == 8
		    RETURN (__mkSmallInteger(iVal));
#  else
		    RETURN (__MKINT(iVal));
#  endif
		}
# endif
#endif
	    }
	}
    }
%}.

    ^ self signedInt32At:byteIndex MSB:IsBigEndian.

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

signedInt32At:byteIndex MSB:msb
    "return the 4-bytes starting at byteIndex as a (signed) Integer.
     The byteIndex is a smalltalk index (i.e. 1-based).
     The value is retrieved MSB-first, if the msb-arg is true;
     LSB-first otherwise."

    |val
     ival "{ Class: SmallInteger }"
     i    "{ Class: SmallInteger }"
     bHH  "{ Class: SmallInteger }"
     bHL  "{ Class: SmallInteger }"
     bLH  "{ Class: SmallInteger }"
     bLL  "{ Class: SmallInteger }"|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

	__fetchBytePointerAndSize__(self, &cp, &sz);
	if (cp) {
	    INT idx = __intVal(byteIndex) - 1;
	    int iVal;

	    cp += idx;
	    if ((idx >= 0) && ((idx+(sizeof(int)-1)) < sz)) {

		if (msb == true) {
#if defined(__MSBFIRST__)
		    if (((INT)cp & (sizeof(int)-1))== 0) {
			/*
			 * aligned
			 */
			iVal = ((int *)cp)[0];
		    } else
#endif
		    {
			iVal = cp[0];
			iVal = (iVal << 8) | cp[1];
			iVal = (iVal << 8) | cp[2];
			iVal = (iVal << 8) | cp[3];
		    }
		} else {
#if defined(__i386__) || (defined(UNALIGNED_FETCH_OK) && defined(__LSBFIRST__))
		    /*
		     * aligned or not - we don't care
		     * (i386 can fetch unaligned)
		     */
		    iVal = ((int *)cp)[0];
#else
# if defined(__LSBFIRST__)
		    if (((INT)cp & (sizeof(int)-1))== 0) {
			/*
			 * aligned
			 */
			iVal = ((int *)cp)[0];
		    } else
# endif
		    {
			iVal = cp[3];
			iVal = (iVal << 8) | cp[2];
			iVal = (iVal << 8) | cp[1];
			iVal = (iVal << 8) | cp[0];
		    }
#endif
		}
#if __POINTER_SIZE__ == 8
		RETURN (__mkSmallInteger(iVal));
#else
		RETURN (__MKINT(iVal));
#endif
	    }
	}
    }
%}.

    val := self unsignedInt32At:byteIndex MSB:msb.
    (val > (16r7FFFFFFF)) ifTrue:[
	^ val - (16r100000000)
    ].
    ^ val

    "
     |b|

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

signedInt32At:byteIndex put:anInteger
    "set the 4-bytes starting at index from the signed Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored in the machine's natural byte order."

    ^ self signedInt32At:byteIndex put:anInteger MSB:IsBigEndian

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

signedInt32At:byteIndex put:anInteger MSB:msb
    "set the 4-bytes starting at byteIndex from the signed Integer value.
     The byteIndex is a smalltalk index (i.e. 1-based).

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

    |v|

%{
    /*
     * handle the most common case fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+3) < sz)) {
		cp += idx;

		if (__isSmallInteger(anInteger)) {
		    INT __v = __intVal(anInteger);

# if __POINTER_SIZE__ == 8
		    if ((__v < -0x80000000L) || (__v > 0x7FFFFFFF)) {
			goto badArg;
		    }
# endif
		    if (((INT)cp & 3) == 0) {
			/*
			 * aligned
			 */
			if (
# ifdef __LSBFIRST__
			    (msb == false)
# else
#  ifdef __MSBFIRST__
			    (msb == true)
#  else
			    (0)
#  endif
# endif
			) {
			    ((int *)cp)[0] = (int)__v;
			    RETURN (anInteger);
			}
		    }
		    if (msb == false) {
			cp[0] = __v & 0xFF;
			cp[1] = (__v>>8) & 0xFF;
			cp[2] = (__v>>16) & 0xFF;
			cp[3] = (__v>>24) & 0xFF;
		    } else {
			cp[0] = (__v>>24) & 0xFF;
			cp[1] = (__v>>16) & 0xFF;
			cp[2] = (__v>>8) & 0xFF;
			cp[3] = __v & 0xFF;
		    }
		    RETURN (anInteger);
		}
	    }
	}
    }
  badArg: ;
%}.

    anInteger >= 0 ifTrue:[
	v := anInteger
    ] ifFalse:[
	v := anInteger + 16r100000000
    ].
    self unsignedInt32At:byteIndex put:v MSB:msb.
    ^ anInteger

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

signedInt32AtLSB:byteIndex
    "return the 4-bytes starting at index as a signed 32bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with least significant byte first"

    ^ self signedInt32At:byteIndex MSB:false
!

signedInt32AtLSB:byteIndex put:anInteger
    "set the 4-bytes starting at index from the signed Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self signedInt32At:byteIndex put:anInteger MSB:false
!

signedInt32AtMSB:byteIndex
    "return the 4-bytes starting at index as a signed 32bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with most significant byte first"

    ^ self signedInt32At:byteIndex MSB:true
!

signedInt32AtMSB:byteIndex put:anInteger
    "set the 4-bytes starting at index from the signed Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with most significant byte first."

    ^ self signedInt32At:byteIndex put:anInteger MSB:true
!

unsignedInt32At:byteIndex
    "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 machine's natural byte order."

    ^ self unsignedInt32At:byteIndex MSB:IsBigEndian

    "
     |b|

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

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

unsignedInt32At:byteIndex 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."

    |val
     ival "{ Class: SmallInteger }"
     i    "{ Class: SmallInteger }"
     bHH  "{ Class: SmallInteger }"
     bHL  "{ Class: SmallInteger }"
     bLH  "{ Class: SmallInteger }"
     bLL  "{ Class: SmallInteger }"|

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+(sizeof(int)-1)) < sz)) {
		cp += idx;

		if (msb == true) {
#if defined(__MSBFIRST__)
		    if (((INT)cp & (sizeof(int)-1))== 0) {
			/*
			 * aligned
			 */
			iVal = ((unsigned int *)cp)[0];
		    } else
#endif
		    {
			iVal = cp[0];
			iVal = (iVal << 8) | cp[1];
			iVal = (iVal << 8) | cp[2];
			iVal = (iVal << 8) | cp[3];
		    }
		} else {
#if defined(__i386__) || (defined(UNALIGNED_FETCH_OK) && defined(__LSBFIRST__))
		    /*
		     * aligned or not - we don't care
		     * (i386 can fetch unaligned)
		     */
		    iVal = ((unsigned int *)cp)[0];
#else
# if defined(__LSBFIRST__)
		    if (((INT)cp & (sizeof(int)-1))== 0) {
			/*
			 * aligned
			 */
			iVal = ((unsigned int *)cp)[0];
		    } else
# endif
		    {
			iVal = cp[3];
			iVal = (iVal << 8) | cp[2];
			iVal = (iVal << 8) | cp[1];
			iVal = (iVal << 8) | cp[0];
		    }
#endif
		}
#if __POINTER_SIZE__ == 8
		RETURN (__mkSmallInteger(iVal));
#else
		RETURN (__MKUINT(iVal));
#endif
	    }
	}
    }
%}.

    "/ fallBack code - non ByteArray-like receiver
    "/ or funny byteIndex

    i := byteIndex.
    msb ifFalse:[
	bLL := self byteAt:i.
	bLH := self byteAt:(i+1).
	bHL := self byteAt:(i+2).
	bHH := self byteAt:(i+3).
    ] ifTrue:[
	bHH := self byteAt:i.
	bHL := self byteAt:(i+1).
	bLH := self byteAt:(i+2).
	bLL := self byteAt:(i+3).
    ].
    ival := (bHH bitShift:8) + bHL.
    ival := (ival bitShift:8) + bLH.
    val := (ival bitShift:8) + bLL.
    ^ val

    "
     |b|

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

unsignedInt32At:byteIndex put:anInteger
    "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 in the machine's native byte order"

    ^ self unsignedInt32At:byteIndex put:anInteger MSB:IsBigEndian

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

unsignedInt32At:byteIndex put:anInteger MSB:msb
    "set the 4-bytes starting at byteIndex from the unsigned Integer value.
     The byteIndex is a smalltalk index (i.e. 1-based).

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

    |v i b1 b2 b3 b4|

%{
    /*
     * handle the most common case fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+3) < sz)) {
		cp += idx;

		if (__isSmallInteger(anInteger)) {
		    INT __v = __intVal(anInteger);

# if __POINTER_SIZE__ == 8
		    if ((__v < 0) || (__v > 0xFFFFFFFF)) {
			goto badArg;
		    }
# endif
		    if (((INT)cp & 3) == 0) {
			/*
			 * aligned
			 */
			if (
# ifdef __LSBFIRST__
			    (msb == false)
# else
#  ifdef __MSBFIRST__
			    (msb == true)
#  else
			    (0)
#  endif
# endif
			) {
			    ((int *)cp)[0] = (int)__v;
			    RETURN (anInteger);
			}
		    }
		    if (msb == false) {
			cp[0] = __v & 0xFF;
			cp[1] = (__v>>8) & 0xFF;
			cp[2] = (__v>>16) & 0xFF;
			cp[3] = (__v>>24) & 0xFF;
		    } else {
			cp[0] = (__v>>24) & 0xFF;
			cp[1] = (__v>>16) & 0xFF;
			cp[2] = (__v>>8) & 0xFF;
			cp[3] = __v & 0xFF;
		    }
		    RETURN (anInteger);
		}
	    }
	}
    }
  badArg: ;
%}.

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

    i := byteIndex.
    msb ifTrue:[
	b1 := (anInteger digitAt:4).
	b2 := (anInteger digitAt:3).
	b3 := (anInteger digitAt:2).
	b4 := (anInteger digitAt:1).
    ] ifFalse:[
	b1 := (anInteger digitAt:1).
	b2 := (anInteger digitAt:2).
	b3 := (anInteger digitAt:3).
	b4 := (anInteger digitAt:4).
    ].
    self byteAt:i     put:b1.
    self byteAt:(i+1) put:b2.
    self byteAt:(i+2) put:b3.
    self byteAt:(i+3) put:b3.
    ^ anInteger

    "
     |b|
     b := ByteArray new:4.
     b signedInt32At:1 put:-1.
     (b unsignedInt32At:1) printStringRadix:16
    "
    "
     |b|
     b := ByteArray new:4.
     b unsignedInt32At:1 put:16rFFFFFFFF.
     (b signedInt32At:1)
    "
!

unsignedInt32AtLSB:byteIndex
    "return the 4-bytes starting at index as an unsigned 32bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with least significant byte first"

    ^ self unsignedInt32At:byteIndex MSB:false
!

unsignedInt32AtLSB:byteIndex put:anInteger
    "set the 4-bytes starting at index from the unsigned Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with least significant byte first."

    ^ self unsignedInt32At:byteIndex put:anInteger MSB:false
!

unsignedInt32AtMSB:byteIndex
    "return the 4-bytes starting at index as an unsigned 32bit Integer.
     The index is a smalltalk index (i.e. 1-based).
     The value is retrieved with most significant byte first"

    ^ self unsignedInt32At:byteIndex MSB:true
!

unsignedInt32AtMSB:byteIndex put:anInteger
    "set the 4-bytes starting at index from the unsigned Integer anInteger.
     The index is a smalltalk index (i.e. 1-based).
     The integer is stored with most significant byte first."

    ^ self unsignedInt32At:byteIndex put:anInteger MSB:true
! !

!UninterpretedBytes methodsFor:'accessing-pointers'!

pointerAt:byteIndex
    "get a pointer starting at byteIndex as ExternalAddress.
     The byteIndex is a smalltalk index (i.e. 1-based).
     Only aligned accesses are allowed.
     The pointer is of native cpu's size (4 or 8 bytes).
     This returns an external adress."

    |failReason|

%{
    if (__isSmallInteger(byteIndex)) {
        unsigned char *cp;
        INT sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            INT idx = __smallIntegerVal(byteIndex) - 1;
            char *pointer;

            if ((idx >= 0) && ((idx+(sizeof(pointer)-1)) < sz)) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(pointer)-1)) == 0) {
                    pointer = ((char **)cp)[0];
                    RETURN (__MKEXTERNALADDRESS(pointer));
                }
                // fprintf(stderr, "cp UNALIGNED (%"_lx_")\n", (INT)cp);
                failReason = @symbol(unaligned);
            } else {
                // fprintf(stderr, "idx(%"_ld_")+(sizeof(pointer)-1) (%d) >= sz (%"_ld_")\n",
                //        idx, (int)(sizeof(pointer)-1), sz);
                failReason = @symbol(invalidIndex);
            }
        } else {
            // fprintf(stderr, "cp is NULL\n");
            failReason = @symbol(nullPointer);
        }
    } else {
        // fprintf(stderr, "non integer index\n");
        failReason = @symbol(invalidIndex);
    }
bad:;
%}.
    ^ self reportError:failReason with:byteIndex

    "
     |b|
     b := ByteArray new:(ExternalAddress pointerSize).
     b pointerAt:1 put:(ExternalAddress newAddress:16r12345678).
     Transcript showCR:((b unsignedInt32At:1) printStringRadix:16).
     Transcript showCR:((b pointerAt:1)).

     |b|
     b := ByteArray new:(ExternalAddress pointerSize).
     b pointerAt:1 put:(ExternalAddress newAddress:16r12345678abcdef).
     Transcript showCR:((b unsignedInt64At:1) printStringRadix:16).
     Transcript showCR:((b pointerAt:1)).
    "

    "Modified (comment): / 14-11-2016 / 17:32:23 / cg"
!

pointerAt:byteIndex put:value
    "set the pointer starting at byteIndex from the integer or externalAddress value.
     The byteIndex is a smalltalk index (i.e. 1-based).
     Only aligned accesses are allowed.
     The pointer is of native cpu's size (4 or 8 bytes).
     The value may be either an ExternalAddress, ExternalBytes or an Integer"

    |failReason|

%{
    OBJ *pointer;

    if (__isExternalAddressLike(value)) {
        pointer = __externalAddressVal(value);
    } else if (__isExternalBytesLike(value)) {
        pointer = __externalBytesVal(value);
        if (pointer == (OBJ *)0)
            pointer = 0;
    } else if (value == nil) {
        pointer = 0;
    } else if (__isSmallInteger(value)) {
        pointer = (OBJ *)__intVal(value);
    } else {
        if ((pointer = (OBJ *)__unsignedLongIntVal(value)) == 0) {
            // fprintf(stderr, "not a largeInt\n");
            failReason = @symbol(badValue);
            goto bad;
        }
    }

    if (__isSmallInteger(byteIndex)) {
        unsigned char *cp;
        INT sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            INT idx = __smallIntegerVal(byteIndex) - 1;

            if ((idx >= 0) && ((idx+(sizeof(pointer)-1)) < sz)) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(pointer)-1)) == 0) {
                    ((char **)cp)[0] = (char *) pointer;
                    RETURN (value);
                }
                // fprintf(stderr, "cp unaligned\n");
                failReason = @symbol(unaligned);
            } else {
                // fprintf(stderr, "idx out of bounds\n");
                failReason = @symbol(invalidIndex);
            }
        } else {
            // fprintf(stderr, "cp is null\n");
            failReason = @symbol(nullPointer);
        }
    } else {
        // fprintf(stderr, "byteIndex not a smallInt\n");
        failReason = @symbol(invalidIndex);
    }
bad:;
%}.
    ^ self reportError:failReason with:byteIndex

    "
     |b|
     b := ByteArray new:ExternalAddress pointerSize.
     b pointerAt:1 put:(ExternalAddress newAddress:16r12345678).
     (b unsignedLongAt:1) printStringRadix:16
    "

    "Created: / 05-03-1998 / 10:57:18 / stefan"
    "Modified (comment): / 14-11-2016 / 17:28:27 / cg"
!

pointerValueAt:byteIndex
    "get a pointer value starting at byteIndex as unsigned integer.
     The byteIndex is a smalltalk index (i.e. 1-based).
     Only aligned accesses are allowed.
     The pointer is of native cpu's size (4 or 8 bytes).
     This returns an int with sizeof the machines's native pointer (4 or 8 bytes)"

    |failReason|
%{
    if (__isSmallInteger(byteIndex)) {
        unsigned char *cp;
        INT sz;

        __fetchBytePointerAndSize__(self, &cp, &sz);
        if (cp) {
            INT idx = __smallIntegerVal(byteIndex) - 1;
            char *pointer;

            if ((idx >= 0) && ((idx+(sizeof(pointer)-1)) < sz)) {
                cp += idx;
                /*
                 * aligned
                 */
                if (((INT)cp & (sizeof(pointer)-1)) == 0) {
                    pointer = ((char **)cp)[0];
                    RETURN (__MKUINT((INT)(pointer)));
                }
                // printf("cp UNALIGNED (%"_lx_")\n", (INT)cp);
                failReason = @symbol(unaligned);
            } else {
                // printf("idx(%"_ld_")+(sizeof(pointer)-1) (%d) >= sz (%"_ld_")\n",
                //        idx, (int)(sizeof(pointer)-1), sz);
                failReason = @symbol(invalidIndex);
            }
        } else {
            // fprintf(stderr, "cp is NULL\n");
            failReason = @symbol(nullPointer);
        }
    } else {
        // fprintf(stderr, "non integer index\n");
        failReason = @symbol(invalidIndex);
    }
bad:;
%}.

    ^ self reportError:failReason with:byteIndex

    "
     |b|
     b := ByteArray new:(ExternalAddress pointerSize).
     b pointerAt:1 put:(ExternalAddress newAddress:16r12345678).
     Transcript showCR:((b unsignedLongAt:1) printStringRadix:16).
     Transcript showCR:((b pointerAt:1)).
     Transcript showCR:((b pointerValueAt:1)).
    "

    "Modified (comment): / 14-11-2016 / 17:28:33 / cg"
! !

!UninterpretedBytes methodsFor:'accessing-shorts (16bit)'!

signedInt16At:byteIndex
    "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 machine's natural byte order."

    ^ (self unsignedInt16At:byteIndex) signExtendedShortValue

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

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

signedInt16At:byteIndex 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 (high 8 bits at lower index) if msb is true;
     LSB-first (i.e. low 8-bits at lower byte index) if it's false.
     Notice:
	the index is a byte index; thus, this allows for unaligned access to
	words on any boundary."

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

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+(2-1)) < sz)) {
		short sVal;

		cp += idx;
		if (msb == false) {
#if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
		    /*
		     * aligned or not, we don't care (i386 can do both)
		     */
		    sVal = ((short *)cp)[0];
#else
		    sVal = (cp[0] & 0xFF) | ((cp[1] & 0xFF) << 8);
#endif
		} else {
		    sVal = ((cp[0] & 0xFF) << 8) | (cp[1] & 0xFF);
		}
		RETURN (__mkSmallInteger(sVal));
	    }
	}
    }
%}.

    b1 := self byteAt:byteIndex.
    b2 := self byteAt:(byteIndex + 1).
    msb ifTrue:[
	^ ((b1 bitShift:8) + b2) signExtendedShortValue
    ].
    ^ ((b2 bitShift:8) + b1) signExtendedShortValue
!

signedInt16At:index put:anInteger
    "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 machine's natural byte order."

    ^ self signedInt16At:index put:anInteger MSB:IsBigEndian

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

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

signedInt16At:byteIndex put:anInteger MSB:msb
    "set the 2-bytes starting at byteIndex from the signed integer value.
     The byteIndex 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."

%{  /* NOCONTEXT */
    /*
     * handle the most common case fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+1) < sz)) {
		cp += idx;

		if (__isSmallInteger(anInteger)) {
		    INT __v = __intVal(anInteger);

		    if ((__v < -0x8000L) || (__v > 0x7FFF)) {
			goto badArg;
		    }
		    if (msb == false) {
#if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
			((short *)cp)[0] = (short)__v;
#else
			cp[0] = __v & 0xFF;
			cp[1] = (__v >> 8) & 0xFF;
#endif
		    } else {
			cp[0] = (__v >> 8) & 0xFF;
			cp[1] = __v & 0xFF;
		    }
		    RETURN (anInteger);
		}
	    }
	}
    }
  badArg: ;
%}.
    anInteger >= 0 ifTrue:[
	self unsignedInt16At:byteIndex put:anInteger MSB:msb.
    ] ifFalse:[
	self unsignedInt16At:byteIndex put:(16r10000 + anInteger) MSB:msb.
    ].
    ^ anInteger

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

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

signedInt16AtLSB:byteIndex
    "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 with least significant byte first"

    ^ self signedInt16At:byteIndex MSB:false

    "
     |b|
     b := ByteArray new:2.
     b wordAt:1 put:16rFFFE.
     b signedInt16AtLSB:1.
     b signedInt16AtMSB:1.
    "

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

signedInt16AtLSB:index put:anInteger
    "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 0 .. 16rFFFF.
     The value is stored with least significant byte first"

    ^ self signedInt16At:index put:anInteger MSB:false

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

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

signedInt16AtMSB:byteIndex
    "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 with most significant byte first"

    ^ self signedInt16At:byteIndex MSB:true

    "
     |b|
     b := ByteArray new:2.
     b wordAt:1 put:16rFFFE.
     b signedInt16AtLSB:1.
     b signedInt16AtMSB:1.
    "

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

signedInt16AtMSB:index put:anInteger
    "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 0 .. 16rFFFF.
     The value is stored with most significant byte first"

    ^ self signedInt16At:index put:anInteger MSB:true

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

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

unsignedInt16At: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 machine's natural byte order"

    ^ self unsignedInt16At:index MSB:IsBigEndian
!

unsignedInt16At:byteIndex 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 it's false.
     Notice:
	the index is a byte index; thus, this allows for unaligned access to
	words on any boundary."

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

%{
    /*
     * handle the most common cases fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

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

	    if ((idx >= 0) && ((idx+(2-1)) < sz)) {
		int iVal;

		cp += idx;
		if (msb == false) {
#if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
		    /*
		     * aligned or not, we don't care (i386 can do both)
		     */
		    iVal = ((unsigned short *)cp)[0];
#else
		    iVal = (cp[0] & 0xFF) | ((cp[1] & 0xFF) << 8);
#endif
		} else {
		    iVal = ((cp[0] & 0xFF) << 8) | (cp[1] & 0xFF);
		}
		RETURN (__mkSmallInteger(iVal));
	    }
	}
    }
%}.

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

    "
     #[ 16rFF 16r00 ] unsignedInt16At:1 MSB:true
     #[ 16rFF 16r00 ] unsignedInt16At:1 MSB:false

     #[ 16rFF 16r00 ] unsignedInt16At:2 MSB:true
     #[ 16rFF 16r00 ] unsignedInt16At:2 MSB:false
    "
!

unsignedInt16At:index put:anInteger
    "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 machine's natural byteorder."

    ^ self unsignedInt16At:index put:anInteger MSB:IsBigEndian

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

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

unsignedInt16At:byteIndex put:anInteger 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"

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

%{  /* NOCONTEXT */
    /*
     * handle the most common case fast ...
     */
    if (__isSmallInteger(byteIndex)) {
	unsigned char *cp;
	INT sz;

	__fetchBytePointerAndSize__(self, &cp, &sz);
	// printf("cp=%"_lx_"\n", (INT)cp);
	if (cp) {
	    INT idx = __intVal(byteIndex) - 1;

	    if ((idx >= 0) && ((idx+1) < sz)) {
		cp += idx;

		if (__isSmallInteger(anInteger)) {
		    INT __v = __intVal(anInteger);

		    if (((unsigned INT)__v) > 0xFFFF) {
			goto badArg;
		    }
		    if (msb == false) {
#if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
			((unsigned short *)cp)[0] = (unsigned short)__v;
#else
			cp[0] = __v & 0xFF;
			cp[1] = (__v >> 8) & 0xFF;
#endif
		    } else {
			cp[0] = (__v >> 8) & 0xFF;
			cp[1] = __v & 0xFF;
		    }
		    RETURN (anInteger);
		}
	    }
	}
    }
  badArg: ;
%}.
    iVal := anInteger.
    ((iVal < 0) or:[iVal > 16rFFFF]) ifTrue:[
	^ self elementBoundsError:iVal
    ].
    msb ifTrue:[
	b1 := ((iVal bitShift:-8) bitAnd:16rFF).
	b2 := (iVal bitAnd:16rFF).
    ] ifFalse:[
	b1 := (iVal bitAnd:16rFF).
	b2 := ((iVal bitShift:-8) bitAnd:16rFF).
    ].
    self byteAt:byteIndex   put:b1.
    self byteAt:byteIndex+1 put:b2.
    ^ anInteger

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

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

unsignedInt16AtLSB:byteIndex
    "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 with least significant byte first"

    ^ self unsignedInt16At:byteIndex MSB:false

    "
     |b|
     b := ByteArray new:2.
     b wordAt:1 put:16rFFFE.
     b unsignedInt16AtLSB:1.
     b unsignedInt16AtMSB:1.
    "

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

unsignedInt16AtLSB:index put:anInteger
    "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 with least significant byte first"

    ^ self unsignedInt16At:index put:anInteger MSB:false

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

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

unsignedInt16AtMSB:byteIndex
    "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 with most significant byte first"

    ^ self unsignedInt16At:byteIndex MSB:true

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

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

unsignedInt16AtMSB:index put:anInteger
    "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 with most significant byte first"

    ^ self unsignedInt16At:index put:anInteger MSB:true

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

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

!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:(String new:40).
    i := index.
    [(c := self byteAt:i) ~~ 0] whileTrue:[
	stream nextPut:(Character value:c).
	i := i + 1.
    ].
    ^ stream contents

    "
      #[71 72 73 74 75 76 77 0] stringAt:1
      #[71 72 73 74 75 76 77 0] stringAt:2
      '1234567890' stringAt:2
    "
!

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

    |i "{ Class: SmallInteger }"|

    i := index.
    aString do:[:aChar |
	self byteAt:i put:aChar codePoint.
	i := i + 1.
    ].
    self byteAt: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)
     ].
    "

    "
     (String new:20) stringAt:1 put:'hello'; stringAt:6 put:' world'; yourself
    "

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

stringAt:index put:aString size:maxSize
    "copy aString to the receiver, starting at index up to either maxSize characters,
     or (and including) the 0-byte, whichever is encountered first.
     The final 0-byte is only written, if the string is shorter than maxSize.
     The index is a smalltalk index (i.e. 1-based)."

    |remaining "{ Class: SmallInteger }"
     i         "{ Class: SmallInteger }"|

    remaining := maxSize.
    remaining <= 0 ifTrue:[^ aString].

    i := index.
    aString do:[:aChar |
	self byteAt:i put:aChar codePoint.
	i := i + 1.
	remaining := remaining - 1.
	remaining <= 0 ifTrue:[^ aString].
    ].
    self byteAt:i put:0.
    ^ aString

    "
     |bytes|

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

     bytes := ByteArray new:10 withAll:16rFF.
     bytes stringAt:1 put:'he' size:3.
     1 to:bytes size do:[:i |
	Transcript showCR:(bytes at:i)
     ]
    "

    "
     (String new:20) stringAt:1 put:'hello' size:3 ; stringAt:4 put:' world' size:4; yourself
    "


    "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
     max "{ Class: SmallInteger }"
     start "{ Class: SmallInteger }"|

    stream := WriteStream on:(String new:maxSize).
    start := index.
    max := start + maxSize - 1.

    start to:max do:[:eachIndex|
	c := self byteAt:eachIndex.
	c == 0 ifTrue:[
	    ^ stream contents
	].
	stream nextPut:(Character value:c).
    ].
    ^ stream contents

    "
      #[71 72 73 74 75 76 77] stringAt:1 size:7
      #[71 72 73 74 75 76 77] stringAt:2 size:6
      '1234567890' stringAt:2 size:6
    "
!

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 endIndex idx|

    endIndex := self indexOf:0 startingAt:index.
    endIndex == 0 ifTrue:[
	endIndex := self size + 1
    ].
    endIndex := (endIndex min: (index + count)) - 1.
    bytes := self copyFrom:index to:endIndex.
    ^ bytes asString

    "
     #[ 1 2 3 4 5 6 7 8 ] zeroByteStringAt:2 maximumSize:10
     #[ 1 2 3 4 5 0 6 7 8 ] zeroByteStringAt:2 maximumSize:10
     #[ 1 2 3 4 5 0 6 7 8 ] zeroByteStringAt:2 maximumSize:3
     #[ 1 2 3 4 5 0 6 7 8 ] zeroByteStringAt:2 maximumSize:4
    "
! !

!UninterpretedBytes methodsFor:'converting'!

asExternalBytes
    "in earlier times, this use to return protected memory
     (i.e. it would not be garbage collected, and the user had to free it manually).
     This was changed to now return garbage collected memory."

    ^ self asExternalBytesUnprotected.

    "
      #[1 2 3 4 5 6 7] asExternalBytes
      'Hello World' asExternalBytes
      'Hello World' asUnicodeString asExternalBytes
    "

    "Modified (comment): / 04-08-2017 / 11:25:00 / cg"
!

asExternalBytesUnprotected
    "Like asExternalBytes, but does not protect the bytes from the collector,
     so the bytes are GARBAGE-COLLECTED
     (i.e. free is called when the smalltalk object is no longer referenced)."

    |bytes sz|

    sz := self byteSize.
    bytes := ExternalBytes unprotectedNew:sz.
    bytes replaceFrom:1 to:sz with:self startingAt:1.
    ^ bytes

    "
     |x|
     x := 'fooBar' asExternalBytesUnprotected.
     ObjectMemory garbageCollect
    "

    "Created: / 05-06-2012 / 14:11:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-11-2013 / 11:42:21 / cg"
    "Modified (comment): / 04-08-2017 / 11:22:58 / cg"
!

asSingleByteString
    "return the receiver converted to a 'normal' string.
     Raises an error if unrepresentable characters are encountered.
     See also: #asSingleByteStringIfPossible and #asSingleByteStringReplaceInvalidWith:"

    ^ String fromString:self

    "
     #[60 61 62 63] asSingleByteString
     #[60 61 62 63] asExternalBytes  asSingleByteString
     #[67 68 69 70] asIntegerArray asSingleByteString
     'abc' asText asSingleByteString
     (Unicode16String with:(Character value:16rFF)) asSingleByteString
     (Unicode16String with:(Character value:16rFFFF)) asSingleByteString
    "

    "Modified (comment): / 16-02-2017 / 20:25:14 / stefan"
!

asSingleByteStringIfPossible
    "if possible, return the receiver converted to a 'normal' string.
     It is only possible, if there are no characters with codePoints above 255 in the receiver.
     If not possible, the (wideString) receiver is returned."

    self containsNon8BitElements ifTrue:[^ self asString].
    ^ self asSingleByteString.

    "
     #[67 68 69 70] asSingleByteStringIfPossible
     #[67 68 69 70] asIntegerArray asSingleByteStringIfPossible
     'hello' asUnicodeString asSingleByteStringIfPossible
    "
!

asUUID
    ^ UUID fromBytes:self
! !

!UninterpretedBytes methodsFor:'encoding & decoding'!

base64Decoded
    ^ Base64Coder decode:self

    "
     'abc' base64Encoded base64Decoded
     #[1 2 3] base64Encoded base64Decoded
    "

    "Created: / 21-01-2019 / 17:24:00 / Claus Gittinger"
!

base64Encoded
    ^ Base64Coder encode:self

    "
     'abc' base64Encoded
     #[1 2 3] base64Encoded
    "

    "Created: / 21-01-2019 / 17:23:33 / Claus Gittinger"
!

utf8Decoded
    "Interpreting myself as an UTF-8 representation, decode and return the decoded string."

    ^ CharacterArray decodeFromUTF8:self.

    "
     #[16rC8 16rA0] utf8Decoded
     #[16rC8 16rA0] asString utf8Decoded
     #[16rC8 16rA0] asExternalBytes utf8Decoded
     (Character value:16r220) utf8Encoded utf8Decoded

     (Character value:16r800) utf8Encoded
     (Character value:16r220) utf8Encoded utf8Decoded
    "

    "test:

      1 to:16r10FFFF do:[:codepoint |
	|utf8Encoding original readBack|

	original := (Character value:codepoint) asString.
	utf8Encoding := original utf8Encoded.
	readBack := utf8Encoding utf8Decoded.
	readBack ~= original ifTrue:[
	    self halt
	]
      ]
    "

    "Modified (comment): / 07-02-2017 / 17:36:08 / stefan"
!

utf8DecodedWithTwoByteCharactersReplacedBy:replacementCharacter
    "Interpreting myself as an UTF-8 representation, decode and return
     the decoded string. Suppress all 2-byte (above 16rFF) characters,
     and replace them with replacementCharacter"

    |in out|

    self containsNon7BitAscii ifFalse:[
        ^ self asSingleByteString   "plain ASCII"
    ].

    out := WriteStream on:(String uninitializedNew:self utf8DecodedSize).
    in := self readStream.
    [in atEnd] whileFalse:[
        |c|

        c := Character utf8DecodeFrom:in.
        c codePoint > 16rFF ifTrue:[
            c := replacementCharacter
        ].
        out nextPut:c.
    ].
    ^ out contents

    "
     (Character value:16r220) utf8Encoded
        utf8DecodedWithTwoByteCharactersReplacedBy:(Character space)

     (Character value:16r220) utf8Encoded asExternalBytes copyButLast
        utf8DecodedWithTwoByteCharactersReplacedBy:(Character space)
    "

    "Modified (comment): / 02-01-2018 / 18:54:18 / stefan"
! !

!UninterpretedBytes methodsFor:'filling & replacing'!

replaceBytesFrom:start to:stop with:aCollection startingAt:repStart
    "replace elements from another collection, which must be a ByteArray-
     like collection.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

%{  /* NOCONTEXT */

    int nIndex, repNIndex;
    int startIndex, stopIndex;
    REGISTER unsigned char *src;
    REGISTER int repStartIndex;
    int repStopIndex, count;
    REGISTER unsigned char *dst;
    OBJ cls;

#ifndef NO_PRIM_BYTEARR
    if ((__isBytes(aCollection) || __isExternalBytesLike(aCollection))
     && (__isBytes(self) || __isWords(self))
     && __bothSmallInteger(start, stop)
     && __isSmallInteger(repStart)) {
	startIndex = __intVal(start) - 1;
	if (startIndex >= 0) {
	    dst = (__ByteArrayInstPtr(self)->ba_element) + startIndex;
	    nIndex = __byteArraySize(self);

	    if ((cls = __qClass(self)) != @global(ByteArray)) {
		int nInst;

		nInst = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
		dst += nInst;
		nIndex -= nInst;
	    }

	    stopIndex = __intVal(stop) - 1;
	    count = stopIndex - startIndex + 1;
	    if (count == 0) {
		RETURN ( self );
	    }

	    if ((count > 0) && (stopIndex < nIndex)) {
		repStartIndex = __intVal(repStart) - 1;
		if (repStartIndex >= 0) {
		    if (__isExternalBytesLike(aCollection)) {
			OBJ sz;

			src = __externalAddressVal(aCollection);
			if (src == 0) goto fallBack;

			sz = __externalBytesSize(aCollection);
			if (__isSmallInteger(sz)) {
			    repNIndex = __smallIntegerVal(sz);
			} else {
			    repNIndex = repStopIndex+1; /* always enough */
			}
			src = src + repStartIndex;
		    } else {
			if (__isStringLike(aCollection)) {
			    repNIndex = __stringSize(aCollection);
			} else {
			    repNIndex = __qSize(aCollection) - OHDR_SIZE;
			}
			src = (__ByteArrayInstPtr(aCollection)->ba_element) + repStartIndex;
			if ((cls = __qClass(aCollection)) != @global(ByteArray)) {
			    int nInst;

			    nInst = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
			    src += nInst;
			    repNIndex -= nInst;
			}
		    }
		    repStopIndex = repStartIndex + (stopIndex - startIndex);
		    if (repStopIndex < repNIndex) {
			if (aCollection == self) {
			    /* take care of overlapping copy */
			    if (src < dst) {
				/* must do a reverse copy */
				src += count;
				dst += count;
				while (count-- > 0) {
				    *--dst = *--src;
				}
				RETURN ( self );
			    }
			}

# ifdef bcopy4
			if (((unsigned INT)src & 3) == ((unsigned INT)dst & 3)) {
			    int nW;

			    /* copy unaligned part */
			    while (count && ((unsigned INT)src & 3)) {
				*dst++ = *src++;
				count--;
			    }

			    if (count > 0) {
				/* copy aligned part */
				nW = count >> 2;
				bcopy4(src, dst, nW);
				if ((count = count & 3) != 0) {
				    /* copy any remaining part */
				    src += (nW<<2);
				    dst += (nW<<2);
				    while (count--) {
					*dst++ = *src++;
				    }
				}
			    }
			    RETURN ( self );
			}
# else
#  if __POINTER_SIZE__ == 8
			if (((unsigned INT)src & 7) == ((unsigned INT)dst & 7)) {
			    /* copy unaligned part */
			    while (count && ((unsigned INT)src & 7)) {
				*dst++ = *src++;
				count--;
			    }

			    /* copy aligned part */
			    while (count >= 8) {
				((unsigned INT *)dst)[0] = ((unsigned INT *)src)[0];
				dst += 8;
				src += 8;
				count -= 8;
			    }
			    while (count--) {
				*dst++ = *src++;
			    }
			    RETURN ( self );
			}
#  endif /* 64bit */
# endif /* bcopy4 */

# ifdef FAST_MEMCPY
			bcopy(src, dst, count);
# else
#  ifdef __UNROLL_LOOPS__
			while (count >= 8) {
			    dst[0] = src[0]; dst[1] = src[1];
			    dst[2] = src[2]; dst[3] = src[3];
			    dst[4] = src[4]; dst[5] = src[5];
			    dst[6] = src[6]; dst[7] = src[7];
			    dst += 8; src += 8;
			    count -= 8;
			}
#  endif /* __UNROLL_LOOPS__ */
			while (count-- > 0) {
			    *dst++ = *src++;
			}
# endif
			RETURN ( self );
		    }
		}
	    }
	}
    }
fallBack: ;
#endif
%}.
    "
     fall back in case of non-ByteArray argument,
     or for the error report if any index is invalid
    "
    self slowReplaceBytesFrom:start to:stop with:aCollection startingAt:repStart

    "
     #[1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16]
	copy
	    replaceFrom:1 to:8
	    with:#[10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160]
	    startingAt:1

     #[1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16]
	copy
	    replaceFrom:3 to:10
	    with:#[10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160]
	    startingAt:1

     #[1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16]
	copy
	    replaceFrom:3 to:4
	    with:#[10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160]
	    startingAt:1

     #[1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16]
	copy
	    replaceFrom:0 to:9
	    with:#[10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160]
	    startingAt:1

     #[1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16]
	copy
	    replaceFrom:1 to:10
	    with:#[10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160]
	    startingAt:0
    "
!

replaceBytesFrom:startIndex with:replacementCollection startingAt:repStartIndex
    "replace elements from another collection, which must be
     byte-array-like.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self
	replaceBytesFrom:startIndex
	to:(startIndex + replacementCollection size - repStartIndex)
	with:replacementCollection
	startingAt:repStartIndex

    "
     args:    startIndex            : <integer>
	      replacementCollection : <collection of <bytes> >
	      repStartIndex         : <integer>

     returns: self
    "

    "Created: / 27.7.1998 / 16:56:46 / cg"
    "Modified: / 27.7.1998 / 16:58:38 / cg"
!

replaceBytesWith:replacementCollection
    "replace elements from another collection, which must be byte-array-like.
     Replace stops at whichever collection is smaller.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    ^ self
	replaceBytesFrom:1
	to:(replacementCollection sizeInBytes min:self sizeInBytes)
	with:replacementCollection
	startingAt:1

    "
     (ByteArray new:10) replaceBytesWith:'hello'
     (ByteArray new:10) replaceBytesWith:'hello world bla bla bla'
    "

    "Created: / 09-01-2012 / 16:18:10 / cg"
    "Modified: / 28-08-2017 / 02:17:23 / cg"
!

replaceFrom:startIndex to:stopIndex with:aCollection startingAt:repStartIndex
    "replace elements in the receiver between index start and stop,
     with elements  taken from replacementCollection starting at repStart.
     Return the receiver.

     Notice: This operation modifies the receiver, NOT a copy;
     therefore the change may affect all others referencing the receiver."

    (self class isBytes
     and:[aCollection class == self class or:[aCollection isSingleByteCollection]]
    ) ifTrue:[
	"can do it fast: just copy the plain bytes"
	^ self replaceBytesFrom:startIndex to:stopIndex with:aCollection startingAt:repStartIndex
    ].
    ^ super replaceFrom:startIndex to:stopIndex with:aCollection startingAt:repStartIndex

    "
     args:    startIndex            : <integer>
	      stopIndex             : <integer>
	      replacementCollection : <collection of <bytes> >
	      repStartIndex         : <integer>

     returns: self
    "

    "Modified: / 08-05-2012 / 13:23:27 / cg"
! !

!UninterpretedBytes methodsFor:'hashing'!

computeXorHashFrom:startIndex to:endIndex
    "compute and answer the 32bit SmallInteger-Hash of the bytes
     from startIndex to endIndex.
     If endindex = 0 or endIndex > size, hash up the size.

     NOTE: startIndex and endIndex are only hints about what should be hashed.
	   In fact, more bytes could be involved in hashing.
	   SO ARRAYS MUST BE EQUAL TO HASH TO THE SAME VALUE.

    Also NOTE:
	used to return a 32bit hash on 32bit machines and a 64bit integer on 64bit cpus.
	changed to return the same for all (in case hash values are used for other purposes)."

    |w|

%{
    if (__bothSmallInteger(startIndex, endIndex)) {
	unsigned char *cp;
	INT sz;

	__fetchBytePointerAndSize__(self, &cp, &sz);
	if (cp) {
	    INT sidx = ((unsigned INT)__smallIntegerVal(startIndex)) - 1;
	    INT eidx = ((unsigned INT)__smallIntegerVal(endIndex)) - 1;
// #           define H_INT INT
// #           define _MAX_H_INT _MAX_INT;
#           define H_INT int
#           define _MAX_H_INT 0x3FFFFFFF

	    unsigned char *ep;
	    unsigned H_INT hash = 0, hash2 = 0, carry;
	    int i;

	    if (eidx < 0 || eidx >= sz) eidx = sz - 1;
	    if (sidx > eidx) sidx = eidx;
	    if (sidx < 0) {
		RETURN(__mkSmallInteger(0));
	    }

	    ep = cp + eidx;
	    cp += sidx;

#if 0
	    /*
	     * On LSB-First (little endian) cpus,
	     * this code does not produce the same result
	     * if the same bytes are at different positions
	     */

	    if ((H_INT)cp & (sizeof(H_INT)-1)) {
		/* not aligned */

		for (i=0; cp <= ep; cp++) {
		    hash2 = (hash2 << 8) | *cp;
		    if (++i == sizeof(H_INT)) {
			hash ^= hash2;
			i = hash2 = 0;
		    }
		}
	    } else {
		/* aligned */
		for (; cp+sizeof(H_INT) <= ep; cp += sizeof(H_INT)) {
		    hash ^= *(unsigned H_INT *)cp;
		}
		for (; cp <= ep; cp++) {
		    hash2 = (hash2 << 8) | *cp;
		}
	    }
#else
	    for (i=0; cp <= ep-sizeof(H_INT); cp += sizeof(H_INT)) {
		hash2 = cp[0];
		hash2 = (hash2 << 8) | cp[1];
		hash2 = (hash2 << 8) | cp[2];
		hash2 = (hash2 << 8) | cp[3];
# if 0
		if (sizeof(H_INT) == 8) {
		    hash2 = (hash2 << 8) | cp[4];
		    hash2 = (hash2 << 8) | cp[5];
		    hash2 = (hash2 << 8) | cp[6];
		    hash2 = (hash2 << 8) | cp[7];
		}
# endif
		/*
		 * multiply by large prime to scramble bits and
		 * to avoid a 0 result from
		 * #[1 2 3 4 1 2 3 4] computeXorHashFrom:1 to:8.
		 */
		hash ^= (hash * 31415821) ^ hash2;
	    }
	    for (hash2 = 0; cp <= ep; cp++) {
		hash2 = (hash2 << 8) | *cp;
	    }
#endif
	    hash ^= (hash * 31415821) ^ hash2;

	    /*
	     * fold the high bits not fitting into a H_INT
	     */
	    carry = hash & ~_MAX_H_INT;
	    if (carry) {
		hash = (hash & _MAX_H_INT) ^ (carry >> 8);
	    }

	    RETURN(__mkSmallInteger(hash));
	}
    }
%}.

    ^ self primitiveFailed

    "
     #[1 2 3 4] computeXorHashFrom:1 to:4.
     #[1 2 3 4] computeXorHashFrom:1 to:32.
     #[1 2 3 4] computeXorHashFrom:1 to:0.
     #[1 2 3 4 5] computeXorHashFrom:1 to:4.
     #[1 2 3 4 1 2 3 4] computeXorHashFrom:1 to:8.
     #[1 2 3 4 5 6 7 8] computeXorHashFrom:2 to:8.
     #[2 3 4 5 6 7 8] computeXorHashFrom:1 to:7.
     #[2 3 4 5 6 7 8] computeXorHashFrom:1 to:8.
    "
!

hash
    |sz|

    sz := self size.
    sz <= 32 ifTrue:[
        ^ self computeXorHashFrom:1 to:sz.
    ].
    
    "/ the code below is actually not doing what was intended (to take the hashes of the first 16
    "/ and the last 16 bytes.
    "/ It does actually take the last 17 bytes (due to a mistake of the original programmer...)
    "/ However, we will not change it, but keep it that way, in case the hashvalue already found
    "/ its way into some dictionary (as key-index).
    "/ It does not really hurt anyway, so there is no need to change it.
    ^ (sz bitXor:(self computeXorHashFrom:1 to:16)) bitXor:(self computeXorHashFrom:sz-16 to:sz)

    "
        #[1 2 3 4] hash
        #[1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 ] hash
        
        #[1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4
          1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 ] hash
          
        #[1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4
          1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1] hash
    "

    "Modified (format): / 28-11-2017 / 15:03:36 / cg"
! !

!UninterpretedBytes methodsFor:'image manipulation support'!

copyReverse
    <resource: #obsolete>
    "create a copy of myself with elements reversed in order"

    self obsoleteMethodWarning:'use #reversed'.

    ^ self reversed

    "
     #[1 2 3 4 5] copyReverse
     #[1 2 3 4] copyReverse
    "

    "Modified: / 25-07-2017 / 17:10:02 / stefan"
!

swapBytes
    "swap bytes (of int16s) inplace -
     Expects that the receiver has an even number of bytes;
     if not, only the pairs excluding the last byte are swapped"

    |b1 lastIndex "{ Class: SmallInteger }"|

    lastIndex := self size-1.
    1 to:lastIndex by:2 do:[:idx |
	b1 := self byteAt:idx.
	self byteAt:idx put:(self byteAt:idx+1).
	self byteAt:idx+1 put:b1.
    ].

    "
     #[1 2 3 4 5] swapBytes
     #[1 2 3 4] swapBytes
    "
! !


!UninterpretedBytes methodsFor:'misc'!

copyToEndInto:aStream
    "copy all of myself into aStream. Compatibility with Stream"

    aStream nextPutAll:self.

    "Created: / 23-01-2018 / 18:43:40 / stefan"
!

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:'printing & storing'!

hexPrintOn:aStream
    "print as hex string, eg: 'FF0243'.
     This string can be used in #fromHexString: to recreate the byteArray"

    self hexPrintOn:aStream withSeparator:nil

    "
      #[1 2 3 4 10 17] hexPrintOn:Transcript
    "

    "
     |s|
     s := String streamContents:[:s | #[1 2 3 4 10 17] hexPrintOn:s].
     ByteArray fromHexString:s
    "
!

hexPrintOn:aStream withSeparator:aSeparatorStringOrCharacterOrNil
    "print as hex string with separators, eg: 'FF:02:43'"

    |first|

    first := true.
    1 to:self size do:[:idx |
	aSeparatorStringOrCharacterOrNil notNil ifTrue:[
	    first ifFalse:[
		aSeparatorStringOrCharacterOrNil printOn:aStream
	    ] ifTrue:[
		first := false.
	    ].
	].
	(self byteAt:idx) printOn:aStream base:16 size:2 fill:$0.
    ].

    "
      #[1 2 3 4 10 17] hexPrintOn:Transcript withSeparator:$:
      #[1 2 3 4 10 17] hexPrintOn:Transcript withSeparator:(Character space)
      #[1 2 3 4 10 17] hexPrintOn:Transcript withSeparator:'-'
      #[1 2 3 4 10 17] hexPrintOn:Transcript withSeparator:nil
      'hello' hexPrintOn:Transcript withSeparator:'.'
    "
!

hexPrintString
    "print as hex string, eg: 'FF0243'.
     This string can be used in #fromHexString: to recreate the byteArray"

    ^ self hexPrintStringWithSeparator:nil

    "
     #[1 2 3 4 10 17] hexPrintString
     ByteArray fromHexString:#[1 2 3 4 10 17] hexPrintString
     'hello' hexPrintString
    "

    "Modified: / 03-07-2010 / 01:59:19 / cg"
!

hexPrintStringWithSeparator:aSeparatorStringOrCharacterOrNil
    "print as hex string, eg: 'FF:02:43'."

    ^ String
	streamContents:[:s |
	    self hexPrintOn:s withSeparator:aSeparatorStringOrCharacterOrNil.
	]

    "
      #[1 2 3 4 10 17] hexPrintStringWithSeparator:$:
      #[1 2 3 4 10 17] hexPrintStringWithSeparator:Character space
      #[1 2 3 4 10 17] hexPrintStringWithSeparator:' - '
      #[1 2 3 4 10 17] hexPrintStringWithSeparator:nil
      'hello' hexPrintStringWithSeparator:'.'
    "
! !

!UninterpretedBytes methodsFor:'private'!

reportError:failReason with:parameter
    "common helper"

    (failReason == #invalidIndex) ifTrue:[
        ^ self indexNotIntegerOrOutOfBounds:parameter
    ].
    failReason == #nullPointer ifTrue:[
        ^ self error:'free or unallocated object referenced'
    ].
    failReason == #unaligned ifTrue:[
        ^ self error:'unaligned index'. 
    ].
    self primitiveFailed:failReason.
!

slowReplaceBytesFrom:startArg to:stopArg with:sourceBytes startingAt:sourceIndex
    "fallback if primitive code fails"

    |srcIdx "{ Class:SmallInteger }"
     start "{ Class:SmallInteger }"
     stop "{ Class:SmallInteger }"|

    start := startArg.
    stop := stopArg.
    srcIdx := sourceIndex.

    start to:stop do:[:dstIdx |
	self byteAt:dstIdx put:(sourceBytes byteAt:srcIdx).
	srcIdx := srcIdx + 1
    ].

    "Modified: / 28-08-2017 / 02:25:53 / cg"
! !

!UninterpretedBytes methodsFor:'queries'!

containsNon7BitAscii
    "return true, if the underlying collection contains elements longer than 7 bits
     (i.e. if it is non-ascii)"

    |sz "{ Class:SmallInteger }"|

    sz := self size.
    1 to:sz do:[:idx|
	(self at:idx) > 16r7F ifTrue:[
	    ^ true.
	].
    ].
    ^ false.
!

containsNon8BitElements
    "return true, if the underlying structure contains elements larger than a single byte"

    |sz "{ Class:SmallInteger }"|

    sz := self size.
    1 to:sz do:[:idx|
	(self at:idx) > 16rFF ifTrue:[
	    ^ true.
	].
    ].
    ^ false.
!

defaultElement
    ^ 0
!

isAllocated
    "for compatibility with ExternalBytes"
    
    ^ true

    "Created: / 02-04-2019 / 20:30:50 / Claus Gittinger"
!

isNull
    "for compatibility with ExternalBytes"
    
    ^ false

    "Created: / 02-04-2019 / 20:30:45 / Claus Gittinger"
!

isValidUTF8
    "returns true, if the receiver contains a valid UTF8 encoded string"

    |trailing  "{ Class: SmallInteger }"|

    trailing := 0.

    1 to:self size do:[:idx |
	|byte "{ Class: SmallInteger }" |

	byte := self byteAt:idx.
	trailing ~~ 0 ifTrue:[
	    (byte bitAnd:2r11000000) == 2r10000000 ifFalse:[^ false].
	    trailing := trailing - 1.
	] ifFalse:[
	    (byte bitAnd:16r80) == 0 ifTrue:[
		"/ continue
	    ] ifFalse:[
		(byte bitAnd:2r11100000) == 2r11000000 ifTrue:[
		    "/ strict: should not be encoded this way (could have used a shorter sequence)
		    (byte bitAnd:2r00011110) == 0 ifTrue:[
			^ false
		    ].
		    trailing := 1.
		] ifFalse:[
		    (byte bitAnd:2r11110000) == 2r11100000 ifTrue:[
			trailing := 2.
		    ] ifFalse:[
			(byte bitAnd:2r11111000) == 2r11110000 ifTrue:[
			    trailing := 3.
			] ifFalse:[
			    (byte bitAnd:2r11111100) == 2r11111000 ifTrue:[
				trailing := 4.
			    ] ifFalse:[
				(byte bitAnd:2r11111110) == 2r11111100 ifTrue:[
				    trailing := 5.
				] ifFalse:[
				    ^ false
				].
			    ].
			].
		    ].
		].
	    ].
	].
    ].
    ^ trailing == 0

    "
     'abc' isValidUTF8
     'abcöäü' isValidUTF8
     'abcöäü' utf8Encoded isValidUTF8
     (Character value:16r800) utf8Encoded isValidUTF8
     (Character value:16r1000) utf8Encoded isValidUTF8

     1 to:255 do:[:c1 |
	 1 to:255 do:[:c2 |
	     1 to:255 do:[:c3 |
		 self assert:(c1 asCharacter , c2 asCharacter , c3 asCharacter) utf8Encoded isValidUTF8
	     ]
	 ]
     ]

     |s|
     1 to:10000 do:[:c1 |
	 1 to:255 do:[:c2 |
	     s := (c1 asCharacter , c2 asCharacter).
	     self assert:s utf8Encoded isValidUTF8
	 ]
     ]
    "
!

referencesAny:aCollection
    "redefined to speed up searching when many of my instances are present"

%{ /* NOCONTEXT */
    if (__mkSmallInteger(0) == __ClassInstPtr(__qClass(self))->c_ninstvars) {
	/* I am only bytes */
	RETURN(false)
    }
%}.
    ^ super referencesAny:aCollection

    "
	'abc' referencesAny:#()
    "
!

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

    ^ super size

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

utf8DecodedSize
    "return the number of characters needed when this string is
     decoded from UTF-8"

    |sz "{ Class:SmallInteger }"
     cnt "{ Class:SmallInteger }"|

    sz := self size.
    cnt := 0.

    1 to:sz do:[:idx|
        "/ count the number of UTF-8 start bytes
        ((self byteAt:idx) bitAnd:16rC0) ~~ 16r80 ifTrue:[
            cnt := cnt+1.
        ].
    ].
    ^ cnt.

    "
     'hello world' asByteArray utf8DecodedSize
     'ä' utf8Encoded asByteArray utf8DecodedSize
     'äΣΔΨӕἤῴ' utf8Encoded asByteArray utf8DecodedSize
    "

    "Created: / 07-02-2017 / 15:03:07 / stefan"
    "Modified: / 07-02-2017 / 19:14:06 / stefan"
    "Modified (comment): / 02-01-2018 / 18:30:27 / stefan"
    "Modified (comment): / 15-01-2018 / 08:29:10 / mawalch"
! !

!UninterpretedBytes methodsFor:'testing'!

isByteCollection
    "return true, if the receiver has access methods for bytes;
     This is different from 'self class isBytes',
     true is returned here - the method is redefined from Object."

    ^ true
!

isNonByteCollection
    "return true, if the receiver is some kind of collection, but not a String, ByteArray etc.;
     false is returned here - the method is redefined from Collection."

    ^ false
!

isSingleByteCollection
    "return true, if the receiver has access methods for bytes;
     i.e. #at: and #at:put: accesses a byte and are equivalent to #byteAt: and byteAt:put:
     and #replaceFrom:to: is equivalent to #replaceBytesFrom:to:.
     This is different from 'self class isBytes',
     true is returned here - the method is redefined from Object."

    ^ true
! !

!UninterpretedBytes methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter
    "dispatch for visitor pattern; send #visitByteArray:with: to aVisitor."

    ^ aVisitor visitByteArray:self with:aParameter
! !

!UninterpretedBytes class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


UninterpretedBytes initialize!