commentary
authorClaus Gittinger <cg@exept.de>
Tue, 23 Apr 1996 12:50:41 +0200
changeset 206 975f42e01bb1
parent 205 ddb3c0dfcc0d
child 207 ae381eaf10d4
commentary
BlitImageReader.st
BlitImgRdr.st
--- a/BlitImageReader.st	Tue Apr 23 12:44:35 1996 +0200
+++ b/BlitImageReader.st	Tue Apr 23 12:50:41 1996 +0200
@@ -10,33 +10,15 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.8 on 9-nov-1995 at 17:56:18'                    !
-
 ImageReader subclass:#BlitImageReader
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Graphics-Images support'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Images support'
 !
 
 !BlitImageReader class methodsFor:'documentation'!
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/BlitImageReader.st,v 1.6 1995-12-12 17:37:50 cg Exp $'
-!
-
-documentation
-"
-    A q&d hack to read 48x48x1 Blit images (faces)
-"
-!
-
-examples
-"
-    Image fromFile:'.../.../48x48x1'
-"
-!
-
 copyright 
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
@@ -49,23 +31,88 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+!
+
+documentation
+"
+    A q&d hack to read 48x48x1 Blit images (faces)
+    A variation of this format is also used to pass face-icons in mail headers
+    (X-face: header line).
+    To support those, images can also be read from a string which is
+    encoded in that format (see: #fromCompressedString:).
+
+    [See also:]
+        GIFReader FaceReader JPEGReader PBMReader PCXReader 
+        ST80FormReader SunRasterReader TIFFReader WindowsIconReader 
+        XBMreader XPMReader XWDReader 
+"
+!
+
+examples
+"
+    Image fromFile:'.../.../48x48x1'
+"
 ! !
 
 !BlitImageReader class methodsFor:'initialization'!
 
 initialize
+    "install myself in the Image classes fileFormat table
+     for files named `48x48x1' (funny)."
+
     Image fileFormats at:'48x48x1'  put:self.
 
     "
      BlitImageReader initialize
     "
 
-    "Created: 9.11.1995 / 17:05:04 / cg"
-    "Modified: 9.11.1995 / 17:06:28 / cg"
+    "Modified: 23.4.1996 / 12:47:48 / cg"
 ! !
 
 !BlitImageReader class methodsFor:'special formats'!
 
+fromCompressedString:aString
+    "given a compressed image string (such as present in mail headers),
+     return a Depth1Image for it.
+     Since I am not willing to port/include the uncompface stuff into ST/X,
+     open a pipe to the uncompressor.
+     If you dont have compface/uncompface, get it from your nearest ftp server."
+
+    |f s img|
+
+    f := Filename newTemporary.
+    s := f writeStream.
+    s nextPutAll:aString.
+    s close.
+
+    s := PipeStream readingFrom:('uncompface ' , f name).
+    s isNil ifTrue:[
+	'BLITIMGREADER: no uncompface utility.' errorPrintNL.
+	f delete.
+	^ nil
+    ].
+
+    img := self fromStream:s.
+    s close.
+    f delete.
+    ^ img
+
+    "   
+     |s|
+
+     s := '
+Iqsa(US9p?)Y^W
++6Ff[Z]<t?\A!!eaL''DG{20*#{C1;''Ct&}L}B^/1(aYI@hP)4!!<}7D=2gm
+8!!$T`8QNfK<te\20%A\`wm*wa2' , Character doubleQuote asString , '^Up*Qs' , Character doubleQuote asString ,
+'X}KeV*3XeB2te&sKp*t`N;^BDh[6=K{ZBE=O>rM' , Character doubleQuote asString , 'uFE)
+lFDjag1e]\/#2'.
+    BlitImageReader fromCompressedString:s
+    "
+
+    "Created: 9.11.1995 / 17:55:19 / cg"
+    "Modified: 9.11.1995 / 17:56:07 / cg"
+!
+
 uncompressString:aString
     "given a compressed string (as present in mail-headers),
      return a string in 48x48x1 BlitImage fromat.
@@ -106,63 +153,24 @@
 
     "Created: 9.11.1995 / 17:55:19 / cg"
     "Modified: 21.11.1995 / 19:28:41 / cg"
-!
-
-fromCompressedString:aString
-    "given a compressed image string (such as present in mail headers),
-     return a Depth1Image for it.
-     Since I am not willing to port/include the uncompface stuff into ST/X,
-     open a pipe to the uncompressor.
-     If you dont have compface/uncompface, get it from your nearest ftp server."
-
-    |f s img|
-
-    f := Filename newTemporary.
-    s := f writeStream.
-    s nextPutAll:aString.
-    s close.
-
-    s := PipeStream readingFrom:('uncompface ' , f name).
-    s isNil ifTrue:[
-	'BLITIMGREADER: no uncompface utility.' errorPrintNL.
-	f delete.
-	^ nil
-    ].
-
-    img := self fromStream:s.
-    s close.
-    f delete.
-    ^ img
-
-    "   
-     |s|
-
-     s := '
-Iqsa(US9p?)Y^W
-+6Ff[Z]<t?\A!!eaL''DG{20*#{C1;''Ct&}L}B^/1(aYI@hP)4!!<}7D=2gm
-8!!$T`8QNfK<te\20%A\`wm*wa2' , Character doubleQuote asString , '^Up*Qs' , Character doubleQuote asString ,
-'X}KeV*3XeB2te&sKp*t`N;^BDh[6=K{ZBE=O>rM' , Character doubleQuote asString , 'uFE)
-lFDjag1e]\/#2'.
-    BlitImageReader fromCompressedString:s
-    "
-
-    "Created: 9.11.1995 / 17:55:19 / cg"
-    "Modified: 9.11.1995 / 17:56:07 / cg"
 ! !
 
 !BlitImageReader class methodsFor:'testing'!
 
 isValidImageFile:aFileName
-    "return true, if aFileName contains a GIF image"
+    "return true, if aFileName contains a BlitImage image"
 
     ^ aFileName = '48x48x1'
 
     "Created: 9.11.1995 / 17:04:29 / cg"
+    "Modified: 23.4.1996 / 12:48:01 / cg"
 ! !
 
 !BlitImageReader methodsFor:'reading'!
 
 fromStream:aStream
+    "read an image in my format from aStream"
+
     |line 
      dstIndex "{ Class: SmallInteger }"
      bytesPerRow
@@ -175,23 +183,23 @@
     dstIndex := 1.
 
     [aStream atEnd] whileFalse:[
-	line := aStream nextLine.
-	line notNil ifTrue:[
-	    words := (line asCollectionOfSubstringsSeparatedBy:$,) asOrderedCollection.
-	    words last isEmpty ifTrue:[
-		words removeLast
-	    ].
-	    words do:[:w |
-		|s bits|
+        line := aStream nextLine.
+        line notNil ifTrue:[
+            words := (line asCollectionOfSubstringsSeparatedBy:$,) asOrderedCollection.
+            words last isEmpty ifTrue:[
+                words removeLast
+            ].
+            words do:[:w |
+                |s bits|
 
-		s := w readStream.
-		s skip:2.
-		bits := Integer readFrom:s radix:16 onError:0. 
-		data at:dstIndex put:(bits bitShift:-8).
-		data at:dstIndex+1 put:(bits bitAnd:16rFF).
-		dstIndex := dstIndex + 2
-	    ]
-	]
+                s := w readStream.
+                s skip:2.
+                bits := Integer readFrom:s radix:16 onError:0. 
+                data at:dstIndex put:(bits bitShift:-8).
+                data at:dstIndex+1 put:(bits bitAnd:16rFF).
+                dstIndex := dstIndex + 2
+            ]
+        ]
     ].
 
 
@@ -204,6 +212,12 @@
     "
 
     "Created: 9.11.1995 / 17:03:04 / cg"
+    "Modified: 23.4.1996 / 12:48:15 / cg"
 ! !
 
+!BlitImageReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/BlitImageReader.st,v 1.7 1996-04-23 10:50:41 cg Exp $'
+! !
 BlitImageReader initialize!
--- a/BlitImgRdr.st	Tue Apr 23 12:44:35 1996 +0200
+++ b/BlitImgRdr.st	Tue Apr 23 12:50:41 1996 +0200
@@ -10,33 +10,15 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.8 on 9-nov-1995 at 17:56:18'                    !
-
 ImageReader subclass:#BlitImageReader
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Graphics-Images support'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Images support'
 !
 
 !BlitImageReader class methodsFor:'documentation'!
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/Attic/BlitImgRdr.st,v 1.6 1995-12-12 17:37:50 cg Exp $'
-!
-
-documentation
-"
-    A q&d hack to read 48x48x1 Blit images (faces)
-"
-!
-
-examples
-"
-    Image fromFile:'.../.../48x48x1'
-"
-!
-
 copyright 
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
@@ -49,23 +31,88 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+!
+
+documentation
+"
+    A q&d hack to read 48x48x1 Blit images (faces)
+    A variation of this format is also used to pass face-icons in mail headers
+    (X-face: header line).
+    To support those, images can also be read from a string which is
+    encoded in that format (see: #fromCompressedString:).
+
+    [See also:]
+        GIFReader FaceReader JPEGReader PBMReader PCXReader 
+        ST80FormReader SunRasterReader TIFFReader WindowsIconReader 
+        XBMreader XPMReader XWDReader 
+"
+!
+
+examples
+"
+    Image fromFile:'.../.../48x48x1'
+"
 ! !
 
 !BlitImageReader class methodsFor:'initialization'!
 
 initialize
+    "install myself in the Image classes fileFormat table
+     for files named `48x48x1' (funny)."
+
     Image fileFormats at:'48x48x1'  put:self.
 
     "
      BlitImageReader initialize
     "
 
-    "Created: 9.11.1995 / 17:05:04 / cg"
-    "Modified: 9.11.1995 / 17:06:28 / cg"
+    "Modified: 23.4.1996 / 12:47:48 / cg"
 ! !
 
 !BlitImageReader class methodsFor:'special formats'!
 
+fromCompressedString:aString
+    "given a compressed image string (such as present in mail headers),
+     return a Depth1Image for it.
+     Since I am not willing to port/include the uncompface stuff into ST/X,
+     open a pipe to the uncompressor.
+     If you dont have compface/uncompface, get it from your nearest ftp server."
+
+    |f s img|
+
+    f := Filename newTemporary.
+    s := f writeStream.
+    s nextPutAll:aString.
+    s close.
+
+    s := PipeStream readingFrom:('uncompface ' , f name).
+    s isNil ifTrue:[
+	'BLITIMGREADER: no uncompface utility.' errorPrintNL.
+	f delete.
+	^ nil
+    ].
+
+    img := self fromStream:s.
+    s close.
+    f delete.
+    ^ img
+
+    "   
+     |s|
+
+     s := '
+Iqsa(US9p?)Y^W
++6Ff[Z]<t?\A!!eaL''DG{20*#{C1;''Ct&}L}B^/1(aYI@hP)4!!<}7D=2gm
+8!!$T`8QNfK<te\20%A\`wm*wa2' , Character doubleQuote asString , '^Up*Qs' , Character doubleQuote asString ,
+'X}KeV*3XeB2te&sKp*t`N;^BDh[6=K{ZBE=O>rM' , Character doubleQuote asString , 'uFE)
+lFDjag1e]\/#2'.
+    BlitImageReader fromCompressedString:s
+    "
+
+    "Created: 9.11.1995 / 17:55:19 / cg"
+    "Modified: 9.11.1995 / 17:56:07 / cg"
+!
+
 uncompressString:aString
     "given a compressed string (as present in mail-headers),
      return a string in 48x48x1 BlitImage fromat.
@@ -106,63 +153,24 @@
 
     "Created: 9.11.1995 / 17:55:19 / cg"
     "Modified: 21.11.1995 / 19:28:41 / cg"
-!
-
-fromCompressedString:aString
-    "given a compressed image string (such as present in mail headers),
-     return a Depth1Image for it.
-     Since I am not willing to port/include the uncompface stuff into ST/X,
-     open a pipe to the uncompressor.
-     If you dont have compface/uncompface, get it from your nearest ftp server."
-
-    |f s img|
-
-    f := Filename newTemporary.
-    s := f writeStream.
-    s nextPutAll:aString.
-    s close.
-
-    s := PipeStream readingFrom:('uncompface ' , f name).
-    s isNil ifTrue:[
-	'BLITIMGREADER: no uncompface utility.' errorPrintNL.
-	f delete.
-	^ nil
-    ].
-
-    img := self fromStream:s.
-    s close.
-    f delete.
-    ^ img
-
-    "   
-     |s|
-
-     s := '
-Iqsa(US9p?)Y^W
-+6Ff[Z]<t?\A!!eaL''DG{20*#{C1;''Ct&}L}B^/1(aYI@hP)4!!<}7D=2gm
-8!!$T`8QNfK<te\20%A\`wm*wa2' , Character doubleQuote asString , '^Up*Qs' , Character doubleQuote asString ,
-'X}KeV*3XeB2te&sKp*t`N;^BDh[6=K{ZBE=O>rM' , Character doubleQuote asString , 'uFE)
-lFDjag1e]\/#2'.
-    BlitImageReader fromCompressedString:s
-    "
-
-    "Created: 9.11.1995 / 17:55:19 / cg"
-    "Modified: 9.11.1995 / 17:56:07 / cg"
 ! !
 
 !BlitImageReader class methodsFor:'testing'!
 
 isValidImageFile:aFileName
-    "return true, if aFileName contains a GIF image"
+    "return true, if aFileName contains a BlitImage image"
 
     ^ aFileName = '48x48x1'
 
     "Created: 9.11.1995 / 17:04:29 / cg"
+    "Modified: 23.4.1996 / 12:48:01 / cg"
 ! !
 
 !BlitImageReader methodsFor:'reading'!
 
 fromStream:aStream
+    "read an image in my format from aStream"
+
     |line 
      dstIndex "{ Class: SmallInteger }"
      bytesPerRow
@@ -175,23 +183,23 @@
     dstIndex := 1.
 
     [aStream atEnd] whileFalse:[
-	line := aStream nextLine.
-	line notNil ifTrue:[
-	    words := (line asCollectionOfSubstringsSeparatedBy:$,) asOrderedCollection.
-	    words last isEmpty ifTrue:[
-		words removeLast
-	    ].
-	    words do:[:w |
-		|s bits|
+        line := aStream nextLine.
+        line notNil ifTrue:[
+            words := (line asCollectionOfSubstringsSeparatedBy:$,) asOrderedCollection.
+            words last isEmpty ifTrue:[
+                words removeLast
+            ].
+            words do:[:w |
+                |s bits|
 
-		s := w readStream.
-		s skip:2.
-		bits := Integer readFrom:s radix:16 onError:0. 
-		data at:dstIndex put:(bits bitShift:-8).
-		data at:dstIndex+1 put:(bits bitAnd:16rFF).
-		dstIndex := dstIndex + 2
-	    ]
-	]
+                s := w readStream.
+                s skip:2.
+                bits := Integer readFrom:s radix:16 onError:0. 
+                data at:dstIndex put:(bits bitShift:-8).
+                data at:dstIndex+1 put:(bits bitAnd:16rFF).
+                dstIndex := dstIndex + 2
+            ]
+        ]
     ].
 
 
@@ -204,6 +212,12 @@
     "
 
     "Created: 9.11.1995 / 17:03:04 / cg"
+    "Modified: 23.4.1996 / 12:48:15 / cg"
 ! !
 
+!BlitImageReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/Attic/BlitImgRdr.st,v 1.7 1996-04-23 10:50:41 cg Exp $'
+! !
 BlitImageReader initialize!