MacOSXIconReader.st
author Claus Gittinger <cg@exept.de>
Mon, 06 May 2013 16:37:12 +0200
changeset 3121 98e10307cc6a
child 3132 32f94ccd6bf0
permissions -rw-r--r--
initial checkin

"
 COPYRIGHT (c) 2013 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.
"
"{ Package: 'stx:libview2' }"

ImageReader subclass:#MacOSXIconReader
	instanceVariableNames:'image'
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

!MacOSXIconReader class methodsFor:'documentation'!

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

documentation
"
    Reader for mac osx icon files.

    These files are actually bundles of a sequence of icons (in possibly different resolutions,
    colors and sizes).
    When such a file is read, I return the first image as usual, 
    and all images as an imagesequence.

    Only a subset of the supported image formats are supported by this reader
    (i.e. JPEG and PNG based image encodings only). This means, that only 10.8-and later
    icon files are really supported.

    [See also:]
        Image Form Icon
        GIFReader JPEGReader PNGReader TIFFReader WindowsIconReader
"
! !

!MacOSXIconReader class methodsFor:'initialization'!

initialize
    "install myself in the Image classes fileFormat table
     for the `.icns' extension."

    "/ MIMETypes defineImageType:'image/x-icns' suffix:'icns'  reader:self.
    MIMETypes defineImageType:nil          suffix:'icns' reader:self.
! !

!MacOSXIconReader class methodsFor:'testing'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     Assuming that we store in PNG format, delegate that decision."

    ^ PNGReader canRepresent:anImage
!

isValidImageFile:aFileName
    "return true, if aFileName is an apple osx icon file"

    |id inStream|

    inStream := self streamReadingFile:aFileName.
    inStream isNil ifTrue:[^ false].

    inStream text.

    id := String new:4.
    inStream nextBytes:4 into:id.
    inStream close.

    ^ (id = 'icns')
! !

!MacOSXIconReader methodsFor:'image reading'!

fromStream:aStream
    "read a stream containing an icon image (or a collection of images).
     Leave image description in instance variables."

    |sizeRemaining id img firstImage frame imageCount chunkType numChunkBytes chunkData|

    inStream := aStream.
    aStream text.

    "icon-files are always msb"
    byteOrder := #msb.

    id := aStream nextBytes:4.
    id size ~~ 4 ifTrue:[
        ^ self fileFormatError:'not an icns file (short read)'.
    ].
    id := id asString.

    (id ~= 'icns') ifTrue:[
        ^ self fileFormatError:('not an icns file (id=''' , id , ''')').
    ].

    imageCount := 0.
    sizeRemaining := aStream nextUnsignedLongMSB:true.
    sizeRemaining := sizeRemaining - 4 - 4. "/ file magic and size are included in count
    [ sizeRemaining > 0 ] whileTrue:[
        chunkType := aStream nextBytes:4.
        chunkType size ~~ 4 ifTrue:[
            ^ self fileFormatError:'not an icns file (short read on icon type)'.
        ].
        chunkType := chunkType asString.

        numChunkBytes := aStream nextUnsignedLongMSB:true.
        numChunkBytes := numChunkBytes - 4 - 4. "/ type and size are included in count

        chunkData := aStream next:numChunkBytes.
        sizeRemaining := sizeRemaining - 4 - numChunkBytes.

        img := self readSingleIcon:chunkType from:chunkData.
        imageCount == 0 ifTrue:[
            firstImage := image := img.
        ] ifFalse:[
            imageCount == 1 ifTrue:[
                imageSequence := ImageSequence new.
                img imageSequence:imageSequence.

                "/ add frame for first image.
                frame := ImageFrame new image:firstImage.
                imageSequence add:frame.
            ].  
            img imageSequence:imageSequence.

            "/ add frame for this image.
            frame := ImageFrame new image:img.
            imageSequence add:frame.
        ].
        imageCount := imageCount + 1.
    ].

    "
     Image fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

readSingleIcon:iconType from:iconBytes
    "read a single image from the inputStream."

    ^ self 
        perform:('read_',(iconType copyReplaceAll:$# with:$_),'_from:') asSymbol 
        with:iconBytes
        ifNotUnderstood:[
            self breakPoint:#cg.
self halt.
            ('MacOSXIconReader: unsupported icon format: ',iconType) infoPrintCR.
            ^ self fileFormatError:'unsupported icon format: ',iconType
        ].

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
! !

!MacOSXIconReader methodsFor:'image writing'!

save:anImage onStream:aStream
    "save an icon to aStream."

    self saveAll:(Array with:anImage) onStream:aStream.

    "
     self 
        save:(Image fromScreen:(0@0 corner:16@16))
        onFile:'test.icns'
    "
!

saveAll:aCollectionOfImages onStream:aStream
    "save a number of images to aStream."

    |tempFile tempFileStream|

    (aCollectionOfImages conform:
        [:eachImage |
            (eachImage width = eachImage height)
            and:[ (#(16 32 128 256 512 1024) includes:eachImage width)]
        ]
    ) ifFalse:[
        ^ self fileFormatError:'unsupported image size (must be square and width 16, 32, 128, 512 or 1024)'.
    ].

    tempFile := Filename newTemporary asAutoDeletedFilename.
    tempFileStream := tempFile writeStream.
    tempFileStream binary.

    aCollectionOfImages do:[:eachImage |
        |typeCode s data|

        s := WriteStream on:(ByteArray new:1024).
        PNGReader save:eachImage onStream:s.
        data := s contents.
        self assert:data notEmptyOrNil.

        typeCode := #(16 32 128 256 512 1024) 
                    map: #('ipc4' 'ipc5' 'ic07' 'ic08' 'ic09' 'ic10')
                    at:eachImage width ifAbsent:[self error]. 
        tempFileStream nextPutBytes:typeCode.
        tempFileStream nextPutLong:(data size + 4 + 4) MSB:true.
        tempFileStream nextPutAll:data.
    ].
    tempFileStream close.

    aStream binary.
    aStream nextPutBytes:'icns'.
    aStream nextPutLong:(tempFile fileSize + 4 + 4) MSB:true.
    aStream nextPutAll:(tempFile binaryContentsOfEntireFile).
    tempFile delete.

    "
     self 
        save:(Image fromScreen:(0@0 corner:16@16))
        onFile:'test.icns'
    "
! !

!MacOSXIconReader methodsFor:'private'!

makeImage
    "image is already made"

    ^ image
! !

!MacOSXIconReader methodsFor:'private reading'!

readPNGOrJPEGFrom:bytes expectedSize:expectedSizeOrNil
    "read a PNG or JPEG image.
     Helper for ipc4, ipc5, ic07, ic09, ic10 formats"

    |img|

    img := PNGReader fromStream:(bytes readStream).
    img isNil ifTrue:[
        img := JPEGReader fromStream:(bytes readStream).
    ].
    expectedSizeOrNil notNil ifTrue:[
        self assert:(img width = expectedSizeOrNil).
        self assert:(img height = expectedSizeOrNil).
    ].
    ^ img
!

read_ICN__from:bytes
    "read an ICN# format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_ic07_from:bytes
    "read an ic07 (PNG or JPEG, 128) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:128.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_ic08_from:bytes
    "read an ic08 (PNG or JPEG, 256) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:256.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_ic09_from:bytes
    "read an ic09 (PNG or JPEG, 512) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:512.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_ic10_from:bytes
    "read an ic10 (PNG or JPEG, 1024) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:1024.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_icl8_from:bytes
    "read an icl8 format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_ics8_from:bytes
    "read an ics8 format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_ics__from:bytes
    "read an ics# format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_il32_from:bytes
    "read an il32 format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_ipc4_from:bytes
    "read an ipc4 (PNG or JPEG, 16x16) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:16.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_ipc5_from:bytes
    "read an ipc5 (PNG or JPEG, 32) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:32.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'test.icns'
    "
!

read_is32_from:bytes
    "read an is32 format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_it32_from:bytes
    "read an it32 format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_l8mk_from:bytes
    "read an l8mk format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_s8mk_from:bytes
    "read an s8mk format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
!

read_t8mk_from:bytes
    "read an t8mk format icon"

self halt.
    ^ nil

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
    "
! !

!MacOSXIconReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/MacOSXIconReader.st,v 1.1 2013-05-06 14:37:12 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libview2/MacOSXIconReader.st,v 1.1 2013-05-06 14:37:12 cg Exp $'
! !


MacOSXIconReader initialize!