SunRasterReader.st
author claus
Fri, 16 Jul 1993 11:42:12 +0200
changeset 0 3f9277473954
child 3 78aaa5408119
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1993 by Claus Gittinger
              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.
"

ImageReader subclass:#SunRasterReader
         instanceVariableNames:''
         classVariableNames:''
         poolDictionaries:''
         category:'Graphics-Support'
!

SunRasterReader comment:'

COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

this class provides methods for loading Sun Raster file images

%W% %E%
written Summer 91 by claus
'!

!SunRasterReader methodsFor:'reading from file'!

fromFile: aFilename 
    | rasterType mapType mapBytes imageWords form depth 
      rMap gMap bMap mapLen
      bits a b c index|

    inStream := FileStream readonlyFileNamed:aFilename.
    inStream isNil ifTrue:[
        'open error' printNewline. 
        ^ nil
    ].

    inStream binary.

    ((inStream nextWord = 16r59A6) 
    and:[inStream nextWord = 16r6A95]) ifFalse: [
"
    inStream nextLong = 16r59A66A95 ifFalse: [
"
        inStream close.
        self error: 'Not a Sun Raster File (bad magic number)'
    ].

    width := inStream nextLong.
    height := inStream nextLong.

    depth := inStream nextLong.
    inStream nextLong.   "Ignore the image length since I can't rely on it anyway."
    rasterType _ inStream nextLong.
    mapType := inStream nextLong.  "Ignore the raster maptype."
    mapBytes := inStream nextLong.  

    depth = 8 ifTrue: [
        mapLen := (mapBytes // 3).
        rMap := ByteArray new:mapLen.
        gMap := ByteArray new:mapLen.
        bMap := ByteArray new:mapLen.
        inStream nextBytes:mapLen into:rMap.
        inStream nextBytes:mapLen into:gMap.
        inStream nextBytes:mapLen into:bMap.

        data := ByteArray new:(width * height).
        inStream nextBytes:(width * height) into:data.

        photometric := #palette.
        samplesPerPixel := 1.
        bitsPerSample := #(8).
        colorMap := Array with:rMap with:gMap with:bMap.
        inStream close.
        ^ self
    ].
    depth ~~ 1 ifTrue: [
        inStream close.
        self error: 'Raster file is not monochrome'
    ].

    form := nil.

    inStream skip: mapBytes.  "Skip the color map."
    imageWords _ (width / 16) ceiling * height.
    data := ByteArray new:(imageWords * 2).

    (rasterType between: 0 and: 2) ifFalse: [
        inStream close.
        self error: 'Unknown raster file rasterType'
    ].

    (rasterType = 2)  ifFalse: [
        "no compression of bytes"
        inStream nextBytes:(imageWords * 2) into:data
    ] ifTrue: [ 
        "run length compression of bytes"

        bits _ ByteArray new: imageWords * 2.
        index := 1.
        a _ inStream next.
        [a notNil] whileTrue: [
            (a = 128) ifFalse: [
                bits at:index put: a.
                index := index + 1
            ] ifTrue: [
                b _ inStream next.
                b = 0 ifTrue: [
                    bits at:index put:128 .
                    index := index + 1
                ] ifFalse: [
                    c := inStream next.
                    1 to:(b+1) do:[:i |
                        bits at:index put:c.
                        index := index + 1
                    ]
                ]
            ].
            a _ inStream next
        ].
        1 to: imageWords do: [:i | form bitsWordAt: i put: (bits wordAt: i)]
    ].
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).
    inStream close

    "Image fromFile:'../fileIn/bitmaps/founders.im8'"
! !