Base64Coder.st
author Stefan Vogel <sv@exept.de>
Thu, 05 Sep 2002 15:23:53 +0200
changeset 1084 9d51967037ad
parent 1078 698bd52be7d1
child 1111 2a64f0fe418a
permissions -rw-r--r--
Fix for whitespace and end of line and multiple of 4 characters

"{ Package: 'stx:libbasic2' }"

ObjectCoder subclass:#Base64Coder
	instanceVariableNames:'buffer bits charCount atEnd'
	classVariableNames:'Base64Mapping Base64ReverseMapping'
	poolDictionaries:''
	category:'System-Storage'
!

!Base64Coder class methodsFor:'documentation'!

documentation
"
    Instances of this class perform Base64 en- and decoding as defined in RFC 2045
    3 bytes are mapped to 4 characters, representing 6 bits each.

    [author:]
        Stefan Vogel

    [see also:]

    [instance variables:]
        buffer          SmallInteger   Up to 24 bits of 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:]
        Base64Mapping         String   Mapping from bytes (with 6 valid bits)   
                                       to Base64 characters
        Base64ReverseMapping  Array    Mapping from Base64 characters to 6-bit-Bytes
"
!

examples
"

                                                                [exBegin]
   |coder|

   coder := Base64Coder on:'' writeStream.
   coder nextPutAll:#[0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19].
   coder flush.
   coder contents inspect.
   coder reset.
   coder nextPut:254.
   coder contents inspect.
                                                                [exEnd]

                                                                [exBegin]
   |coder coder1|

   coder := Base64Coder on:'' writeStream.
   coder nextPutAll:#[0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20].
   coder flush.

   coder1 := Base64Coder on:coder contents readStream.
   [coder1 atEnd] whileFalse:[
      Transcript show:coder1 next
   ].
   Transcript cr.
                                                                [exEnd]
"
! !

!Base64Coder class methodsFor:'initialization'!

initialize
    "initialize class variables"

    "64 characters representing the 6-bit values from 0-63 and one pad character"
    Base64Mapping := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/='.
    Base64ReverseMapping := ByteArray new:256 withAll:255.
    Base64Mapping keysAndValuesDo:[:idx :char|
        Base64ReverseMapping at:char asciiValue put:idx-1.
    ].

    "
     self initialize
    "
! !

!Base64Coder class methodsFor:'instance creation'!

new
   ^ self basicNew initialize
! !

!Base64Coder methodsFor:'decoding'!

fillBuffer
    "fill buffer with next 4 characters each representing 6 bits"

    |b shift|

    buffer := 0.
    bits := 0.
    [
        "read next valid Base64 character, skip invalid characters"
        [
            b := stream next.
            b isNil ifTrue:[ "end of stream"
                atEnd := true.
                ^ self.
            ].
            b := Base64ReverseMapping at:b asciiValue.
        ] doWhile:[b == 255].

        b == 64 ifTrue:[
            "got #=, end of Base64 string has been reached"
            atEnd := true.
            bits == 12 ifTrue:[
                "data has been padded to 12, skip 4 bits"
                shift := -4.
            ] ifFalse:[
                "data has been padded to 18, skip 2 bits"
                shift := -2.
            ].
            bits := bits + shift.
            buffer := buffer bitShift:shift.
        ] ifFalse:[
            "got valid Base64 character, append to buffer"
            buffer := (buffer bitShift:6) bitOr:b.
            bits := bits + 6.
        ].
    ] doWhile:[bits ~~ 24 and:[atEnd not]].
!

next
    "answer the next decoded byte"

    |b|

    bits == 0 ifTrue:[
        self fillBuffer.
        bits == 0 ifTrue:[
            ^ stream class endOfStreamSignal raiseRequest.
        ]
    ].

    b := (buffer bitShift:(8 - bits)) bitAnd:16rFF.
    bits := bits - 8.

    ^ b.
! !

!Base64Coder methodsFor:'encoding'!

encodeByteArray:aByteArray with:aParameter

    ^ self nextPutAll:aByteArray; flush.

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

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

    ^ self shouldNotImplement
!

encodeString:aString with:aParameter

    ^ self nextPutAll:aString asByteArray; flush.

    "
      self encodingOf:'hello world'
    "
!

nextPut:aByte
    "encode aByte on the output stream"

    |b1 b2 b3 b4|

    buffer := (buffer bitShift:8) bitOr:aByte.
    bits := bits + 8.
    bits == 24 ifTrue:[
        b4 := buffer bitAnd:16r3F.
        b3 := (buffer bitShift:-6)  bitAnd:16r3F.
        b2 := (buffer bitShift:-12) bitAnd:16r3F.
        b1 := (buffer bitShift:-18) bitAnd:16r3F.
        buffer := bits := 0.
        stream nextPut:(Base64Mapping at:b1+1);
               nextPut:(Base64Mapping at:b2+1);
               nextPut:(Base64Mapping at:b3+1);
               nextPut:(Base64Mapping at:b4+1).

        "RFC 2045 says: max 76 characters in one line"
        charCount >= 68 ifTrue:[
            stream cr.
            charCount := 0.
        ] ifFalse:[
            charCount := charCount + 4.
        ]
    ].
! !

!Base64Coder methodsFor:'initialization'!

emptyWriteStream
   "answer an empty stream. We encode as string"

   ^ WriteStream on:(String new:64)
!

initialize

    buffer := bits := charCount := 0.
    atEnd := false.
! !

!Base64Coder methodsFor:'misc'!

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

   |b1 b2 b3 b4|

   bits == 0 ifTrue:[
        "buffer is empty, nothing to do"
        ^ self.
   ].

   bits == 8 ifTrue:[
        buffer := buffer bitShift:4.
        b4 := b3 := 64. "pad with '=='"
        b1 := (buffer bitShift:-6) bitAnd:16r3F.
        b2 := buffer bitAnd:16r3F.
   ] ifFalse:[bits = 16 ifTrue:[
        buffer := buffer bitShift:2.
        b4 := 64.        "pad with '='"
        b3 := buffer bitAnd:16r3F.
        b2 := (buffer bitShift:-6)  bitAnd:16r3F.
        b1 := (buffer bitShift:-12) bitAnd:16r3F.
   ]].
   bits := buffer := 0.

   stream nextPut:(Base64Mapping at:b1+1);
          nextPut:(Base64Mapping at:b2+1);
          nextPut:(Base64Mapping at:b3+1);
          nextPut:(Base64Mapping at:b4+1).
!

reset
    "reset to initial state"

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

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

!Base64Coder methodsFor:'stream compatibility'!

upToEnd
    "return a collection of the elements up-to the end.
     Return nil if the stream-end is reached before."

    |answerStream|

    answerStream := WriteStream on:(ByteArray new:128).
    [self atEnd] whileFalse:[
        answerStream nextPut:self next
    ].

    ^ answerStream contents
! !

!Base64Coder class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Base64Coder.st,v 1.4 2002-09-05 13:23:53 stefan Exp $'
! !
Base64Coder initialize!