XPMReader.st
changeset 28 8daff0234d2e
parent 24 6bc436eb4c4a
child 32 6bdcb6da4d4f
--- a/XPMReader.st	Mon Oct 10 03:32:51 1994 +0100
+++ b/XPMReader.st	Mon Oct 10 03:34:22 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -11,17 +11,17 @@
 "
 
 ImageReader subclass:#XPMReader
-         instanceVariableNames:''
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Graphics-Support'
+	 instanceVariableNames:''
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Graphics-Support'
 !
 
 XPMReader comment:'
 COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.2 1994-08-05 01:16:30 claus Exp $
+$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.3 1994-10-10 02:34:22 claus Exp $
 '!
 
 !XPMReader class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.2 1994-08-05 01:16:30 claus Exp $
+$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.3 1994-10-10 02:34:22 claus Exp $
 "
 !
 
@@ -53,19 +53,25 @@
     of them). The code here is a hack - it may not work for all images (it works
     for the testfiles I got here).
     Limitations: 
-        only reads the full-color specification, ignoring monochrome
-        and greyscale info.
+	only reads the full-color specification, ignoring monochrome
+	and greyscale info.
 
-        Can only handle single-character index.
+	Can only handle single-character index.
 
-        Does not (currently) handle none-colors (i.e. for image-masks).
+	Does not (currently) handle none-colors (i.e. for image-masks).
 
-        Save not supported
+	Save not supported
 
     Suggestions: adapt & use the XPM library here.
 "
 ! !
 
+!XPMReader class methodsFor:'initialization'!
+
+initialize
+    Image fileFormats at:'.xpm'  put:self.
+! !
+
 !XPMReader class methodsFor:'testing'!
 
 isValidImageFile:aFileName
@@ -98,13 +104,13 @@
     |s|
 
     aStream peek == $# ifTrue:[
-        aStream next.
-        s := '#'.
+	aStream next.
+	s := '#'.
     ] ifFalse:[
-        s := ''.
+	s := ''.
     ].
