PBMReader.st
author claus
Mon, 10 Oct 1994 03:32:51 +0100
changeset 27 93da277c5ddd
parent 23 11c422f6d825
child 28 8daff0234d2e
permissions -rw-r--r--
Initial revision

"
 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:#PBMReader
         instanceVariableNames:''
         classVariableNames:''
         poolDictionaries:''
         category:'Graphics-Support'
!

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

$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.6 1994-08-05 01:14:51 claus Exp $
'!

!PBMReader 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/PBMReader.st,v 1.6 1994-08-05 01:14:51 claus Exp $
"
!

documentation
"
    this class provides methods for loading and saving Portable BitMap-file images
    (Jef Poskanzers portable bitmap package)..
"
! !

!PBMReader methodsFor:'private'!

skipPBMJunkOn: aStream 
    "This method removes any superfluous characters from the input stream."

    | char foundNL|

    [
        char := aStream peek.
        char == $# ifTrue:[
            "Start of a comment. Skip to end-of-line."
            foundNL := (aStream skipUpTo: Character cr) notNil.
            foundNL ifFalse: [
                "Must be EOF"
                ^self
            ].
            char := aStream peek].
            aStream atEnd not and: [char isSeparator]
    ] whileTrue: [aStream next]
!

skipXPMJunkOn: aStream
    "This method removes any superfluous characters from the input stream."

    | char |

    [       
        char := aStream peek. 
        aStream atEnd not and: [char isSeparator not]
    ] whileTrue: [aStream next].

    [aStream atEnd not and: [char isSeparator]] whileTrue: [
        aStream next. char := aStream peek
    ].
    aStream atEnd ifTrue: [^char].
    (char isDigit) ifTrue: [ ^char ].
    (char == $") ifTrue: [ 
        aStream next. 
        char := aStream peek. 
        ((char isAlphaNumeric or: [char = $#]) or: [char = Character space]) ifFalse:[
            ^self skipXPMJunkOn: aStream 
        ] ifTrue: [^char]
    ].

    ^self skipXPMJunkOn: aStream.
! !

!PBMReader methodsFor:'writing to file'!

save:image onFile:aFileName
    "save image as PBM/PGM/PNM file on aFileName"

    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.

    photometric == #rgb ifTrue:[
        ^ self writePNMFile
    ].
    samplesPerPixel == 1 ifTrue:[
        ((bitsPerSample at:1) == 1) ifTrue:[
            ^ self writePBMFile
        ].
        ((bitsPerSample at:1) == 8) ifTrue:[
            ^ self writePGMFile
        ].
    ].
    self error:'format not supported'.
!

writePNMFile
    self error:'not yet implemented'
!

writePBMFile
    self error:'not yet implemented'
!

writePGMFile
    self error:'not yet implemented'
! !

!PBMReader methodsFor:'reading from file'!

fromFile:fileName
    "read a Portable bitmap file format as of Jef Poskanzers Portable Bitmap Package.
     supported are PBM, PGB and PNM files." 

    | pnmType |

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

    inStream next == $P ifFalse:[
        ('not PNM format in ', fileName) errorPrintNL.
        inStream close. 
        ^nil
    ].
    pnmType := inStream next.
    inStream close.
    pnmType == $4 ifTrue: [
        ^ self readDepth1PBMFile:fileName
    ].
    pnmType == $5 ifTrue: [
        ^ self readDepth8PGMFile:fileName
    ].
    pnmType == $6 ifTrue: [
        ^ self readDepth24PPMFile:fileName
    ].
    ('No recognized pnm file format in ', fileName) errorPrintNL.
    ^ nil

    "PBMReader fromFile:'bitmaps/testimg.ppm'"
!

readDepth1PBMFile:fileName 
    "import portable bitmap (PBM)"

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

    (inStream next == $P) ifFalse: [
        inStream close. 
        'not a pbm file format' errorPrintNL.
        ^ nil
    ].

    (inStream next == $4) ifFalse:[
        inStream close. 
        'not a pbm file format' errorPrintNL.
        ^ nil
    ].

    self skipPBMJunkOn: inStream.
    width := Integer readFrom: inStream.
    width > 0 ifFalse: [
        inStream close. 
        'Invalid width' errorPrintNL.
        ^ nil
    ].

    self skipPBMJunkOn: inStream.
    height := Integer readFrom: inStream.
    height > 0 ifFalse: [
        inStream close. 
        'Invalid height' errorPrintNL.
        ^ nil
    ].

    inStream nextLine "skipThrough: Character cr".
    inStream binary.
    data := inStream contents.
    inStream close.

    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).
!

readDepth8PGMFile:fileName 
    "import portable gray map (PGM)"

    |maxval|

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

    inStream next == $P ifFalse:[ 
        inStream close.
        'not a pgm file format' errorPrintNL.
        ^ nil
    ].
    inStream next == $5 ifFalse:[ 
        inStream close.
        'not a pgm file format' errorPrintNL.
        ^ nil
    ].
    self skipPBMJunkOn: inStream.
    width := Integer readFrom: inStream.
    width > 0 ifFalse:[ 
        inStream close.
        'pgm read error' errorPrintNL.
        ^ nil
    ].
    self skipPBMJunkOn: inStream.
    height := Integer readFrom: inStream.
    height > 0 ifFalse:[ 
        inStream close.
        'pgm read error' errorPrintNL.
        ^ nil
    ].
    self skipPBMJunkOn: inStream.
    maxval := Integer readFrom: inStream.
    maxval >= 256 ifTrue:[
        inStream close.
        'pgm read error' errorPrintNL.
        ^ nil
    ].
    inStream skipThrough: Character cr.
    inStream binary.
    data := inStream contents.

    photometric := #blackIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
!

readDepth24PPMFile: fileName
    "import portable pixmap (PPM)"

    | maxval |

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

    (inStream next == $P) ifFalse: [
        inStream close. 
        self error: 'not a ppm file format' errorPrintNL.
        ^ nil
    ].

    (inStream next == $6) ifFalse: [
        inStream close. 
        self error: 'not a ppm file format' errorPrintNL.
        ^ nil
    ].

    self skipPBMJunkOn: inStream.
    width := Integer readFrom: inStream.
    width > 0 ifFalse: [
        inStream close. 
        self error: 'ppm read error' errorPrintNL.
        ^ nil
    ].

    self skipPBMJunkOn: inStream.
    height := Integer readFrom: inStream.
    height > 0 ifFalse: [
        inStream close. 
        self error: 'ppm read error' errorPrintNL.
        ^ nil
    ].

    self skipPBMJunkOn: inStream.
    maxval := Integer readFrom: inStream.
    maxval >= 256 ifTrue: [
        inStream close. 
        self error: 'ppm read error' errorPrintNL.
        ^ nil
    ].

    inStream skipThrough: Character cr.
    inStream binary.

    data := inStream contents.
    photometric := #rgb.
    samplesPerPixel := 3.
    bitsPerSample := #(8 8 8).
! !