BaseNCoder.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5459 70e5b29dd7d3
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 2002 by eXept Software AG
              All Rights Reserved

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

"{ NameSpace: Smalltalk }"

ObjectCoder subclass:#BaseNCoder
	instanceVariableNames:'buffer bits charCount peekByte atEnd lineLimit mapping
		reverseMapping'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Storage'
!

!BaseNCoder class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2002 by eXept Software AG
              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
"
    Abstract superclass of Base64Coder and Base32Coder
    Their main entry point API is 
        <BaseNCoder> encode:aStringOrBytes
    and
        <BaseNCoder> decode:aString

    If the decoder should return a string, use
        <BaseNCoder> decodeAsString:aString.

    [examples:]
        Base64Coder encode:'helloWorld'
        
        Base64Coder decode:'aGVsbG9Xb3JsZA=='
        
        Base64Coder decodeAsString:'aGVsbG9Xb3JsZA=='
        
    [author:]
        Stefan Vogel (stefan@zwerg)

    [instance variables:]
        buffer          SmallInteger   buffered data
        bits            SmallInteger   Number of valid bits in buffer
        charCount       SmallInteger   Number of characters since last cr
        atEnd           Boolean        true if end of Base64 string reached

    [class variables:]

    [see also:]

"
! !

!BaseNCoder class methodsFor:'initialization'!

initializeMappings
    self subclassResponsibility

    "
     self withAllSubclassesDo:#initialize
    "

    "Modified (comment): / 30-09-2018 / 15:39:16 / Claus Gittinger"
!

mapping
    self subclassResponsibility

    "Created: / 30-09-2018 / 15:30:08 / Claus Gittinger"
!

reverseMapping
    self subclassResponsibility

    "Created: / 30-09-2018 / 15:30:11 / Claus Gittinger"
!

reverseMappingFor:mapping
    "initialize class variables"

    |revMapping|
    
    revMapping := ByteArray new:128 withAll:255.
    mapping keysAndValuesDo:[:idx :char|
        revMapping at:char codePoint put:idx-1.
    ].
    ^ revMapping

    "Created: / 30-09-2018 / 15:34:37 / Claus Gittinger"
! !

!BaseNCoder class methodsFor:'instance creation'!

new
   self initializeMappings.
   ^ self basicNew initialize
! !

!BaseNCoder class methodsFor:'constants'!

lineLimit
    ^ 76. "/ RFC 2045 says: max 76 characters in one line

    "Created: / 21-03-2019 / 21:54:41 / Claus Gittinger"
! !

!BaseNCoder class methodsFor:'decoding'!

decodeAsString:encodedString
    "decode a base-n encoded string.
     We already expect a string instead of a ByteArray"

    ^ (self on:encodedString readStream) stringUpToEnd
! !

!BaseNCoder class methodsFor:'queries'!

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

    ^ self == BaseNCoder.
! !

!BaseNCoder methodsFor:'accessing'!

lineLimit:something
    "set the line length of the encoded output.
     Default is a line length of 76 characters.

     If nil, no line breaks will be done."

    lineLimit := something.
!

mapping:aString
    "the default mapping is
        0 -> A
        1 -> B
        ...
        63 -> =
     (see initializeMapping on the class side)
     This accessor allows for different mappings to be used."

    mapping := aString.
    reverseMapping := self class reverseMappingFor:mapping.

    "
     |encoded decoded|

     encoded := Base64Coder encode:'hello world'.    'aGVsbG8gd29ybGQ='.
     decoded := Base64Coder decode:encoded.    
     self assert:(decoded asString = 'hello world').
    "

    "
     |encoded decoded|

     encoded := Base64Coder new 
                    mapping:'A0B1C2D3E4F5G6H7I8J9K+L/M=NaObPcQdReSfTgUhViWjXkYlZmnopqrstuvwxyz';
                    encodingOf:'hello world'.    'ND+WaDvQbpwZaDIz'.
     decoded := Base64Coder new
                    mapping:'A0B1C2D3E4F5G6H7I8J9K+L/M=NaObPcQdReSfTgUhViWjXkYlZmnopqrstuvwxyz'; 
                    decodingOf:encoded.    
     self assert:(decoded asString = 'hello world').
    "
! !

!BaseNCoder methodsFor:'decoding'!

decodingOf:aString
    stream := aString readStream.
    ^ self stringUpToEnd 
!

next
    "answer the next decoded byte"

    |b|

    peekByte notNil ifTrue:[
        b := peekByte.
        peekByte := nil.
        ^ b
    ].
    ^ self basicNext.
!

next:count
    "return the next count bytes of the stream as ByteArray"

    |answerStream 
     cnt  "{ Class: SmallInteger }" |

    cnt := count.
    answerStream := WriteStream on:(ByteArray new:cnt).
    answerStream signalAtEnd:true.
    1 to:cnt do:[:index |
        |next|

        next := self next.
        next isNil ifTrue:[
            "if next did not raise EndOfStreamError, we have to do it"
            EndOfStreamError raiseRequestFrom:self.
            "if you proceed, you get what we have already collected"
            ^ answerStream contents
        ].
        answerStream nextPut:next.
    ].
    ^ answerStream contents
