Base64Coder.st
author Claus Gittinger <cg@exept.de>
Wed, 11 Jul 2007 16:05:31 +0200
changeset 1888 7113378d5a37
parent 1641 f708600ad7d9
child 1964 671b01812775
permissions -rw-r--r--
*** empty log message ***

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

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

!Base64Coder 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
"
    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]
   0 to:16 do:[:l |
        |coder decoder data encoding decoded|

        data := (0 to:l) asByteArray copyTo:l.
        coder := Base64Coder on:'' writeStream.
        coder nextPutAll:data.
        coder flush.

        encoding := coder contents.

        decoder := Base64Coder on:encoding readStream.
        decoded := decoder upToEnd.
        Transcript showCR:(data printString).
        Transcript show:' -> '; showCR:encoding.
        Transcript show:' ---> '; showCR:(decoded printString).
        self assert:(data = decoded).
   ].
                                                                [exEnd]
                                                                [exBegin]
   |data1 text data2|

   data1 := #[0 1 16r7F 16r80 16r81 16rFE 16rFF].
   text := Base64Coder encode:data1.
   data2 := Base64Coder decode:text.
   data2  
                                                                [exEnd]

                                                                [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 decoder|

   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.

   decoder := Base64Coder on:(coder contents readStream).
   [decoder atEnd] whileFalse:[
      Transcript show:decoder next
   ].
   Transcript cr.
                                                                [exEnd]
                                                                [exBegin]
   |coder|

   coder := Base64Coder on:'' writeStream.
   coder nextPutAll:(0 to:200) asByteArray.
   coder flush.

   Transcript showCR:(coder contents).
                                                                [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 codePoint put:idx-1.
    ].

    "
     self initialize
    "
! !

!Base64Coder class methodsFor:'instance creation'!

new
   ^ self basicNew initialize
! !

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

!Base64Coder methodsFor:'decoding'!

next
    "answer the next decoded byte"

    |b|

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

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

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

!Base64Coder methodsFor:'encoding'!

nextPut:aByte
    "encode aByte on the output stream"

    |b1 b2 b3 b4|

    buffer := (buffer bitShift:8) bitOr:aByte.
    bits := bits + 8.
    bits == 24 ifTrue:[
        "RFC 2045 says: max 76 characters in one line"
        (lineLimit notNil and:[charCount >= lineLimit]) ifTrue:[
            stream cr.
            charCount := 0.
        ].

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

        charCount := charCount + 4.
    ].
!

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

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

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

    "
      |encoded decoded decoder|

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

!Base64Coder methodsFor:'initialization'!

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

initialize

    buffer := bits := charCount := 0.
    lineLimit := 76.   "RFC 2045 says: max 76 characters in one line"
    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.

    "RFC 2045 says: max 76 characters in one line"
    (lineLimit notNil and:[charCount >= lineLimit]) ifTrue:[
        stream cr.
        charCount := 0.
    ].

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

reset
    "reset to initial state"

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

!Base64Coder methodsFor:'private'!

basicNext
    "answer the next decoded byte. 
     Not 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.
!

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

    |b shift tempBuffer "{Class: SmallInteger}"|

    tempBuffer := 0.
    bits := 0.
    [
        "read next valid Base64 character, skip invalid characters"
        [
            b := stream next.
            b isNil ifTrue:[ "end of stream"
                b := 64. "/ end-mark
            ] ifFalse:[
                b := Base64ReverseMapping at:b codePoint.
            ]
        ] 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:[bits == 18 ifTrue:[
                "data has been padded to 18, skip 2 bits"
                shift := -2.
            ] ifFalse:[
                shift := 0.
            ]].
            tempBuffer := tempBuffer bitShift:shift.
            bits := bits + shift.
        ] ifFalse:[
            "got valid Base64 character, append to buffer"
            tempBuffer := (tempBuffer bitShift:6) bitOr:b.
            bits := bits + 6.
        ].
    ] doWhile:[bits ~~ 24 and:[atEnd not]].

    buffer := tempBuffer.
! !

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

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

    ^ self
!

isStream
    "we simulate a stream"

    ^ true
! !

!Base64Coder methodsFor:'stream compatibility'!

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

    |off|

    off := offset.
    [self atEnd] whileFalse:[
        anObject at:off put:self next.
        off := off + 1.
    ].
    ^ off - offset
!

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.
        ].
        self fillBuffer.
    ] doWhile:[bits > 0].

    ^ answerStream contents
! !

!Base64Coder class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Base64Coder.st,v 1.18 2007-07-11 14:05:31 cg Exp $'
! !

Base64Coder initialize!