checkin from browser
authorClaus Gittinger <cg@exept.de>
Tue, 23 Apr 1996 12:33:51 +0200
changeset 200 33e4adf6fd59
parent 199 d80a247e0cfe
child 201 c707ed0db1d0
checkin from browser
PBMReader.st
--- a/PBMReader.st	Tue Apr 23 12:30:44 1996 +0200
+++ b/PBMReader.st	Tue Apr 23 12:33:51 1996 +0200
@@ -11,10 +11,10 @@
 "
 
 ImageReader subclass:#PBMReader
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Graphics-Images support'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Images support'
 !
 
 !PBMReader class methodsFor:'documentation'!
@@ -31,27 +31,32 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-! 
-
-version
-    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.14 1995-11-11 16:04:45 cg Exp $'
 !
 
 documentation
 "
     this class provides methods for loading and saving Portable BitMap-file 
     images (Jef Poskanzers portable bitmap package).
+
     Reading is supported for 1bit (pbm), greyscale (pgm) and 24bit (ppm) formats.
     Currently, only writing of 1-bit images (Pbm) is supported.
 
     Q: should we bring this one to perfection and base all others on
        pipe-readers to the various pbmplus converters ?
+
+    [See also:]
+        BlitImageReader FaceReader GIFReader JPEGReader PCXReader 
+        ST80FormReader SunRasterReader 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."
+
     Image fileFormats at:'.pbm'  put:self.
     Image fileFormats at:'.pgm'  put:self.
     Image fileFormats at:'.pnm'  put:self.
@@ -60,53 +65,180 @@
 !PBMReader methodsFor:'private'!
 
 skipPBMJunkOn:aStream 