!

peek
    "answer the next decoded byte. Do not consume this byte"

    peekByte isNil ifTrue:[
        peekByte := self basicNext.
    ].
    ^ peekByte
! !

!BaseNCoder methodsFor:'encoding'!

encodingOf:anObject with:aParameter
    lineLimit := aParameter.
    ^ super encodingOf:anObject with:aParameter

    "Created: / 21-03-2019 / 22:01:20 / Claus Gittinger"
!

visitByteArray:aByteArray with:aParameter 
    ^ self
        nextPutBytes:aByteArray;
        flush.

    "
      Base64Coder encodingOf:#[1 2 3 4 5 6 255]
    "
!

visitObject:anObject with:aParameter
    "not defined. Use nextPut or nextPutAll:.
     Could encode the printString here"

    ^ self shouldNotImplement
!

visitStream:aStream with:aParameter
    aStream copyToEndInto:self.
    self flush.

    "
      Base64Coder encodingOf:#[1 2 3 4 5 6 255]
      Base64Coder encodingOf:#[1 2 3 4 5 6 255] readStream
    "
!

visitString:aString with:aParameter 
    ^ self
        nextPutAll:aString;
        flush.

    "
      |encoded decoded decoder|

      encoded := Base64Coder encode:'hello world'.  
      decoded := #[] writeStream.
      decoder := Base64Coder on:encoded readStream.
      [decoder atEnd] whileFalse:[
          decoded nextPut:(decoder next).
      ].
      decoded := decoded contents.
      decoded asString.    
    "
! !

!BaseNCoder methodsFor:'initialization'!

emptyWriteStream
    "answer an empty stream. We encode as string"
    
    ^ WriteStream on:(String new:64)
!

initialize

    <modifier: #super> "must be called if redefined"

    buffer := bits := charCount := 0.
    lineLimit := 76.   "RFC 2045 says: max 76 characters in one line"
    atEnd := false.

    mapping := self class mapping.
    reverseMapping := self class reverseMapping.

    "Modified: / 08-02-2017 / 00:33:07 / cg"
    "Modified: / 30-09-2018 / 15:29:41 / Claus Gittinger"
! !

!BaseNCoder methodsFor:'misc'!

reset
    "reset to initial state"

    super reset.
    buffer := bits := charCount := 0.
    atEnd := false.
    peekByte := nil.
! !

!BaseNCoder methodsFor:'private'!

basicNext
    "answer the next decoded byte. 
     No peekByte handling is done here."

    |b|

    bits == 0 ifTrue:[
        self fillBuffer.
        bits == 0 ifTrue:[
            ^ stream pastEndRead.
        ]
    ].
    b := (buffer bitShift:(8 - bits)) bitAnd:16rFF.
    bits := bits - 8.

    ^ b.
! !

!BaseNCoder methodsFor:'queries'!

atEnd
    "answer true, if no more bytes can be read"

    bits == 0 ifTrue:[
        atEnd ifTrue:[^ true].
        self fillBuffer.
        bits == 0 ifTrue:[^ true].
    ].
    ^ false.
!

binary
    "switch to binary mode - nothing is done here.
     Defined for compatibility with ExternalStream."

    ^ self
!

binary:beBinaryBool
    "ExternalStream protocol compatibility"

    ^ false         "/ no-op, I am not in binary mode

    "Created: / 13-03-2019 / 19:15:17 / Stefan Vogel"
!

isStream
    "we simulate a stream"

    ^ true
! !

!BaseNCoder methodsFor:'stream compatibility'!

bufferSizeForBulkCopy
    ^ 1024

    "Created: / 14-03-2019 / 12:58:47 / Stefan Vogel"
!

nextByte
    "ExternalStream compatibility"

    ^ self next

    "Created: / 27-03-2019 / 23:39:24 / stefan"
!

nextBytes:count into:anObject
    "read the next count bytes into an object and return the number of
     bytes read. On EOF, 0 is returned.
     If the receiver is some socket/pipe-like stream, an exception
     is raised if the connection is broken.

     The object must have non-pointer indexed instvars (i.e. it must be
     a ByteArray, String, Float- or DoubleArray).
     If anObject is a string or byteArray and reused, this provides the
     fastest possible physical I/O (since no new objects are allocated).

     Use with care - non object oriented i/o.
     Warning: in general, you cannot use this method to pass data from other
     architectures since it does not care for byte order or float representation."

    ^ self nextBytes:count into:anObject startingAt:1

    "Created: / 27-03-2019 / 23:37:31 / stefan"
!

nextBytes:numBytes into:anObject startingAt:initialIndex
    "copy bytes into anObject starting at offset"

    |n "{Class: SmallInteger }"|

    n := 0.

    [n ~= numBytes and:[self atEnd not]] whileTrue:[
        anObject byteAt:initialIndex+n put:self next.
        n := n + 1.
    ].
    ^ n

    "Created: / 27-03-2019 / 23:36:59 / stefan"
!

