PBMReader.st
changeset 807 855f41b1ec1a
parent 806 fc45835a5967
child 811 86a93acb3be7
--- a/PBMReader.st	Tue Feb 03 16:49:25 1998 +0100
+++ b/PBMReader.st	Tue Feb 03 17:34:22 1998 +0100
@@ -1,4 +1,15 @@
-'From Smalltalk/X, Version:3.2.1 on 17-oct-1997 at 9:13:03 pm'                  !
+"
+ 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:''
@@ -9,6 +20,21 @@
 
 !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.
+"
+
+!
+
 documentation
 "
     this class provides methods for loading and saving Portable BitMap-file 
@@ -16,10 +42,11 @@
 
     Reading is supported for 1bit (pbm), greyscale (pgm) and 24bit (ppm) formats.
     (i.e. P1, P3, P4, P5 and P6 formats)
+
     Writing is (currently) only supported for the binary formats;
     i.e. 1-bit images as (pbm P4), 8-bit gray as (pgm P5) and 24-bit images as (pnm P6).
 
-    Q: should we bring this one to perfection and base all others on
+    Q: should we broil this one to perfection and base all others on
        pipe-readers to the various pbmplus converters ?
 
     [See also:]
@@ -28,10 +55,21 @@
         ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
         XBMReader XPMReader XWDReader 
 "
