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

Bob Arning arning at charm.net
Fri Jun 9 15:52:50 UTC 2000


On Fri, 9 Jun 2000 12:08:17 Mats Nygren <nygren at sics.se> wrote:
>as you would have guessed I want to take look at Dan I's work. The
>attachment has a .gz so gunzip comes to mind. The text pane of the
>file lister looks as follows:
>
>------------------------------------------
>(This file must be converted with BinHex 4.0)
>
>:&80[ [snip]
>
>uncompress says (something equivalent to) this is not a gzipped file.
>
>I guess this is a problem with different Squeak-ports. I'm running on
>Linux. I received the attachment with Celeste. (what else is there?)
>It seems most people are using Mac's and whateverItIsCalledYouKnowTheOne.
>So what do I do?
>
>Perhaps someone can make this available in another form somewhere. I
>dont usually have problems with attachments gzipped or not.

Mats,

Here is some code that will untangle BinHex. After filing in, you can evaluate

	(GZipReadStream on: (BinHexConverter new decode: (ReadStream on: XXXXX))) upToEnd

where XXXXX is a String containing the data in the attachment.

Cheers,
Bob

===== code follows =====
'From Squeak2.8alpha of 13 January 2000 [latest update: #2299] on 9 June 2000 at 11:47:59 am'!
"Change Set:		BinHexConverter
Date:			9 June 2000
Author:			Bob Arning

Decodes BinHex files 

	BinHexConverter new decode: (ReadStream on: aString)

"!

Object subclass: #BinHexConverter
	instanceVariableNames: 'outputStream repeating '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Streams'!

!BinHexConverter methodsFor: 'as yet unclassified' stamp: 'RAA 6/9/2000 11:36'!
convertToFile: decodedStream

    | nameLength headerData fileName fileType creator finderFlags
        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)
    +--------------------------------------+--+
"! !

!BinHexConverter methodsFor: 'as yet unclassified' stamp: 'RAA 7/16/1998 18:16'!
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
! !

!BinHexConverter methodsFor: 'as yet unclassified' stamp: 'RAA 7/16/1998 17:20'!
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
            ].
        ].
! !

!BinHexConverter methodsFor: 'as yet unclassified' stamp: 'RAA 7/16/1998 18:23'!
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! !

!BinHexConverter methodsFor: 'as yet unclassified' stamp: 'RAA 7/16/1998 18:32'!
verifyCRCFor: input length: dataLength

    | crc crcComputer expectedCRC |

    crcComputer := [ :byte |
        8 timesRepeat: [
            crc := (crc << 1) bitOr: (byte >> 7).
            (crc bitAnd: 16r10000) = 0 ifFalse:
            [
                crc := (crc bitAnd: 16rFFFF) bitXor: 16r1021.
            ].
            byte := (byte << 1) bitAnd: 16rFF.
        ].
    ].
    crc := 0.
    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 ifTrue: [
		^true
    ] ifFalse: [
        self halt.
       ^false
    ].! !





More information about the Squeak-dev mailing list