XPMReader.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Jan 1997 04:19:07 +0100
changeset 378 3924b37b0ea4
parent 316 d39f3f8f7627
child 384 f139a7fc423b
permissions -rw-r--r--
added literalEncodings

"
 COPYRIGHT (c) 1994 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:#XPMReader
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Support'
!

!XPMReader  class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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.
"
!

documentation
"
    this class provides methods for loading x-pixmap-file (xpm) images.

    These images are used (in X) for palette images (see ctwm or hp-vue for a lot
    of them). 
    The code here is a hack - it may not work for all images 
    (it works for the testfiles I got here).

    Limitations: 
        only reads the full-color specification, ignoring monochrome
        and greyscale info.

        Can only handle single-character index.

        Only understands single-word color names (i.e. names with spaces 
        are not supported)

        Image writing is not (yet) supported

    Suggestions: adapt & use the XPM library here.


    [See also:]
        Image Form Icon
        BlitImageReader FaceReader GIFReader JPEGReader PBMReader PCXReader 
        ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
        XBMReader XWDReader 
"
! !

!XPMReader  class methodsFor:'initialization'!

initialize
    "tell Image-class, that a new fileReader is present
     for the '.xpm' extension."

    Image fileFormats at:'.xpm'  put:self.
! !

!XPMReader  class methodsFor:'testing'!

isValidImageFile:aFileName
    "return true, if aFileName contains an x-bitmap-file image"

    |line inStream |

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

    line := inStream nextLine.
    inStream close.
    line isNil ifTrue:[^ false].
    (line startsWith:'/* XPM') ifFalse:[^ false].
    ^ true

    "
     XPMReader isValidImageFile:'bitmaps/magtape.xpm'    
     XPMReader isValidImageFile:'bitmaps/ljet.xpm'      
     XPMReader isValidImageFile:'bitmaps/garfield.gif' 
    " 
! !

!XPMReader methodsFor:'reading from file'!

colorNameFrom:aStream
    "read either a color-name or value specified in X-notation
     (#rrggbb where rr, gg and bb are 2-digit hex numbers)"

    |s|

    aStream peek == $# ifTrue:[
	aStream next.
	s := '#'.
    ] ifFalse:[
	s := ''.
    ].
    [aStream peek isLetterOrDigit] whileTrue:[
	s := s copyWith:aStream next
    ].
    ^ s
!

