WBMPReader.st
author Stefan Vogel <sv@exept.de>
Mon, 13 Mar 2017 09:54:33 +0100
changeset 3941 dd9237d3a727
parent 3912 c73544a939fe
permissions -rw-r--r--
#BUGFIX by stefan class: MIMETypes application/xml -> #isXmlType

"
 COPYRIGHT (c) 2017 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.
"
"{ Package: 'stx:libview2' }"

"{ NameSpace: Smalltalk }"

ImageReader subclass:#WBMPReader
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

!WBMPReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2017 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 wbmp-bitmap-file images.
    The Wireless Application Protocol Bitmap Format (shortened to Wireless Bitmap)
    and with file extension .wbmp is a monochrome graphics file format optimized 
    for mobile computing devices.
    Only monochrome images can be represented in this format.
    Both reading and writing of images is supported.

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

    [author:]
        Claus Gittinger
"
!

examples
"
  Reading from a file:
                                                                        [exBegin]
    |image|

    image := Image fromFile:('../../goodies/bitmaps/wbmpImages/smile.wbpm').
    image inspect
                                                                        [exEnd]

  Writing to a file:
                                                                        [exBegin]
    |img|

    img := Image fromFile:'../../goodies/bitmaps/xbmBitmaps/TicTacToe.xbm'.
    WBMPReader save:img onFile:'../../goodies/bitmaps/wbmpBitmaps/TicTacToe.wbmp'.
    img saveOn:'../../goodies/bitmaps/wbmpBitmaps/TicTacToe2.wbmp'.
                                                                        [exEnd]
"
! !

!WBMPReader class methodsFor:'initialization'!

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

    MIMETypes defineImageType:'image/vnd.wap.wbmp' suffix:'wbmp' reader:self.

    "Modified: / 22-02-2017 / 13:48:27 / cg"
! !