-    [aStream peek isAlphaNumeric] whileTrue:[
-        s := s copyWith:aStream next
+    [aStream peek isLetterOrDigit] whileTrue:[
+	s := s copyWith:aStream next
     ].
     ^ s
 !
@@ -121,34 +127,34 @@
 
     inStream := self class streamReadingFile:aFileName.
     inStream isNil ifTrue:[
-        'XPM: file open error' errorPrintNL.
-        ^ nil
+	'XPM: file open error' errorPrintNL.
+	^ nil
     ].
 
     line := inStream nextLine.
     (line notNil and:[line startsWith:'/* XPM']) ifFalse:[
-        'XPM: format error (expected XPM)' errorPrintNL.
-        inStream close.
-        ^ nil
+	'XPM: format error (expected XPM)' errorPrintNL.
+	inStream close.
+	^ nil
     ].
 
     line := inStream nextLine.
     [line notNil and:[line startsWith:'/*']] whileTrue:[
-        line := inStream nextLine.
+	line := inStream nextLine.
     ].
     (line notNil and:[line startsWith:'static char']) ifFalse:[
-        'XPM: format error (expected static char)' errorPrintNL.
-        inStream close.
-        ^ nil
+	'XPM: format error (expected static char)' errorPrintNL.
+	inStream close.
+	^ nil
     ].
     line := inStream nextLine.
     [line notNil and:[line startsWith:'/*']] whileTrue:[
-        line := inStream nextLine.
+	line := inStream nextLine.
     ].
     (line notNil and:[line startsWith:'"']) ifFalse:[
-        'XPM: format error (expected "ww hh nn mm)' errorPrintNL.
-        inStream close.
-        ^ nil
+	'XPM: format error (expected "ww hh nn mm)' errorPrintNL.
+	inStream close.
+	^ nil
     ].
     s := ReadStream on:line.
     s next.  "skip quote"
@@ -157,8 +163,8 @@
     colorMapSize := Integer readFrom:s.
     charsPerPixel := Integer readFrom:s.
     charsPerPixel ~~ 1 ifTrue:[
-        'XPM: can only handle single-character xpm-files' errorPrintNL.
-        ^ nil
+	'XPM: can only handle single-character xpm-files' errorPrintNL.
+	^ nil
     ].
     xlation := Array new:256.
 
@@ -168,85 +174,85 @@
     colorMap := Array with:redMap with:greenMap with:blueMap.
 
     1 to:colorMapSize do:[:colorIndex |
-        |index line color|
+	|index line color|
 
-        line := inStream nextLine.
-        [line notNil and:[line startsWith:'/*']] whileTrue:[
-            line := inStream nextLine.
-        ].
-        (line notNil and:[line startsWith:'"']) ifFalse:[
-            'XPM: format error (expected color spec)' errorPrintNL.
-            inStream close.
-            ^ nil
-        ].
+	line := inStream nextLine.
+	[line notNil and:[line startsWith:'/*']] whileTrue:[
+	    line := inStream nextLine.
+	].
+	(line notNil and:[line startsWith:'"']) ifFalse:[
+	    'XPM: format error (expected color spec)' errorPrintNL.
+	    inStream close.
+	    ^ nil
+	].
 
-        s := ReadStream on:line.
-        s next. "skip quote"
-        index := s next asciiValue.
-        xlation at:index put:colorIndex - 1.
+	s := ReadStream on:line.
+	s next. "skip quote"
+	index := s next asciiValue.
+	xlation at:index put:colorIndex - 1.
 
-        lineDone := false.
-        [lineDone] whileFalse:[
-            s skipSeparators.
-            char := s peek.
-            char == $" ifTrue:[
-                lineDone := true
-            ] ifFalse:[
-                char == $s ifTrue:[
-                    "
-                     symbolic name
-                    "
-                    s next.
-                    s skipSeparators.
-                    s nextWord.    
-                    s skipSeparators.
-                ] ifFalse:[
-                    char == $m ifTrue:[
-                        "
-                         monochrome data
-                        "
-                        s next.
-                        s skipSeparators.
-                        s nextWord.
-                        s skipSeparators.
-                    ] ifFalse:[
-                        (char == $g) ifTrue:[
-                            "
-                             greyscale data
-                            "
-                            s next.
-                            s peek == 4 ifTrue:[s next].
-                            s skipSeparators.
-                            s nextWord.
-                            s skipSeparators.
-                        ] ifFalse:[
-                            (char == $c) ifTrue:[
-                                "
-                                 color data
-                                "
-                                s next.
-                                s skipSeparators.
-                                colorName := self colorNameFrom:s.
-                                s skipSeparators.
-                            ] ifFalse:[
-                                'XPM: format error (expected ''c'',''m'',''g'' or ''s'')' errorPrintNL.
-                                inStream close.
-                                ^ nil
-                            ].
-                        ]
-                    ]
-                ]
-            ].
-        ].
-        ((colorName = 'none') or:[colorName = 'None']) ifTrue:[
-            "mhmh must add mask to Image-instances soon ..."
-            color := Color white
-        ] ifFalse:[
-            color := Color name:colorName.
-        ].
-        redMap at:colorIndex put:(color red * 255 // 100).
-        greenMap at:colorIndex put:(color green * 255 // 100).
-        blueMap at:colorIndex put:(color blue * 255 // 100).
+	lineDone := false.
+	[lineDone] whileFalse:[
+	    s skipSeparators.
+	    char := s peek.
+	    char == $" ifTrue:[
+		lineDone := true
+	    ] ifFalse:[
+		char == $s ifTrue:[
+		    "
+		     symbolic name
+		    "
+		    s next.
+		    s skipSeparators.
+		    s nextWord.    
+		    s skipSeparators.
+		] ifFalse:[
+		    char == $m ifTrue:[
+			"
+			 monochrome data
+			"
+			s next.
+			s skipSeparators.
+			s nextWord.
+			s skipSeparators.
+		    ] ifFalse:[
+			(char == $g) ifTrue:[
+			    "
+			     greyscale data
+			    "
+			    s next.
+			    s peek == 4 ifTrue:[s next].
+			    s skipSeparators.
+			    s nextWord.
+			    s skipSeparators.
+			] ifFalse:[
+			    (char == $c) ifTrue:[
+				"
+				 color data
+				"
+				s next.
+				s skipSeparators.
+				colorName := self colorNameFrom:s.
+				s skipSeparators.
+			    ] ifFalse:[
+				'XPM: format error (expected ''c'',''m'',''g'' or ''s'')' errorPrintNL.
+				inStream close.
+				^ nil
+			    ].
+			]
+		    ]
+		]
+	    ].
+	].
+	((colorName = 'none') or:[colorName = 'None']) ifTrue:[
+	    "mhmh must add mask to Image-instances soon ..."
+	    color := Color white
+	] ifFalse:[
+	    color := Color name:colorName.
+	].
+	redMap at:colorIndex put:(color red * 255 // 100).
+	greenMap at:colorIndex put:(color green * 255 // 100).
+	blueMap at:colorIndex put:(color blue * 255 // 100).
     ].
 
     "actually, could make it an image with less depth most of the time ..."
@@ -259,24 +265,24 @@
 
     dstIndex := 1.
     1 to:height do:[:row |
-        line := inStream nextLine withoutSpaces.
-        [line notNil and:[line startsWith:'/*']] whileTrue:[
-            line := inStream nextLine withoutSpaces.
-        ].
-        (line notNil and:[line startsWith:'"']) ifFalse:[
-            'XPM: format error (expected pixels)' errorPrintNL.
-            inStream close.
-            ^ nil
-        ].
-        srcIndex := 2.
-        1 to: width do:[:col |
-            |char|
+	line := inStream nextLine withoutSpaces.
+	[line notNil and:[line startsWith:'/*']] whileTrue:[
+	    line := inStream nextLine withoutSpaces.
+	].
+	(line notNil and:[line startsWith:'"']) ifFalse:[
+	    'XPM: format error (expected pixels)' errorPrintNL.
+	    inStream close.
+	    ^ nil
+	].
+	srcIndex := 2.
+	1 to: width do:[:col |
+	    |char|
 
-            char := line at:srcIndex.
-            data at:dstIndex put:(xlation at:char asciiValue).
-            srcIndex := srcIndex + 1.
-            dstIndex := dstIndex + 1
-        ]
+	    char := line at:srcIndex.
+	    data at:dstIndex put:(xlation at:char asciiValue).
+	    srcIndex := srcIndex + 1.
+	    dstIndex := dstIndex + 1
+	]
     ].
 
     photometric := #palette.