fromStream:aStream
    "read an XPM-image from aStream. Return the receiver 
     (with all relevant instance variables set for the image) 
     or nil on error"

    |line 
     srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     colorName colorMapSize redMap greenMap blueMap
     charsPerPixel xlation s bitsPerPixel char lineDone maskPixelValue|

    inStream := aStream.

    line := aStream nextLine.
    (line notNil and:[line startsWith:'/* XPM']) ifFalse:[
        'XPM: format error (expected XPM)' errorPrintNL.
        ^ nil
    ].

    line := aStream nextLine.
    [line notNil and:[(line startsWith:'/*') or:[line isBlank]]] whileTrue:[
        line := aStream nextLine.
    ].
    (line notNil and:[line startsWith:'static char']) ifFalse:[
        'XPM: format error (expected static char)' errorPrintNL.
        ^ nil
    ].
    line := aStream nextLine.
    (line notNil and:[line startsWith:'/*']) ifTrue:[
        [line notNil 
         and:[(line startsWith:'/*') or:[line startsWith:' *']]] whileTrue:[
            line := aStream nextLine.
        ].
    ].
    (line notNil and:[line startsWith:'"']) ifFalse:[
        'XPM: format error (expected "ww hh nn mm)' errorPrintNL.
        ^ nil
    ].
    s := ReadStream on:line.
    s next.  "skip quote"
    width := Integer readFrom:s.
    height := Integer readFrom:s.
    colorMapSize := Integer readFrom:s.
    charsPerPixel := Integer readFrom:s.
    charsPerPixel ~~ 1 ifTrue:[
        'XPM: can only handle single-character xpm-files' errorPrintNL.
        ^ nil
    ].
    xlation := Array new:256.

    redMap := ByteArray new:colorMapSize.
    greenMap := ByteArray new:colorMapSize.
    blueMap := ByteArray new:colorMapSize.
    colorMap := Colormap redVector:redMap greenVector:greenMap blueVector:blueMap.

    1 to:colorMapSize do:[:colorIndex |
        |index line color t|

        line := aStream nextLine.
        [line notNil and:[line startsWith:'/*']] whileTrue:[
            line := aStream nextLine.
        ].
        (line notNil and:[line startsWith:'"']) ifFalse:[
            'XPM: format error (expected color spec)' errorPrintNL.
            ^ nil
        ].

        s := ReadStream on:line.
        s next. "skip quote"
        index := s next asciiValue.
        xlation at:index put:colorIndex - 1.

        lineDone := false.
        [lineDone] whileFalse:[
            s skipSeparators.
            char := s peek.
            char == $" ifTrue:[
                lineDone := true
            ] ifFalse:[
                char == $s ifTrue:[
                    "
                     symbolic name
                    "
                    s next.
                    s skipSeparators.
                    self colorNameFrom:s.  
                    s skipSeparators.
                ] ifFalse:[
                    char == $m ifTrue:[
                        "
                         monochrome data
                        "
                        s next.
                        s skipSeparators.
                        self colorNameFrom:s.
                        s skipSeparators.
                    ] ifFalse:[
                        (char == $g) ifTrue:[
                            "
                             greyscale data
                            "
                            s next.
                            s peek == 4 ifTrue:[s next].
                            s skipSeparators.
                            self colorNameFrom:s.
                            s skipSeparators.
                        ] ifFalse:[
                            (char == $c) ifTrue:[
                                "
                                 color data
                                "
                                s next.
                                s skipSeparators.
                                colorName := self colorNameFrom:s.
                                s skipSeparators.
                            ] ifFalse:[
                                'XPM: format error got: ' errorPrint.
"/                                char errorPrint. '(' errorPrint. char asciiValue printString errorPrint.
"/                                '); ' errorPrint.
                                 '(expected ''c'',''m'',''g'' or ''s'')' errorPrintNL.
                                ^ nil
                            ].
                        ]
                    ]
                ]
            ].
        ].
        ((colorName = 'none') or:[colorName = 'None']) ifTrue:[
            color := Color noColor. "/ white
            redMap at:colorIndex put:0.
            greenMap at:colorIndex put:0.
            blueMap at:colorIndex put:0.
            maskPixelValue := colorIndex-1.
        ] ifFalse:[
            color := Color name:colorName.
            redMap at:colorIndex put:(color red asFloat * 255.0 // 100).
            greenMap at:colorIndex put:(color green asFloat * 255.0 // 100).
            blueMap at:colorIndex put:(color blue asFloat * 255.0 // 100).
        ].
    ].

    "actually, could make it an image with less depth most of the time ..."

"
    bitsPerPixel := ((colorMapSize - 1) log:2) truncated + 1.
"
    bitsPerPixel := 8.
    data := ByteArray new:(width * height).

    dstIndex := 1.
    1 to:height do:[:row |
        line := aStream nextLine withoutSpaces.
        [line notNil and:[line startsWith:'/*']] whileTrue:[
            line := aStream nextLine withoutSpaces.
        ].
        (line notNil and:[line startsWith:'"']) ifFalse:[
            'XPM: format error (expected pixels)' errorPrintNL.
            ^ nil
        ].
        srcIndex := 2.
        1 to: width do:[:col |
            |char|

            char := line at:srcIndex.
            data at:dstIndex put:(xlation at:char asciiValue).
            srcIndex := srcIndex + 1.
            dstIndex := dstIndex + 1
        ]
    ].

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := Array with:bitsPerPixel.

    maskPixelValue notNil ifTrue:[
        self buildMaskFromColor:maskPixelValue
    ].

    "
     XPMReader fromStream:('bitmaps/ljet.xpm' asFilename readStream)
     XPMReader fromStream:('bitmaps/magtape.xpm' asFilename readStream)
     XPMReader fromStream:('bitmaps/pixmap.xpm' asFilename readStream) 
     XPMReader fromStream:('bitmaps/SBrowser.xbm' asFilename readStream)
    "

    "Created: 24.9.1995 / 06:20:06 / claus"
    "Modified: 24.9.1995 / 07:07:33 / claus"
    "Modified: 5.7.1996 / 17:27:59 / stefan"
! !

!XPMReader  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.18 1996-07-05 21:09:05 stefan Exp $'
! !
XPMReader initialize!