nextBytesInto:anObject startingAt:initialIndex
    "copy bytes into anObject starting at offset"

    |n "{Class: SmallInteger }"|

    n := 0.

    [self atEnd] whileFalse:[
        anObject byteAt:initialIndex+n put:self next.
        n := n + 1.
    ].
    ^ n

    "Modified: / 27-03-2019 / 23:48:16 / stefan"
!

nextInt32MSB:msbFlag
    "return a signed long (4 bytes) from the stream.
     The receiver must support reading of binary bytes.

     The msbFlag argument controls if the integer is to be read with
     most-significant-byte-first (true) or least-first (false).
     This interface is provided to allow talking to external programs,
     where it's known that the byte order is some definite one.
     If you don't care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order.

     1-to-1 copy from Stream"

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

    b1 := self nextByte.
    b2 := self nextByte.
    b3 := self nextByte.
    b4 := self nextByte.

    msbFlag ifTrue:[
        "most significant first"
        uval := (b1 bitShift:8) bitOr:b2.
        uval := (uval bitShift:8) bitOr:b3.
        val := (uval bitShift:8) bitOr:b4.
    ] ifFalse:[
        "least significant first"
        uval := (b4 bitShift:8) bitOr:b3.
        uval := (uval bitShift:8) bitOr:b2.
        val := (uval bitShift:8) bitOr:b1.
    ].
    "change from unsigned 0..FFFFFFFF to signed -80000000..7FFFFFFF"

    val >= 16r80000000 ifTrue:[
      ^ val - 16r100000000
    ].
    ^ val

    "
     |bytes s|

     bytes := #[16rFF 16rFF 16rFF 16rFF].
     s := bytes readStream.
     Transcript showCR:(s nextInt32MSB:true).
     s reset.
     Transcript showCR:(s nextInt32MSB:false).

     bytes := #[16r12 16r34 16r56 16r78].
     s := bytes readStream.
     Transcript showCR:(s nextInt32MSB:true).
     s reset.
     Transcript showCR:(s nextInt32MSB:false).

     bytes := #[16r89 16rab 16rcd 16ref].
     s := bytes readStream.
     Transcript showCR:(s nextInt32MSB:true).
     s reset.
     Transcript showCR:(s nextInt32MSB:false).
    "

    "Created: / 27-03-2019 / 23:38:32 / stefan"
!

nextPut:aByte
    "encode aByte on the output stream.
     Answer aByte"

    self nextPutByte:aByte asInteger.
    ^ aByte
!

nextPutAll:aCollection startingAt:first to:last
    "append the elements with index from first to last
     of the argument, aCollection onto the receiver."

    aCollection from:first to:last do:[:element |
        self nextPutByte:element
    ].

!

nextPutBytes:aCollectionOfBytes
    "encode all objects from the argument"

    aCollectionOfBytes do:[:o |
        self nextPutByte:o
    ]
!

skip:numberToSkip
    "skip numberToSkip objects, return the receiver.
     1-to-1 copy from Stream."

    "don't know how to unread ..."
    numberToSkip < 0 ifTrue:[
        PositionError raiseRequest.
        ^ self
    ].
    numberToSkip timesRepeat:[self next]

    "Created: / 27-03-2019 / 23:43:26 / stefan"
!

stringUpToEnd
    "return a collection of the elements up-to the end"

    |answerStream|

    answerStream := WriteStream on:(String new:128).
    peekByte notNil ifTrue:[
        answerStream nextPut:(Character codePoint:peekByte).
        peekByte := nil.
    ].
    [
        [bits >= 8] whileTrue:[
            answerStream nextPut:(Character codePoint:((buffer bitShift:(8 - bits)) bitAnd:16rFF)).
            bits := bits - 8.
        ].
        atEnd ifTrue:[
            bits ~~ 0 ifTrue:[
                answerStream nextPut:(Character codePoint:(buffer bitAnd:16rFF)).
                bits := 0.
            ]
        ] ifFalse:[
            self fillBuffer.
        ].
    ] doWhile:[bits > 0].

    ^ answerStream contents
!

upToEnd
    "return a collection of the elements up-to the end"

    |answerStream|

    answerStream := WriteStream on:(ByteArray new:128).
    peekByte notNil ifTrue:[
        answerStream nextPut:peekByte.
        peekByte := nil.
    ].
    [
        [bits >= 8] whileTrue:[
            answerStream nextPut:((buffer bitShift:(8 - bits)) bitAnd:16rFF).
            bits := bits - 8.
        ].
        atEnd ifFalse:[
            self fillBuffer.
        ].
    ] doWhile:[bits > 0].

    ^ answerStream contents

    "Modified: / 30-09-2018 / 16:37:03 / Claus Gittinger"
! !

!BaseNCoder methodsFor:'subclass responsibility'!

fillBuffer
    "fill buffer with next n characters each representing m bits"

    ^ self subclassResponsibility.
!

flush
    "flush the remaining bits of buffer. 
     The number of bits in buffer is not a multiple of m, so we pad
     the buffer and signal that padding has been done via $= characters."

    ^ self subclassResponsibility.
!

nextPutByte:aByte
    "encode aByte on the output stream"

    ^ self subclassResponsibility.
! !

!BaseNCoder class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !