SunReader.st
author claus
Sun, 09 Jan 1994 22:53:13 +0100
changeset 18 5a1262eeb9d7
parent 16 42d4754a035f
child 21 66b31c91177f
permissions -rw-r--r--
*** empty log message ***

"
 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

$Header: /cvs/stx/stx/libview2/Attic/SunReader.st,v 1.5 1994-01-08 17:16:04 claus Exp $
written Summer 91 by claus
'!

!SunRasterReader class methodsFor:'testing'!

isValidImageFile:aFileName
    "return true, if aFileName contains a sunraster image"

    |inStream|

    inStream := self streamReadingFile:aFileName.
    inStream isNil ifTrue:[^ false].

    "try sun raster"
    inStream binary.
    ((inStream nextWord = 16r59A6) 
    and:[inStream nextWord = 16r6A95]) ifTrue: [
        inStream close.
        ^ true
    ].

    "try sun bitmap image format"
    inStream text.
    inStream reset.
    (inStream skipToAll: 'idth') isNil ifTrue: [
        inStream close.
        ^ false
    ].
    inStream skip: 5; skipSeparators.
    (Integer readFrom: inStream) <= 0 ifTrue: [
        inStream close.
        ^ false
    ].

    (inStream skipToAll: 'eight') isNil ifTrue: [
        inStream close.
        ^ false
    ].
    inStream skip: 6; skipSeparators.
    (Integer readFrom: inStream) <= 0 ifTrue: [
        inStream close.
        ^ false
    ].

    inStream close.
    ^ true
! !

!SunRasterReader methodsFor:'reading from file'!

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

    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].

    inStream binary.

    ((inStream nextWord = 16r59A6) 
    and:[inStream nextWord = 16r6A95]) ifFalse: [
        inStream close.
        ^ self fromSunIconFile:aFilename
    ].

    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 uninitializedNew:mapLen.
        gMap := ByteArray uninitializedNew:mapLen.
        bMap := ByteArray uninitializedNew:mapLen.
        inStream nextBytes:mapLen into:rMap.
        inStream nextBytes:mapLen into:gMap.
        inStream nextBytes:mapLen into:bMap.

        data := ByteArray uninitializedNew:(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 uninitializedNew:(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 uninitializedNew: 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'"
!

fromSunIconFile: aFilename 
    | index word |

    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].

    (inStream skipToAll: 'idth') isNil ifTrue: [
        'Not a Sun Raster/Icon File' printNewline.
        ^nil
    ].
    inStream skip: 5; skipSeparators.
    (width := Integer readFrom: inStream) <= 0 ifTrue: [^nil].

    (inStream skipToAll: 'eight') isNil ifTrue: [^nil].
    inStream skip: 6; skipSeparators.
    (height := Integer readFrom: inStream) <= 0 ifTrue: [^nil].

    data := ByteArray uninitializedNew:((width + 7 // 8) * height).
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).

    index := 0.
    1 to: height do: [:row |
       1 to: (width + 15 // 16) do: [:col |
           "rows are rounded up to next multiple of 16 bits"
           (inStream skipToAll: '0x') isNil ifTrue: [^nil]. inStream skip: 2.
           word := Integer readFrom: inStream radix: 16.
           data at: (index _ index + 1) put: (word bitShift:-8).
           data at: (index _ index + 1) put: (word bitAnd:16rFF).
       ]
    ].
    inStream close.
! !