!WBMPReader class methodsFor:'testing'!

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

    |photometric clr0 clr1|

    (anImage depth == 1) ifTrue:[
        photometric := anImage photometric.
        ((photometric == #blackIs0) or:[photometric == #whiteIs0]) ifTrue:[^ true].

        photometric == #palette ifTrue:[
            clr0 := anImage colorFromValue:0.
            clr1 := anImage colorFromValue:1.
            (clr0 = Color white and:[clr1 = Color black]) ifTrue:[^true].
            (clr1 = Color white and:[clr0 = Color black]) ifTrue:[^true].
        ].
    ].
    ('WBPMReader [info]: image depth is not 1 (only b&w images).') infoPrintCR.
    ^ false

    "Modified: / 22-02-2017 / 13:54:10 / cg"
!

isValidImageFile:aFileName
    "return true, if aFileName contains an wbmp-bitmap-file image.
     Bad design: it has no file header;
     so we check the dimension against the size of the file.
     Very fuzzy."

    |good inStream wbmpType fixedHeader width height bytesPerLine position|

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

    good := false.
    
    wbmpType := inStream nextByte.
    wbmpType == 0 ifTrue:[
        fixedHeader := inStream nextByte.
        fixedHeader == 0 ifTrue:[
    
            width := self nextUINTvarFrom:inStream.
            (width notNil and:[width between:1 and:2048]) ifTrue:[          "/ otherwise assume unreasonable width
                height := self nextUINTvarFrom:inStream.
                (height notNil and:[height between:1 and:2048]) ifTrue:[    "/ otherwise assume unreasonable height
                    bytesPerLine := (width+7) // 8.
                    position := inStream position.
                    (inStream size == ((bytesPerLine * height) + position)) ifTrue:[
                        good := true.
                    ].    
                ]
            ]
        ]
    ].
    inStream close.
    ^ good

    "
     WBMPReader isValidImageFile:'../../goodies/bitmaps/wbmpImages/smile.wbmp'
    "

    "Modified: / 22-02-2017 / 14:16:41 / cg"
! !

!WBMPReader class methodsFor:'utilities'!

nextPutUINTvar:anInteger flag:mask on:aStream
    anInteger > 16r7F ifTrue:[
        self nextPutUINTvar:(anInteger bitShift:-7) flag:16r80 on:aStream.
    ].  
    aStream nextPutByte:((anInteger bitAnd:16r7F) bitOr:mask)

    "
     ByteArray streamContents:[:s | self nextPutUINTvar:0 flag:0 on:s ] 
    "

    "Created: / 22-02-2017 / 14:42:05 / cg"
!

nextPutUINTvar:anInteger on:aStream
    "write an uintvar onto a stream (see wikipedia: uintvar)"
    
    self nextPutUINTvar:anInteger flag:0 on:aStream

    "
     (ByteArray streamContents:[:s | self nextPutUINTvar:0 on:s ]) hexPrintStringWithSeparator:$: 
     (ByteArray streamContents:[:s | self nextPutUINTvar:16r7F on:s ]) hexPrintStringWithSeparator:$:
     (ByteArray streamContents:[:s | self nextPutUINTvar:16r80 on:s ]) hexPrintStringWithSeparator:$:
     (ByteArray streamContents:[:s | self nextPutUINTvar:16rFF on:s ]) hexPrintStringWithSeparator:$:

     1 to:10000 do:[:n |
         |bytes n2|
         
         bytes := (ByteArray streamContents:[:s | self nextPutUINTvar:n on:s]).
         n2 := self nextUINTvarFrom:(bytes readStream).
         self assert:(n == n2)
     ].
    "

    "Created: / 22-02-2017 / 14:42:59 / cg"
!

nextUINTvarFrom:inStream
    "read an uintvar from a stream (see wikipedia: uintvar)"

    |val byte|

    val := 0.
    [
        byte := inStream nextByte.
        byte isNil ifTrue:[^ nil].
        val := (val bitShift:7) bitOr:(byte bitAnd:16r7F).
        (byte bitTest:16r80)
    ] whileTrue.
    ^ val.

    "Created: / 22-02-2017 / 14:11:37 / cg"
! !

!WBMPReader methodsFor:'reading'!

fromStream:aStream
    "read an image in xbm format from aStream.
     Leave image description in instance variables.
     (i.e. to get the image, ask with image)."

    |wbmpType fixedHeader bytesPerLine|

    wbmpType := inStream nextByte.
    wbmpType == 0 ifTrue:[
        fixedHeader := inStream nextByte.
        fixedHeader == 0 ifTrue:[
            width := self class nextUINTvarFrom:inStream.
            (width notNil and:[width between:1 and:2048]) ifTrue:[          "/ otherwise assume unreasonable width
                height := self class nextUINTvarFrom:inStream.
                (height notNil and:[height between:1 and:2048]) ifTrue:[    "/ otherwise assume unreasonable height
                    bytesPerLine := (width+7) // 8.
                    data := inStream nextBytes:(bytesPerLine * height).
                    photometric := #blackIs0.
                    samplesPerPixel := 1.
                    bitsPerSample := #(1).
                    ^ self.
                ]
            ]
        ]
    ].
    ^ self fileFormatError:'not valid WBMP format'.

    "
     WBMPReader fromFile:'../../goodies/bitmaps/wbmpImages/smile.wbmp'
     WBMPReader fromFile:'../../goodies/bitmaps/wbmpImages/edge.wbmp'
     WBMPReader fromFile:'../../goodies/bitmaps/wbmpImages/thumb.wbmp'
    "

    "Modified (format): / 22-02-2017 / 14:28:30 / cg"
! !

!WBMPReader methodsFor:'writing'!

save:image onStream:aStream
    "save image as XBM cdata on aStream.
     Only depth1 b&w images can be represented in this format."

    |srcIndex "{ Class: SmallInteger }"
     rowBytes "{ Class: SmallInteger }" |

    (self class canRepresent:image) ifFalse:[
        ^ Image cannotRepresentImageSignal 
            raiseWith:image
            errorString:('WBMP format only supports monochrome images').
    ].

    image mask notNil ifTrue:[
        Image informationLostQuerySignal
            raiseWith:image
            errorString:('WBMP format does not support an imageMask').
    ].

    outStream := aStream.
    outStream nextPutByte:0.    "/ type: always 0
    outStream nextPutByte:0.    "/ fixed header: always 0
    self class nextPutUINTvar:(width := image width) on:aStream. 
    self class nextPutUINTvar:(height := image height) on:aStream. 
    
    rowBytes := (width + 7) // 8.
    photometric := image photometric.

    data := image bits.
    data size == (rowBytes*height) ifTrue:[
        "/ no extra padding
        
        (photometric == #blackIs0) ifTrue:[
            outStream nextPutBytes:data.
            ^ self.
        ].
        (photometric == #whiteIs0) ifTrue:[
            data := data copy invert.
            outStream nextPutBytes:data.
            ^ self.
        ].
    ].   
    srcIndex := 1.
    1 to:height do:[:rowIdx |
        |row|

        row := data copyFrom:srcIndex to:srcIndex+rowBytes-1.
        photometric == #whiteIs0 ifTrue:[
            row invert
        ].    
        outStream nextPutBytes:row.
        srcIndex := srcIndex + (image bytesPerRow).
    ].

    "
     WBMPReader 
        save:(Image fromFile:'../../goodies/bitmaps/xbmBitmaps/TicTacToe.xbm') 
        onFile:'../../goodies/bitmaps/wbmpBitmaps/TicTacToe.wbmp'
    "

    "Modified: / 22-02-2017 / 14:54:02 / cg"
! !

!WBMPReader class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


WBMPReader initialize!