BlitImageReader.st
author Claus Gittinger <cg@exept.de>
Thu, 09 Nov 1995 17:57:45 +0100
changeset 113 465cc202f0fe
parent 112 9b59ed94db13
child 114 e577a2f332d0
permissions -rw-r--r--
*** empty log message ***

'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.2 1995-11-09 16:57:45 cg Exp $
"

    "Created: 9.11.1995 / 17:08:06 / cg"
!

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

    "Created: 9.11.1995 / 17:08:06 / cg"
    "Modified: 9.11.1995 / 17:08:26 / cg"
!

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

    "Created: 9.11.1995 / 17:08:06 / cg"
    "Modified: 9.11.1995 / 17:08:42 / cg"
!

history

    "Created: 9.11.1995 / 17:08:06 / cg"
    "Modified: 9.11.1995 / 17:08:06 / cg"
! !

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

fromCompressedString:aString
    "since I am not willing to 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.
        ^ nil
    ].

    img := self fromStream:s.
    s close.
    ^ 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!