-    "This method removes any superfluous characters from the input stream."
+    "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."
+        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]
+            foundNL := (aStream skipThrough: 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."
+    "this method removes any superfluous characters from the input stream."
 
     | char |
 
     [       
-	char := aStream peek. 
-	aStream atEnd not and: [char isSeparator not]
+        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 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]
+        aStream next. 
+        char := aStream peek. 
+        (char isLetterOrDigit 
+         or: [(char == $#) 
+         or: [char == Character space]]) ifFalse:[
+            ^ self skipXPMJunkOn: aStream 
+        ] ifTrue: [^char]
     ].
 
     ^self skipXPMJunkOn: aStream.
 ! !
 
+!PBMReader methodsFor:'reading from file'!
+
+fromStream:aStream
+    "read a Portable bitmap file format as of Jef Poskanzers Portable Bitmap Package.
+     supported are PBM, PGB and PNM files." 
+
+    | pnmType |
+
+    inStream := aStream.
+    inStream text.
+
+    inStream next == $P ifFalse:[
+	'PBMREADER: PNM format' errorPrintNL.
+	^nil
+    ].
+    pnmType := inStream next.
+    pnmType == $4 ifTrue: [
+	^ self readDepth1PBMStream:aStream
+    ].
+    pnmType == $5 ifTrue: [
+	^ self readDepth8PGMStream:aStream
+    ].
+    pnmType == $6 ifTrue: [
+	^ self readDepth24PPMStream:aStream
+    ].
+    'PBMREADER: No recognized PNM file format' errorPrintNL.
+    ^ nil
+
+    "
+     PBMReader fromFile:'bitmaps/testimg.ppm'
+     PBMReader fromFile:'../../fileIn/bitmaps/keyboard.pbm'
+    "
+!
+
+readDepth1PBMStream:aStream 
+    "import portable bitmap (PBM); P4 is already read"
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse: [
+	'PBMREADER: Invalid width' errorPrintNL.
+	^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse: [
+	'PBMREADER: Invalid height' errorPrintNL.
+	^ nil
+    ].
+
+    aStream nextLine "skipThrough: Character cr".
+    aStream binary.
+    data := aStream contents.
+
+    photometric := #blackIs0.
+    samplesPerPixel := 1.
+    bitsPerSample := #(1).
+!
+
+readDepth24PPMStream:aStream
+    "import portable pixmap (PPM); P6 is already read"
+
+    | maxval |
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse: [
+	'PBMREADER: Invalid width' errorPrintNL.
+	^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse: [
+	'PBMREADER: Invalid height' errorPrintNL.
+	^ nil
+    ].
+
+    self skipPBMJunkOn:aStream.
+    maxval := Integer readFrom:aStream.
+    maxval >= 256 ifTrue: [
+	'PBMREADER: format error' errorPrintNL.
+	^ nil
+    ].
+
+    aStream skipThrough: Character cr.
+    aStream binary.
+
+    data := aStream contents.
+    photometric := #rgb.
+    samplesPerPixel := 3.
+    bitsPerSample := #(8 8 8).
+!
+
+readDepth8PGMStream:aStream 
+    "import portable gray map (PGM); P5 is already read"
+
+    |maxval|
+
+    self skipPBMJunkOn:aStream.
+    width := Integer readFrom:aStream.
+    width > 0 ifFalse:[ 
+	'PBMREADER: Invalid width' errorPrintNL.
+	^ nil
+    ].
+    self skipPBMJunkOn:aStream.
+    height := Integer readFrom:aStream.
+    height > 0 ifFalse:[ 
+	'PBMREADER: Invalid height' errorPrintNL.
+	^ nil
+    ].
+    self skipPBMJunkOn:aStream.
+    maxval := Integer readFrom:aStream.
+    maxval >= 256 ifTrue:[
+	'PBMREADER: Invalid format' errorPrintNL.
+	^ nil
+    ].
+    aStream skipThrough: Character cr.
+    aStream binary.
+    data := aStream contents.
+
+    photometric := #blackIs0.
+    samplesPerPixel := 1.
+    bitsPerSample := #(8).
+! !
+
 !PBMReader methodsFor:'testing '!
 
 canRepresent:anImage
@@ -178,10 +310,6 @@
     "
 !
 
-writePNMFileOn:outStream
-    self error:'not yet implemented'
-!
-
 writePBMFileOn:aStream
     "Saves the receivers image on the file fileName in Portable Bitmap format.
      See the class method pbmSyntax for details of the format."
@@ -208,132 +336,20 @@
 !
 
 writePGMFileOn:outStream
+    "raise an error - this is not yet implemented"
+
+    self error:'not yet implemented'
+!
+
+writePNMFileOn:outStream
+    "raise an error - this is not yet implemented"
+
     self error:'not yet implemented'
 ! !
 
-!PBMReader methodsFor:'reading from file'!
-
-fromStream:aStream
-    "read a Portable bitmap file format as of Jef Poskanzers Portable Bitmap Package.
-     supported are PBM, PGB and PNM files." 
-
-    | pnmType |
-
-    inStream := aStream.
-    inStream text.
-
-    inStream next == $P ifFalse:[
-	'PBMREADER: PNM format' errorPrintNL.
-	^nil
-    ].
-    pnmType := inStream next.
-    pnmType == $4 ifTrue: [
-	^ self readDepth1PBMStream:aStream
-    ].
-    pnmType == $5 ifTrue: [
-	^ self readDepth8PGMStream:aStream
-    ].
-    pnmType == $6 ifTrue: [
-	^ self readDepth24PPMStream:aStream
-    ].
-    'PBMREADER: No recognized PNM file format' errorPrintNL.
-    ^ nil
-
-    "
-     PBMReader fromFile:'bitmaps/testimg.ppm'
-     PBMReader fromFile:'../../fileIn/bitmaps/keyboard.pbm'
-    "
-!
-
-readDepth1PBMStream:aStream 
-    "import portable bitmap (PBM); P4 is already read"
-
-    self skipPBMJunkOn:aStream.
-    width := Integer readFrom:aStream.
-    width > 0 ifFalse: [
-	'PBMREADER: Invalid width' errorPrintNL.
-	^ nil
-    ].
-
-    self skipPBMJunkOn:aStream.
-    height := Integer readFrom:aStream.
-    height > 0 ifFalse: [
-	'PBMREADER: Invalid height' errorPrintNL.
-	^ nil
-    ].
-
-    aStream nextLine "skipThrough: Character cr".
-    aStream binary.
-    data := aStream contents.
-
-    photometric := #blackIs0.
-    samplesPerPixel := 1.
-    bitsPerSample := #(1).
-!
-
-readDepth8PGMStream:aStream 
-    "import portable gray map (PGM); P5 is already read"
+!PBMReader class methodsFor:'documentation'!
 
-    |maxval|
-
-    self skipPBMJunkOn:aStream.
-    width := Integer readFrom:aStream.
-    width > 0 ifFalse:[ 
-	'PBMREADER: Invalid width' errorPrintNL.
-	^ nil
-    ].
-    self skipPBMJunkOn:aStream.
-    height := Integer readFrom:aStream.
-    height > 0 ifFalse:[ 
-	'PBMREADER: Invalid height' errorPrintNL.
-	^ nil
-    ].
-    self skipPBMJunkOn:aStream.
-    maxval := Integer readFrom:aStream.
-    maxval >= 256 ifTrue:[
-	'PBMREADER: Invalid format' errorPrintNL.
-	^ nil
-    ].
-    aStream skipThrough: Character cr.
-    aStream binary.
-    data := aStream contents.
-
-    photometric := #blackIs0.
-    samplesPerPixel := 1.
-    bitsPerSample := #(8).
-!
-
-readDepth24PPMStream:aStream
-    "import portable pixmap (PPM); P6 is already read"
-
-    | maxval |
-
-    self skipPBMJunkOn:aStream.
-    width := Integer readFrom:aStream.
-    width > 0 ifFalse: [
-	'PBMREADER: Invalid width' errorPrintNL.
-	^ nil
-    ].
-
-    self skipPBMJunkOn:aStream.
-    height := Integer readFrom:aStream.
-    height > 0 ifFalse: [
-	'PBMREADER: Invalid height' errorPrintNL.
-	^ nil
-    ].
-
-    self skipPBMJunkOn:aStream.
-    maxval := Integer readFrom:aStream.
-    maxval >= 256 ifTrue: [
-	'PBMREADER: format error' errorPrintNL.
-	^ nil
-    ].
-
-    aStream skipThrough: Character cr.
-    aStream binary.
-
-    data := aStream contents.
-    photometric := #rgb.
-    samplesPerPixel := 3.
-    bitsPerSample := #(8 8 8).
+version
+    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.15 1996-04-23 10:33:51 cg Exp $'
 ! !
+PBMReader initialize!