XPMReader.st
author claus
Fri, 05 Aug 1994 03:16:30 +0200
changeset 24 6bc436eb4c4a
parent 22 24b4aff428c0
child 28 8daff0234d2e
permissions -rw-r--r--
*** empty log message ***

"
 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-Support'
!

XPMReader comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.2 1994-08-05 01:16:30 claus Exp $
'!

!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.
"
!

version
"
$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.2 1994-08-05 01:16:30 claus Exp $
"
!

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.

        Does not (currently) handle none-colors (i.e. for image-masks).

        Save not supported

    Suggestions: adapt & use the XPM library here.
"
! !

!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 isAlphaNumeric] whileTrue:[
        s := s copyWith:aStream next
    ].
    ^ s
!

fromFile:aFileName
    "read an XPM-image from aFileName. 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|

    inStream := self class streamReadingFile:aFileName.
    inStream isNil ifTrue:[
        'XPM: file open error' errorPrintNL.
        ^ nil
    ].

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

    line := inStream nextLine.
    [line notNil and:[line startsWith:'/*']] whileTrue:[
        line := inStream nextLine.
    ].
    (line notNil and:[line startsWith:'static char']) ifFalse:[
        'XPM: format error (expected static char)' errorPrintNL.
        inStream close.
        ^ nil
    ].
    line := inStream nextLine.
    [line notNil and:[line startsWith:'/*']] whileTrue:[
        line := inStream nextLine.
    ].
    (line notNil and:[line startsWith:'"']) ifFalse:[
        'XPM: format error (expected "ww hh nn mm)' errorPrintNL.
        inStream close.
        ^ 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 := Array new:colorMapSize.
    greenMap := Array new:colorMapSize.
    blueMap := Array new:colorMapSize.
    colorMap := Array with:redMap with:greenMap with:blueMap.

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

        line := inStream nextLine.
        [line notNil and:[line startsWith:'/*']] whileTrue:[
            line := inStream nextLine.
        ].
        (line notNil and:[line startsWith:'"']) ifFalse:[
            'XPM: format error (expected color spec)' errorPrintNL.
            inStream close.
            ^ 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.
                    s nextWord.    
                    s skipSeparators.
                ] ifFalse:[
                    char == $m ifTrue:[
                        "
                         monochrome data
                        "
                        s next.
                        s skipSeparators.
                        s nextWord.
                        s skipSeparators.
                    ] ifFalse:[
                        (char == $g) ifTrue:[
                            "
                             greyscale data
                            "
                            s next.
                            s peek == 4 ifTrue:[s next].
                            s skipSeparators.
                            s nextWord.
                            s skipSeparators.
                        ] ifFalse:[
                            (char == $c) ifTrue:[
                                "
                                 color data
                                "
                                s next.
                                s skipSeparators.
                                colorName := self colorNameFrom:s.
                                s skipSeparators.
                            ] ifFalse:[
                                'XPM: format error (expected ''c'',''m'',''g'' or ''s'')' errorPrintNL.
                                inStream close.
                                ^ nil
                            ].
                        ]
                    ]
                ]
            ].
        ].
        ((colorName = 'none') or:[colorName = 'None']) ifTrue:[
            "mhmh must add mask to Image-instances soon ..."
            color := Color white
        ] ifFalse:[
            color := Color name:colorName.
        ].
        redMap at:colorIndex put:(color red * 255 // 100).
        greenMap at:colorIndex put:(color green * 255 // 100).
        blueMap at:colorIndex put:(color blue * 255 // 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 := inStream nextLine withoutSpaces.
        [line notNil and:[line startsWith:'/*']] whileTrue:[
            line := inStream nextLine withoutSpaces.
        ].
        (line notNil and:[line startsWith:'"']) ifFalse:[
            'XPM: format error (expected pixels)' errorPrintNL.
            inStream close.
            ^ 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.

    "
     XPMReader fromFile:'../fileIn/bitmaps/magtape.xpm' 
     XPMReader fromFile:'../fileIn/bitmaps/pixmap.xpm' 
     XPMReader fromFile:'../fileIn/bitmaps/ljet.xpm'
    " 
! !