XBMReader.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:24:25 +0200
changeset 220 4106d9ce7e02
parent 210 5405de794686
child 234 b6352d13e792
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1992 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:#XBMReader
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images support'
!

!XBMReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 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 and saving x-bitmap-file images.
    These images can (for example) be created using the bitmap editor supplied
    with X. 
    Only monochrome images can be represented in this format.
    Both reading and writing of images is supported.

    [See also:]
        BlitImageReader FaceReader GIFReader JPEGReader PBMReader PCXReader 
        ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
        XPMReader XWDReader 

    [author:]
        Claus Gittinger
"
! !

!XBMReader class methodsFor:'initialization'!

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

    Image fileFormats at:'.xbm'  put:self.

    "Modified: 23.4.1996 / 12:37:30 / cg"
! !

!XBMReader class methodsFor:'testing'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format"

    |photometric|

    (anImage depth ~~ 1) ifTrue:[^ false.].
    (((photometric := anImage photometric) ~~ #blackIs0) and:[photometric ~~ #whiteIs0]) ifTrue:[^ false.].
    ^ true
!

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

    |line inStream index1 index2 keyword|

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

    line := inStream nextLine.
    line isNil ifTrue:[
	inStream close.
	^ false
    ].
    [line startsWith:'#'] whileFalse:[
	line := inStream nextLine.
	line isNil ifTrue:[
	    inStream close.
	    ^ false
	]
    ].
    index1 := line indexOf:(Character space).
    index2 := line indexOf:(Character space) startingAt:(index1 + 1).
    (index2 == 0) ifTrue:[
	inStream close.
	^ false
    ].
    keyword := line copyFrom:index1 to:(index2 - 1).
    (keyword endsWith:'_width') ifFalse:[
	inStream close.
	^ false
    ].
    inStream close.
    ^ true
! !

!XBMReader methodsFor:'reading from file'!

fromStream:aStream
    "read an image in xbm format from aStream"

    |line 
     index    "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     bytesPerRow
     lo       "{ Class: SmallInteger }"
     hi       "{ Class: SmallInteger }"
     val      "{ Class: SmallInteger }"
     reverseBits|

    inStream := aStream.

    line := aStream nextLine.
    line isNil ifTrue:[
        'XBMReader: short file' errorPrintNL.
        ^ nil
    ].

    [line startsWith:'#'] whileFalse:[
        line := aStream nextLine
    ].

    (line startsWith:'#define') ifFalse:[
        'XBMReader: format error (expected #define)' errorPrintNL.
        ^ nil
    ].

    index := line indexOf:(Character space).
    index := line indexOf:(Character space) startingAt:(index + 1).
    (index == 0) ifTrue:[
        'XBMReader: format error' errorPrintNL.
        ^ nil
    ].
    ((line copyTo:index - 1) endsWith:'width') ifFalse:[
        'XBMReader: format error (expected width)' errorPrintNL.
        ^ nil
    ].
    line := line copyFrom:(index + 1).
    width := Number readFromString:line.

    line := aStream nextLine.
    index := line indexOf:(Character space).
    index := line indexOf:(Character space) startingAt:(index + 1).
    (index == 0) ifTrue:[
        'XBMReader: format error' errorPrintNL.
        ^ nil
    ].
    ((line copyTo:index - 1) endsWith:'height') ifFalse:[
        'XBMReader: format error (expected height)' errorPrintNL.
        ^ nil
    ].
    line := line copyFrom:(index + 1).
    height := Number readFromString:line.

    bytesPerRow := width // 8.
    ((width \\ 8) ~~ 0) ifTrue:[
        bytesPerRow := bytesPerRow + 1
    ].

    reverseBits := self class reverseBits.

    data := ByteArray new:(bytesPerRow * height).
    dstIndex := 1.

    line := aStream nextLine.
    [line startsWith:'#'] whileTrue:[
        line := aStream nextLine.
    ].

    [line notNil and:[(line startsWith:'static') not]] whileTrue:[
        line := aStream nextLine.
    ].
    line := aStream nextLine.

    [line notNil] whileTrue:[
        index := 1.
        [index ~~ 0] whileTrue:[
            index := line indexOf:$x startingAt:index.
            (index ~~ 0) ifTrue:[
                index := index + 1.
                hi := (line at:index) digitValue.
                index := index + 1.
                lo := (line at:index) digitValue.
                val := (hi bitShift:4) bitOr:lo.
                data at:dstIndex put:(reverseBits at:(val + 1)).
                dstIndex := dstIndex + 1
            ]
        ].
        line := aStream nextLine
    ].
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).

    "
     XBMReader fromFile:'bitmaps/globe1.xbm'
    "

    "Modified: 23.4.1996 / 12:38:05 / cg"
! !

!XBMReader methodsFor:'writing to file'!

save:image onFile:aFileName
    "save image as XBM file on aFileName.
     Only depth1 b&w images can be represented in this format."

    |reverseBits bits byte
     h        "{ Class: SmallInteger }"
     srcIndex "{ Class: SmallInteger }"
     rowBytes "{ Class: SmallInteger }" |

    (self class canRepresent:image) ifFalse:[
        self error:'can only save depth 1 B&W images'.
        ^ nil.
    ].

    outStream := FileStream newFileNamed:aFileName.
    outStream isNil ifTrue:[
        'XBMReader: create error' errorPrintNL. 
        ^ nil
    ].

    width := image width.
    height := image height.
    photometric := image photometric.
    samplesPerPixel := image samplesPerPixel.
    bitsPerSample := image bitsPerSample.
    colorMap := image colorMap.

    outStream nextPutAll: '#define xbm_width '.
    outStream nextPutAll:(width printString).
    outStream cr.
    outStream nextPutAll: '#define xbm_height '.
    outStream nextPutAll:(height printString).
    outStream cr.
    outStream nextPutAll: 'static char xbm_bits[] = {'; cr.

    reverseBits := self class reverseBits.

    rowBytes := width + 7 // 8.
    data := image bits.
    srcIndex := 1.

    h := height.
    h timesRepeat:[
        rowBytes timesRepeat:[
            outStream nextPutAll: '0x'.
            bits := data at:srcIndex. srcIndex := srcIndex + 1.
            photometric == #blackIs0 ifTrue:[
                bits := bits bitInvert bitAnd:16rFF
            ].
            byte := (reverseBits at:(bits + 1)).
            byte < 16 ifTrue:[
                outStream nextPut:$0
            ].
            byte printOn:outStream radix:16.
            outStream nextPutAll: ', '.
        ].
        outStream cr
    ].
    outStream nextPutAll: '};'; cr.
    outStream close

    "
     XBMReader save:(Image fromFile:'bitmaps/SBrowser.xbm') onFile:'test.xbm'
    "
    "
     convert sun icon to XBM format:

     XBMReader save:(Image fromFile:'bitmaps/hello_world.icon') onFile:'test.xbm'
    "

    "Modified: 23.4.1996 / 12:38:30 / cg"
! !

!XBMReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.24 1996-04-25 16:23:34 cg Exp $'
! !
XBMReader initialize!