BinHex decoding - Re: attachment problem - from: When in doubt, try it out...

Les Tyrrell tyrrell at canis.uiuc.edu
Fri Jun 9 16:42:17 UTC 2000


( ... The VW version is attached ) er, no it isn't.  Here it is...

( after you work in Smalltalk too long, you develop a twitchy mouse select button finger... )

- les
-------------- next part --------------
'From VisualWorks?, Release 3.0 of February 5, 1998 on June 9, 2000 at 9:38:30 am'!

Object subclass: #BinHexConverter
	instanceVariableNames: 'outputStream repeating fileName fileType finderFlags creator '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'EMail-CoDecs'!
BinHexConverter comment:
'Written by Bob Arning'!


!BinHexConverter methodsFor: 'decode'!

convertToFile: decodedStream

    | nameLength headerData dataStart dataLength resourceStart resourceLength allCRCValuesMatched |

    allCRCValuesMatched := true.
    decodedStream reset.
    nameLength := decodedStream peek asciiValue.
    headerData := ReadStream on: (decodedStream next: 1 + nameLength + 1 + 20).
    dataStart := decodedStream position.   " be sure we know where data starts"

    "pick out pieces of header that we need"
    headerData reset.
    nameLength := headerData next asciiValue.
    fileName := headerData next: nameLength.
    headerData next.
 
    fileType := headerData next: 4.
    creator := headerData next: 4.
    finderFlags := self nextNumber: 2 fromCharacterStream: headerData.
    dataLength :=  self nextNumber: 4 fromCharacterStream: headerData.
    resourceLength := self nextNumber: 4 fromCharacterStream: headerData.
    "headerCRC := "self nextNumber: 2 fromCharacterStream: headerData.
    
    "check CRC on header info"
    headerData reset.
    allCRCValuesMatched := self verifyCRCFor: headerData length: headerData contents size - 2.
    
    "check CRC on data fork (if any)"
    dataLength > 0 ifTrue: [
        allCRCValuesMatched := allCRCValuesMatched and:
             [self verifyCRCFor: decodedStream length: dataLength].
    ].
    
    "check CRC on resource fork (if any)"
    resourceStart := dataStart + dataLength + 2.
    decodedStream position: resourceStart.
    resourceLength > 0 ifTrue: [
        allCRCValuesMatched := allCRCValuesMatched and:
            [self verifyCRCFor: decodedStream length: resourceLength].
    ].
    
    allCRCValuesMatched ifTrue:
    [          
                decodedStream position: dataStart.
                ^decodedStream next: dataLength
    ] ifFalse: [
        self halt.
    ].
        
"So the decoded data between the first and last colon (:) looks like:

     1       n       4    4    2    4    4   2    (length)
    +-+---------+-+----+----+----+----+----+--+
    |n| name... |0|TYPE|AUTH|FLAG|DLEN|RLEN|HC|   (contents)
    +-+---------+-+----+----+----+----+----+--+

            DLEN                             2    (length)
    +--------------------------------------+--+
    |    DATA FORK                         |DC|   (contents)
    +--------------------------------------+--+

            RLEN                             2    (length)
    +--------------------------------------+--+
    |    RESOURCE FORK                     |RC|   (contents)
    +--------------------------------------+--+
"!

decode: aStream

    | done startFlag decoderString decodeArray accumulator accumCount c |

        repeating := false.

    aStream reset.
    outputStream := ReadWriteStream on: ''.
    decoderString := '!!"#$%&''()*+,-012345689 at ABCDEFGHIJKLMNPQRSTUVXYZ[`abcdefhijklmpqr'.
    (decodeArray := Array new: 256) atAllPut: 0.
    1 to: decoderString size do: [ :i |
        decodeArray at: (decoderString at: i) asciiValue + 1 put: i  - 1.
    ].
    startFlag := '(This file must be converted with BinHex'.
    accumulator := 0.
    accumCount := 0.
    
    [aStream atEnd or: [aStream nextLine beginsWith: startFlag]] whileFalse.
    aStream upTo: $:.
    done := false.
    [done or: [aStream atEnd]] whileFalse: [
        c := aStream next.
        c = $: ifTrue: [ done := true]. 
        c isSeparator ifFalse: [
            accumulator := (accumulator << 6) + (decodeArray at: c asciiValue + 1).
            (accumCount := accumCount + 1) = 4 ifTrue: [
                self 
                    emit: (accumulator >> 16 bitAnd: 16rFF);
                    emit: (accumulator >> 8 bitAnd: 16rFF);
                    emit: (accumulator bitAnd: 16rFF).
                accumulator := 0.
                accumCount := 0.
            ].
        ].
    ].
        ^self convertToFile: outputStream!

emit: aByte

        repeating ifTrue: [
            aByte = 0 ifTrue: [
                outputStream nextPut: 16r90 asCharacter
            ] ifFalse: [
                outputStream next: aByte - 1 put: outputStream last.
            ].
            repeating := false.
        ] ifFalse: [
            aByte = 16r90  ifTrue: [
                repeating := true
            ] ifFalse: [
                outputStream nextPut: aByte asCharacter
            ].
        ].!

nextNumber: n  fromCharacterStream: strm
        "Answer the next n bytes as a positive Integer or LargePositiveInteger."
        | s |
        s := 0.
        1 to: n do: 
                [:i | s := (s bitShift: 8) bitOr: strm next asciiValue].
        ^ s normalize!

verifyCRCFor: input length: dataLength

	| crc crcComputer expectedCRC byte |

	crc := 0.

	crcComputer := [ : inputByte |
		byte := inputByte.
		8 timesRepeat: [
			crc := (crc << 1) bitOr: (byte >> 7).
			( crc bitAnd: 16r10000 ) isZero
				ifFalse: [ crc := (crc bitAnd: 16rFFFF) bitXor: 16r1021 ].
			byte := (byte << 1) bitAnd: 16rFF.
			].
		].

	dataLength
		timesRepeat: [ crcComputer value: input next asciiValue ].

	crcComputer
		value: 0 ;
		value: 0.	 "place where crc ended up"

	expectedCRC := self nextNumber: 2 fromCharacterStream: input.

	^ crc = expectedCRC! !


More information about the Squeak-dev mailing list