-!
+! !
+
+!PBMReader class methodsFor:'initialization'!
+
+initialize
+    "install myself in the Image classes fileFormat table
+     for the `.pbm', '.pgm' and '.pnm' extensions."
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.31 1998-02-03 15:49:25 cg Exp $'
+    MIMETypes defineImageType:'image/x-portable-bitmap'  suffix:'pbm' reader:self.
+    MIMETypes defineImageType:'image/x-portable-graymap' suffix:'pgm' reader:self.
+    MIMETypes defineImageType:'image/x-portable-anymap'  suffix:'pnm' reader:self.
+    MIMETypes defineImageType:'image/x-portable-pixmap'  suffix:'ppm' reader:self.
+
+    "Modified: / 1.2.1997 / 15:02:14 / cg"
+    "Created: / 3.2.1998 / 17:19:59 / cg"
 ! !
 
 !PBMReader class methodsFor:'testing'!
@@ -53,10 +91,329 @@
     ^ false
 
     "Modified: 17.10.1997 / 20:20:52 / cg"
+!
+
+isValidImageFile:aFileName
+    "return true, if aFileName contains a PBM image (which I can read)"
+
+    |inStream pnmType|
+
+    inStream := self streamReadingFile:aFileName.
+    inStream isNil ifTrue:[^ false].
+    inStream text.
+    inStream next ~~ $P ifTrue:[^ false].
+
+    pnmType := inStream next.
+    (#( $1 $3 $4 $5 $6 ) includes:pnmType) ifFalse:[^ false].
+    ^ true
+
+    "Modified: / 4.4.1997 / 11:17:11 / cg"
+    "Created: / 3.2.1998 / 17:29:07 / cg"
+! !
+
+!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 := (aStream skipThrough: Character cr) notNil.
+            foundNL ifFalse: [
+                "Must be EOF"
+                ^self
+            ].
+            char := aStream peek].
+            aStream atEnd not and: [char isSeparator]
+    ] whileTrue: [aStream next]
+
+    "Created: / 3.2.1998 / 17:20:37 / cg"
+!
+
+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 isLetterOrDigit 
+         or: [(char == $#) 
+         or: [char == Character space]]) ifFalse:[
+            ^ self skipXPMJunkOn: aStream 
+        ] ifTrue: [^char]
+    ].
+
+
+    ^self skipXPMJunkOn: aStream.
+
+    "Created: / 3.2.1998 / 17:20:54 / cg"
 ! !
 
 !PBMReader methodsFor:'reading from file'!
 
+fromStream:aStream
+    "read a Portable bitmap file format as of Jeff Poskanzers Portable Bitmap Package.
+     supported are PBM, PGB and PNM files." 
+
+    | pnmType |
+
+    inStream := aStream.
+    inStream text.
+
+    inStream next == $P ifFalse:[
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: not PNM format'.
+        ^nil
+    ].
+    pnmType := inStream next.
+
+    (pnmType == $1) ifTrue: [
+        ^ self readDepth1AsciiPBMStream:aStream
+    ].
+    (pnmType == $3) ifTrue: [
+        ^ self readDepth24AsciiPBMStream:aStream
+    ].
+    (pnmType == $4) ifTrue: [
+        ^ self readDepth1PBMStream:aStream
+    ].
+    (pnmType == $5) ifTrue: [
+        ^ self readDepth8PGMStream:aStream
+    ].
+    (pnmType == $6) ifTrue: [
+        ^ self readDepth24PPMStream:aStream
+    ].
+    Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: No recognized PNM file format'.
+    ^ nil
+
+    "
+     PBMReader fromFile:'bitmaps/testimg.ppm'
+     PBMReader fromFile:'../../fileIn/bitmaps/keyboard.pbm'
+     PBMReader fromFile:'/home2/cg/ppm2fli_b1-92/jeff.001'
+    "
+
+    "Created: / 3.2.1998 / 17:25:34 / cg"
+    "Modified: / 3.2.1998 / 17:31:24 / cg"
+!
+
+readDepth1AsciiPBMStream:aStream 
+    "import portable bitmap ascii (PBM, P1 format); P1 is already read"
+
+    |n bits rowIdx dstIdx bytesPerRow char|
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid width'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid height'.
+        ^ nil
+    ].
+
+    aStream nextLine "skipThrough: Character cr".
+
+    bytesPerRow := (width + 7) // 8.
+    data := ByteArray new:bytesPerRow * height.
+    rowIdx := 1.
+
+    1 to:height do:[:row |
+        dstIdx := rowIdx.
+        bits := 0. n := 0.
+        1 to:width do:[:col |
+            char := aStream next.
+            [char notNil and:[char isSeparator]] whileTrue:[
+                char := aStream next
+            ].
+            bits := bits bitShift:1.
+            char == $1 ifTrue:[
+                bits := bits bitOr:1
+            ].
+            n := n + 1.
+            n == 8 ifTrue:[
+                data at:dstIdx put:bits.
+                dstIdx := dstIdx + 1.
+                bits := 0.
+                n := 0.
+            ].
+        ].
+        n ~~ 0 ifTrue:[
+            data at:dstIdx put:bits.
+        ].
+        rowIdx := rowIdx + bytesPerRow
+    ].
+
+    photometric := #whiteIs0.
+    samplesPerPixel := 1.
+    bitsPerSample := #(1).
+
+    "Created: / 3.2.1998 / 17:21:22 / cg"
+    "Modified: / 3.2.1998 / 17:32:07 / cg"
+!
+
+readDepth1PBMStream:aStream 
+    "import portable bitmap (PBM, P4 format); P4 is already read"
+
+    |bytesPerRow|
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream onError:0.
+    width > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid width'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream onError:0.
+    height > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid height'.
+        ^ nil
+    ].
+
+    aStream nextLine "skipThrough: Character cr".
+
+    bytesPerRow := width // 8.
+    ((width \\ 8) ~~ 0) ifTrue:[
+        bytesPerRow := bytesPerRow + 1
+    ].
+
+    "/ the rest is the binary image data ...
+    aStream binary.
+    data := ByteArray uninitializedNew:(bytesPerRow*height).
+    aStream nextBytes:(data size) into:data.
+
+    photometric := #blackIs0.
+    samplesPerPixel := 1.
+    bitsPerSample := #(1).
+
+    "Created: / 3.2.1998 / 17:21:37 / cg"
+    "Modified: / 3.2.1998 / 17:32:24 / cg"
+!
+
+readDepth24AsciiPBMStream:aStream
+    "import ascii portable pixmap (PBM, P3 format); P3 is already read"
+
+    |maxval 
+     nBytes "{Class: SmallInteger }" 
+     v      "{Class: SmallInteger }"
+     c|
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid width'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid height'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    maxval := Integer readFrom:aStream.
+    maxval >= 256 ifTrue: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: format error'.
+        ^ nil
+    ].
+
+    aStream skipThrough: Character cr.
+
+    nBytes := width*height*3.
+    data := ByteArray new:nBytes.
+    1 to:nBytes do:[:i |
+        aStream skipSeparators.
+        v := 0.
+        c := aStream next.
+        [c isDigit] whileTrue:[
+            v := v * 10 + (c digitValue).
+            c := aStream next.
+        ].
+        data at:i put:v
+    ].
+
+    photometric := #rgb.
+    samplesPerPixel := 3.
+    bitsPerSample := #(8 8 8).
+
+    "Created: / 3.2.1998 / 17:21:55 / cg"
+    "Modified: / 3.2.1998 / 17:32:48 / cg"
+!
+
+readDepth24PPMStream:aStream
+    "import portable pixmap (PPM, P6 format); P6 is already read"
+
+    | maxval |
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid width'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid height'.
+        ^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    maxval := Integer readFrom:aStream.
+    maxval >= 256 ifTrue: [
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: format error'.
+        ^ nil
+    ].
+
+    aStream skipThrough: Character cr.
+
+    "/ the rest is the binary image data ...
+    aStream binary.
+    data := ByteArray uninitializedNew:(width*height*3).
+    aStream nextBytes:(data size) into:data.
+
+    photometric := #rgb.
+    samplesPerPixel := 3.
+    bitsPerSample := #(8 8 8).
+
+    "Created: / 3.2.1998 / 17:22:18 / cg"
+    "Modified: / 3.2.1998 / 17:33:10 / cg"
+!
+
 readDepth8PGMStream:aStream 
     "import portable gray map (PGM, P5 format); P5 is already read"
 
@@ -65,19 +422,22 @@
     self skipPBMJunkOn:aStream.
     width := Integer readFrom:aStream.
     width > 0 ifFalse:[ 
-        'PBMREADER: Invalid width' errorPrintNL.
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid width'.
         ^ nil
     ].
     self skipPBMJunkOn:aStream.
     height := Integer readFrom:aStream.
     height > 0 ifFalse:[ 
-        'PBMREADER: Invalid height' errorPrintNL.
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid height'.
         ^ nil
     ].
     self skipPBMJunkOn:aStream.
     maxval := Integer readFrom:aStream.
     maxval >= 256 ifTrue:[
-        'PBMREADER: Invalid format' errorPrintNL.
+        Image badImageFormatQuerySignal
+            raiseErrorString:'PBMReader [info]: Invalid format'.
         ^ nil
     ].
     aStream nextLine "skipThrough: Character cr".
@@ -91,7 +451,7 @@
     samplesPerPixel := 1.
     bitsPerSample := #(8).
 
-    "Modified: 14.10.1997 / 19:44:05 / cg"
+    "Modified: / 3.2.1998 / 17:33:29 / cg"
 ! !
 
 !PBMReader methodsFor:'writing to file'!
@@ -270,3 +630,9 @@
     "Modified: 14.10.1997 / 20:07:08 / cg"
 ! !
 
+!PBMReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.32 1998-02-03 16:34:22 cg Exp $'
+! !
+PBMReader initialize!