Initial revision
authorclaus
Wed, 13 Oct 1993 01:31:41 +0100
changeset 2 842b6a603cdc
parent 1 6fe019b6ea79
child 3 78aaa5408119
Initial revision
JPEGReader.st
PBMReader.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/JPEGReader.st	Wed Oct 13 01:31:41 1993 +0100
@@ -0,0 +1,27 @@
+ImageReader subclass:#JPEGReader
+         instanceVariableNames:''
+         classVariableNames:''
+         poolDictionaries:''
+         category:'Graphics-Support'
+!
+
+!JPEGReader methodsFor:'reading from file'!
+
+fromFile:aFileName
+    "make it the easy way: let djpeg convert it to gif,
+     then let GIFReader read the file"
+
+    |tempFileName reader|
+
+    tempFileName := '/tmp/img' , (OperatingSystem getProcessId printString).
+    Transcript showCr:'converting to gif ..'.
+    (OperatingSystem executeCommand:'djpeg -gif ' , aFileName , ' > ' , tempFileName)
+    ifTrue:[
+        reader := GIFReader fromFile:tempFileName.
+        OperatingSystem executeCommand:'rm ' , tempFileName.
+        ^ reader
+    ].
+    ^ nil
+
+    "JPEGReader fromFile:'bitmaps/testimg.jpg'"
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PBMReader.st	Wed Oct 13 01:31:41 1993 +0100
@@ -0,0 +1,258 @@
+"
+ COPYRIGHT (c) 1993 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-93 by Claus Gittinger
+              All Rights Reserved
+
+this class provides methods for loading and saving Portable BitMap-file images
+(Jef Poskanzers portable bitmap package)..
+
+%W% %E%
+written Aug 93 by claus
+'!
+
+!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"
+
+    |pos1 pos|
+
+    outStream := FileStream newFileNamed:aFileName.
+    outStream isNil ifTrue:[
+        'create error' printNewline. 
+        ^ 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'.
+! !
+
+!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 := FileStream readonlyFileNamed:fileName.
+    inStream isNil ifTrue:[
+        ('open error on ' , fileName) printNewline.
+        ^ nil
+    ].
+    inStream next == $P ifFalse:[
+        ('not PNM format in ', fileName) printNewline.
+        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) printNewline.
+    ^ nil
+
+    "PBMReader fromFile:'bitmaps/testimg.ppm'"
+!
+
+readDepth1PBMFile:fileName 
+    "import portable bitmap (PBM)"
+
+    inStream := FileStream readonlyFileNamed:fileName.
+
+    (inStream next == $P) ifFalse: [
+        inStream close. 
+        self error: 'not a pbm file format'
+    ].
+
+    (inStream next == $4) ifFalse:[
+        inStream close. 
+        self error: 'not a pbm file format'
+    ].
+
+    self skipPBMJunkOn: inStream.
+    width := Integer readFrom: inStream.
+    width > 0 ifFalse: [inStream close. self error: 'Invalid width'].
+
+    self skipPBMJunkOn: inStream.
+    height := Integer readFrom: inStream.
+    height > 0 ifFalse: [inStream close. self error: 'Invalid height'].
+
+    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 := FileStream readonlyFileNamed:fileName.
+    inStream next == $P ifFalse:[ 
+        inStream close.
+        self error: 'not a pgm file format'
+    ].
+    inStream next == $5 ifFalse:[ 
+        inStream close.
+        self error: 'not a pgm file format'
+    ].
+    self skipPBMJunkOn: inStream.
+    width := Integer readFrom: inStream.
+    width > 0 ifFalse:[ 
+        inStream close.
+        self error: 'pgm read error'
+    ].
+    self skipPBMJunkOn: inStream.
+    height := Integer readFrom: inStream.
+    height > 0 ifFalse:[ 
+        inStream close.
+        self error: 'pgm read error'
+    ].
+    self skipPBMJunkOn: inStream.
+    maxval := Integer readFrom: inStream.
+    maxval >= 256 ifTrue:[
+        inStream close.
+        self error: 'pgm read error'
+    ].
+    inStream skipThrough: Character cr.
+    inStream binary.
+    data := inStream contents.
+
+    photometric := #blackIs0.
+    samplesPerPixel := 1.
+    bitsPerSample := #(8).
+!
+
+readDepth24PPMFile: fileName
+    "import portable pixmap (PPM)"
+
+    | maxval |
+
+    inStream := FileStream readonlyFileNamed:fileName.
+    (inStream next == $P) ifFalse: [
+        inStream close. 
+        self error: 'not a ppm file format'
+    ].
+
+    (inStream next == $6) ifFalse: [
+        inStream close. 
+        self error: 'not a ppm file format'
+    ].
+
+    self skipPBMJunkOn: inStream.
+    width := Integer readFrom: inStream.
+    width > 0 ifFalse: [inStream close. self error: 'ppm read error'].
+
+    self skipPBMJunkOn: inStream.
+    height := Integer readFrom: inStream.
+    height > 0 ifFalse: [inStream close. self error: 'ppm read error'].
+
+    self skipPBMJunkOn: inStream.
+    maxval := Integer readFrom: inStream.
+    maxval >= 256 ifTrue: [inStream close. self error: 'ppm read error'].
+
+    inStream skipThrough: Character cr.
+    inStream binary.
+
+
+    data := inStream contents.
+    photometric := #rgb.
+    samplesPerPixel := 3.
+    bitsPerSample := #(8 8 8).
+! !