BlitImageReader.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 11:34:06 +0100
changeset 134 f83c245371c2
parent 133 57daa569a22b
child 141 977cb52010f9
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1995 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.
"

'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'
!

!BlitImageReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/BlitImageReader.st,v 1.5 1995-12-04 12:08:59 cg Exp $'
!

documentation
"
    A q&d hack to read 48x48x1 Blit images (faces)
"
!

examples
"
    Image fromFile:'.../.../48x48x1'
"
!

copyright 
"
 COPYRIGHT (c) 1995 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.
"
! !

!BlitImageReader class methodsFor:'initialization'!

initialize
    Image fileFormats at:'48x48x1'  put:self.

    "
     BlitImageReader initialize
    "

    "Created: 9.11.1995 / 17:05:04 / cg"
    "Modified: 9.11.1995 / 17:06:28 / cg"
! !

!BlitImageReader class methodsFor:'special formats'!

uncompressString:aString
    "given a compressed string (as present in mail-headers),
     return a string in 48x48x1 BlitImage fromat.
     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 str|

    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
    ].

    str := s contents asString.
    s close.
    f delete.
    ^ str

    "   
     |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 uncompressString:s
    "

    "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"

    ^ aFileName = '48x48x1'

    "Created: 9.11.1995 / 17:04:29 / cg"
! !

!BlitImageReader methodsFor:'reading'!

fromStream:aStream
    |line 
     dstIndex "{ Class: SmallInteger }"
     bytesPerRow
     s words nm|

    width := height := 48.
    bytesPerRow := width // 8.

    data := ByteArray new:(bytesPerRow * height).
    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|

		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
	    ]
	]
    ].


    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1)

    "
     BlitImageReader fromFile:'/tmp/faces/facedir/facedir/misc./acsnet/48x48x1'
    "

    "Created: 9.11.1995 / 17:03:04 / cg"
! !

BlitImageReader initialize!