XBMReader.st
author claus
Mon, 10 Oct 1994 03:34:22 +0100
changeset 28 8daff0234d2e
parent 24 6bc436eb4c4a
child 33 be90784ee668
permissions -rw-r--r--
*** empty log message ***

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

XBMReader comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.8 1994-10-10 02:34:18 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.8 1994-10-10 02:34:18 claus Exp $
"
!

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.
    See also: XPMRreader, SunReader, WinIconReader, GIFReader and TIFFReader
"
! !

!XBMReader class methodsFor:'initialization'!

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

!XBMReader methodsFor:'writing to file'!

save:image onFile:aFileName
    "save image as XBM file on aFileName"

    |reverseBits bits srcIndex rowBytes|

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

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

    ((samplesPerPixel ~~ 1)
    or:[((bitsPerSample at:1) ~~ 1)
    or:[(photometric ~~ #blackIs0) and:[photometric ~~ #whiteIs0]]]) ifTrue:[
	self error:'can only save Depth1Images'.
	outStream close.
	^ nil.
    ].

    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.

    height timesRepeat:[
	rowBytes timesRepeat:[
	    outStream nextPutAll: '0x'.
	    bits := data at:srcIndex. srcIndex := srcIndex + 1.
	    (reverseBits at:(bits + 1)) printOn:outStream radix:16.
	    outStream nextPutAll: ', '.
	].
	outStream cr
    ].
    outStream nextPutAll: '};'; cr.
    outStream close

    "XBMReader save:(Image fromFile:'bitmaps/SBrowser.xbm') onFile:'test.xbm'"
! !

!XBMReader class methodsFor:'testing'!

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:[
	^ false
    ].
    inStream close.
    ^ true
! !

!XBMReader methodsFor:'reading from file'!

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

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

    line := inStream nextLine.
    line isNil ifTrue:[
	inStream close.
	^ nil
    ].

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

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

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

    line := inStream nextLine.
    index := line indexOf:(Character space).
    index := line indexOf:(Character space) startingAt:(index + 1).
    (index == 0) ifTrue:[
	'format error' errorPrintNL.
	inStream close.
	^ nil
    ].
    ((line copyTo:index - 1) endsWith:'height') ifFalse:[
	'format error (expected height)' errorPrintNL.
	inStream close.
	^ 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 := inStream nextLine.
    [line startsWith:'#'] whileTrue:[
	line := inStream nextLine
    ].

    line := inStream 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 := inStream nextLine
    ].
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).

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