MacOSXIconReader.st
author Stefan Vogel <sv@exept.de>
Fri, 31 Mar 2017 16:31:43 +0200
changeset 3946 3aa94b58d2b0
parent 3937 95c7ec9f0a7e
child 4188 f9e164682d74
permissions -rw-r--r--
#REFACTORING by stefan class: BlockValue changed: #setArguments:

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

"{ NameSpace: Smalltalk }"

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/writer 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 the writer
    (i.e. JPEG and PNG based image encodings only). 
    This means, that only 10.8-and later icon files are really generated.

    [caveat:]
        only a subset of the possibly formats are supported.

    [notice:]
        when reading an ICNS file with multiple icons in it,
        the first image is returned as such, holding on the other images in its
        imageFrames instvar.
        Thus, the imageEditor will usually present the first of the images,
        and offer a next-in-sequence button to step through them.
        To get a collection of all images, collect the images from the sequence, as in:
            someIcoImage imageFrames collect:#image

    [supported formats:]
    
    support   format   length                pixels  OS-version  description
    -----------------------------------------------------------------------------   
    r           ICON    128                     32      1.0     32×32 1-bit mono icon
    r           ICN#    256                     32      6.0     32×32 1-bit mono icon with 1-bit mask
                icm#    48                      16      6.0     16×12 1 bit mono icon with 1-bit mask
                icm4    96                      16      7.0     16×12 4 bit icon
                icm8    192                     16      7.0     16×12 8 bit icon
    r           ics#    64 (32 img + 32 mask)   16      6.0     16×16 1-bit mask
    r           ics4    128                     16      7.0     16×16 4-bit icon
    r           ics8    256                     16      7.0     16x16 8 bit icon
                is32    varies (768)            16      8.5     16×16 24-bit icon
    r           s8mk    256                     16      8.5     16x16 8-bit mask
    r           icl4    512                     32      7.0     32×32 4-bit icon
    r           icl8    1,024                   32      7.0     32×32 8-bit icon
    r           il32    varies (3,072)          32      8.5     32x32 24-bit icon
    r           l8mk    1,024                   32      8.5     32×32 8-bit mask
    r           ich#    288                     48      8.5     48×48 1-bit mask
    r           ich4    1,152                   48      8.5     48×48 4-bit icon
    r           ich8    2,304                   48      8.5     48×48 8-bit icon
    r           ih32    varies (6,912)          48      8.5     48×48 24-bit icon
    r           h8mk    2,304                   48      8.5     48×48 8-bit mask
    r           it32    varies (49,152)        128     10.0    128×128 24-bit icon
    r           t8mk    16,384                 128     10.0    128×128 8-bit mask
    r           icp4    varies                  16     10.7    16x16 icon in JPEG 2000 or PNG format
    r           icp5    varies                  32     10.7    32x32 icon in JPEG 2000 or PNG format
                icp6    varies                  64     10.7    64x64 icon in JPEG 2000 or PNG format
    r           ic07    varies                 128     10.7    128x128 icon in JPEG 2000 or PNG format
    r           ic08    varies                 256     10.5    256×256 icon in JPEG 2000 or PNG format
    r           ic09    varies                 512     10.5    512×512 icon in JPEG 2000 or PNG format
    r           ic10    varies                1024     10.7    1024×1024 in 10.7 (or 512x512@2x 'retina' in 10.8) icon in JPEG 2000 or PNG format
                ic11    varies                  32     10.8    16x16@2x 'retina' icon in JPEG 2000 or PNG format
                ic12    varies                  64     10.8    32x32@2x 'retina' icon in JPEG 2000 or PNG format
                ic13    varies                 256     10.8    128x128@2x 'retina' icon in JPEG 2000 or PNG format
                ic14    varies                 512     10.8    256x256@2x 'retina' icon in JPEG 2000 or PNG format

     Other types (ignored):
               'TOC '   varies          'Table of Contents' 
                                        a list of all image types in the file, 
                                        and their sizes (added in Mac OS X 10.7)

                'icnV'  4               4-byte big endian float 
                                        - equal to the bundle version number of Icon Composer.app that created to icon

    [See also:]
        Image Form Icon
        GIFReader JPEGReader PNGReader TIFFReader WindowsIconReader
        http://en.wikipedia.org/wiki/Apple_Icon_Image_format
"
! !

!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.
    sizeRemaining := aStream nextUnsignedInt32MSB:true.
    sizeRemaining := sizeRemaining - 4 - 4. "/ file magic and size are included in count

    (id ~= 'icns') ifTrue:[
        chunkData := aStream next:sizeRemaining.
        image := self readSingleIcon:chunkType from:chunkData.
        ^ self
    ].

    imageCount := 0.
    [ sizeRemaining > 0 ] whileTrue:[
        chunkType := aStream next:4.
        chunkType size ~~ 4 ifTrue:[
            ^ self fileFormatError:'not an icns file (short read on icon type)'.
        ].
        chunkType := chunkType asString.

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

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

        img := self readSingleIcon:chunkType from:chunkData.
        "/ unsupported images are skipped...
        img notNil ifTrue:[
            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.
                ].  

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

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

    "Modified: / 22-02-2017 / 10:24:38 / cg"
!

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

    Logger info:'ICNSReader: read %1' with:iconType.

    ^ Error handle:[:ex |
        self fileFormatError:'internal error while reading: ',iconType.
        nil
    ] do:[
        |img|

        img := self 
            perform:('read_',(iconType copyReplaceAny:#( $# $ ) with:$_),'_from:') asSymbol 
            with:iconBytes
            ifNotUnderstood:[
                self breakPoint:#cg.
                ('MacOSXIconReader: unsupported icon format: ',iconType) infoPrintCR.
                self fileFormatError:'unsupported icon format: ',iconType.
                nil
            ].
        "/ img inspect.    
        img    
    ].

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

    "Modified: / 08-02-2017 / 19:08:05 / stefan"
    "Modified: / 22-02-2017 / 12:11:30 / cg"
! !

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

    |tempStream|

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

    tempStream := ReadWriteStream on:(ByteArray new:1024).

    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 64 128 256 512 1024) 
                    map: #('ipc4' 'ipc5' 'ipc6' 'ic07' 'ic08' 'ic09' 'ic10')
                    at:eachImage width ifAbsent:[self error]. 
        tempStream
            nextPutBytes:typeCode;
            nextPutInt32:(data size + 4 + 4) MSB:true;
            nextPutAll:data.
    ].

    aStream 
        binary;
        nextPutBytes:'icns';
        nextPutInt32:(tempStream position + 4 + 4) MSB:true;
        nextPutAll:(tempStream contents).

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

     Image fromFile:'test.icns'

     ImageSequence
     MacOSXIconReader
         saveAll:{
                    (Image fromScreen:(0@0 corner:16@16)) .
                    (Image fromScreen:(0@0 corner:32@32)) .
                    (Image fromScreen:(0@0 corner:64@64)) .
                    (Image fromScreen:(0@0 corner:128@128)) .
                 }
         onFile:'test.icns'   
    "

    "Modified: / 22-02-2017 / 12:16:07 / cg"
! !

!MacOSXIconReader methodsFor:'private'!

colormap4
    ^ #[
           16rFF 16rFF 16rFF
           16rFC 16rF3 16r05
           16rFF 16r64 16r02
           16rDD 16r08 16r06
           16rF2 16r08 16r84
           16r46 16r00 16rA5
           16r00 16r00 16rD4
           16r02 16rAB 16rEA
           16r1F 16rB7 16r14
           16r00 16r64 16r11
           16r56 16r2C 16r05
           16r90 16r71 16r3A
           16rC0 16rC0 16rC0
           16r80 16r80 16r80
           16r40 16r40 16r40
           16r00 16r00 16r00
    ]
!

colormap8
    ^ #[
           16rFF 16rFF 16rFF
           16rFF 16rFF 16rCC
           16rFF 16rFF 16r99
           16rFF 16rFF 16r66
           16rFF 16rFF 16r33
           16rFF 16rFF 16r00
           16rFF 16rCC 16rFF
           16rFF 16rCC 16rCC
           16rFF 16rCC 16r99
           16rFF 16rCC 16r66
           16rFF 16rCC 16r33
           16rFF 16rCC 16r00
           16rFF 16r99 16rFF
           16rFF 16r99 16rCC
           16rFF 16r99 16r99
           16rFF 16r99 16r66
           16rFF 16r99 16r33
           16rFF 16r99 16r00
           16rFF 16r66 16rFF
           16rFF 16r66 16rCC
           16rFF 16r66 16r99
           16rFF 16r66 16r66
           16rFF 16r66 16r33
           16rFF 16r66 16r00
           16rFF 16r33 16rFF
           16rFF 16r33 16rCC
           16rFF 16r33 16r99
           16rFF 16r33 16r66
           16rFF 16r33 16r33
           16rFF 16r33 16r00
           16rFF 16r00 16rFF
           16rFF 16r00 16rCC
           16rFF 16r00 16r99
           16rFF 16r00 16r66
           16rFF 16r00 16r33
           16rFF 16r00 16r00
           16rCC 16rFF 16rFF
           16rCC 16rFF 16rCC
           16rCC 16rFF 16r99
           16rCC 16rFF 16r66
           16rCC 16rFF 16r33
           16rCC 16rFF 16r00
           16rCC 16rCC 16rFF
           16rCC 16rCC 16rCC
           16rCC 16rCC 16r99
           16rCC 16rCC 16r66
           16rCC 16rCC 16r33
           16rCC 16rCC 16r00
           16rCC 16r99 16rFF
           16rCC 16r99 16rCC
           16rCC 16r99 16r99
           16rCC 16r99 16r66
           16rCC 16r99 16r33
           16rCC 16r99 16r00
           16rCC 16r66 16rFF
           16rCC 16r66 16rCC
           16rCC 16r66 16r99
           16rCC 16r66 16r66
           16rCC 16r66 16r33
           16rCC 16r66 16r00
           16rCC 16r33 16rFF
           16rCC 16r33 16rCC
           16rCC 16r33 16r99
           16rCC 16r33 16r66
           16rCC 16r33 16r33
           16rCC 16r33 16r00
           16rCC 16r00 16rFF
           16rCC 16r00 16rCC
           16rCC 16r00 16r99
           16rCC 16r00 16r66
           16rCC 16r00 16r33
           16rCC 16r00 16r00
           16r99 16rFF 16rFF
           16r99 16rFF 16rCC
           16r99 16rFF 16r99
           16r99 16rFF 16r66
           16r99 16rFF 16r33
           16r99 16rFF 16r00
           16r99 16rCC 16rFF
           16r99 16rCC 16rCC
           16r99 16rCC 16r99
           16r99 16rCC 16r66
           16r99 16rCC 16r33
           16r99 16rCC 16r00
           16r99 16r99 16rFF
           16r99 16r99 16rCC
           16r99 16r99 16r99
           16r99 16r99 16r66
           16r99 16r99 16r33
           16r99 16r99 16r00
           16r99 16r66 16rFF
           16r99 16r66 16rCC
           16r99 16r66 16r99
           16r99 16r66 16r66
           16r99 16r66 16r33
           16r99 16r66 16r00
           16r99 16r33 16rFF
           16r99 16r33 16rCC
           16r99 16r33 16r99
           16r99 16r33 16r66
           16r99 16r33 16r33
           16r99 16r33 16r00
           16r99 16r00 16rFF
           16r99 16r00 16rCC
           16r99 16r00 16r99
           16r99 16r00 16r66
           16r99 16r00 16r33
           16r99 16r00 16r00
           16r66 16rFF 16rFF
           16r66 16rFF 16rCC
           16r66 16rFF 16r99
           16r66 16rFF 16r66
           16r66 16rFF 16r33
           16r66 16rFF 16r00
           16r66 16rCC 16rFF
           16r66 16rCC 16rCC
           16r66 16rCC 16r99
           16r66 16rCC 16r66
           16r66 16rCC 16r33
           16r66 16rCC 16r00
           16r66 16r99 16rFF
           16r66 16r99 16rCC
           16r66 16r99 16r99
           16r66 16r99 16r66
           16r66 16r99 16r33
           16r66 16r99 16r00
           16r66 16r66 16rFF
           16r66 16r66 16rCC
           16r66 16r66 16r99
           16r66 16r66 16r66
           16r66 16r66 16r33
           16r66 16r66 16r00
           16r66 16r33 16rFF
           16r66 16r33 16rCC
           16r66 16r33 16r99
           16r66 16r33 16r66
           16r66 16r33 16r33
           16r66 16r33 16r00
           16r66 16r00 16rFF
           16r66 16r00 16rCC
           16r66 16r00 16r99
           16r66 16r00 16r66
           16r66 16r00 16r33
           16r66 16r00 16r00
           16r33 16rFF 16rFF
           16r33 16rFF 16rCC
           16r33 16rFF 16r99
           16r33 16rFF 16r66
           16r33 16rFF 16r33
           16r33 16rFF 16r00
           16r33 16rCC 16rFF
           16r33 16rCC 16rCC
           16r33 16rCC 16r99
           16r33 16rCC 16r66
           16r33 16rCC 16r33
           16r33 16rCC 16r00
           16r33 16r99 16rFF
           16r33 16r99 16rCC
           16r33 16r99 16r99
           16r33 16r99 16r66
           16r33 16r99 16r33
           16r33 16r99 16r00
           16r33 16r66 16rFF
           16r33 16r66 16rCC
           16r33 16r66 16r99
           16r33 16r66 16r66
           16r33 16r66 16r33
           16r33 16r66 16r00
           16r33 16r33 16rFF
           16r33 16r33 16rCC
           16r33 16r33 16r99
           16r33 16r33 16r66
           16r33 16r33 16r33
           16r33 16r33 16r00
           16r33 16r00 16rFF
           16r33 16r00 16rCC
           16r33 16r00 16r99
           16r33 16r00 16r66
           16r33 16r00 16r33
           16r33 16r00 16r00
           16r00 16rFF 16rFF
           16r00 16rFF 16rCC
           16r00 16rFF 16r99
           16r00 16rFF 16r66
           16r00 16rFF 16r33
           16r00 16rFF 16r00
           16r00 16rCC 16rFF
           16r00 16rCC 16rCC
           16r00 16rCC 16r99
           16r00 16rCC 16r66
           16r00 16rCC 16r33
           16r00 16rCC 16r00
           16r00 16r99 16rFF
           16r00 16r99 16rCC
           16r00 16r99 16r99
           16r00 16r99 16r66
           16r00 16r99 16r33
           16r00 16r99 16r00
           16r00 16r66 16rFF
           16r00 16r66 16rCC
           16r00 16r66 16r99
           16r00 16r66 16r66
           16r00 16r66 16r33
           16r00 16r66 16r00
           16r00 16r33 16rFF
           16r00 16r33 16rCC
           16r00 16r33 16r99
           16r00 16r33 16r66
           16r00 16r33 16r33
           16r00 16r33 16r00
           16r00 16r00 16rFF
           16r00 16r00 16rCC
           16r00 16r00 16r99
           16r00 16r00 16r66
           16r00 16r00 16r33
           16rEE 16r00 16r00
           16rDD 16r00 16r00
           16rBB 16r00 16r00
           16rAA 16r00 16r00
           16r88 16r00 16r00
           16r77 16r00 16r00
           16r55 16r00 16r00
           16r44 16r00 16r00
           16r22 16r00 16r00
           16r11 16r00 16r00
           16r00 16rEE 16r00
           16r00 16rDD 16r00
           16r00 16rBB 16r00
           16r00 16rAA 16r00
           16r00 16r88 16r00
           16r00 16r77 16r00
           16r00 16r55 16r00
           16r00 16r44 16r00
           16r00 16r22 16r00
           16r00 16r11 16r00
           16r00 16r00 16rEE
           16r00 16r00 16rDD
           16r00 16r00 16rBB
           16r00 16r00 16rAA
           16r00 16r00 16r88
           16r00 16r00 16r77
           16r00 16r00 16r55
           16r00 16r00 16r44
           16r00 16r00 16r22
           16r00 16r00 16r11
           16rEE 16rEE 16rEE
           16rDD 16rDD 16rDD
           16rBB 16rBB 16rBB
           16rAA 16rAA 16rAA
           16r88 16r88 16r88
           16r77 16r77 16r77
           16r55 16r55 16r55
           16r44 16r44 16r44
           16r22 16r22 16r22
           16r11 16r11 16r11
           16r00 16r00 16r00
    ]
!

makeImage
    "image is already made"

    ^ image
! !

!MacOSXIconReader methodsFor:'private reading'!

common_read_paletteImage_from:bytes size:size width:w height:h depth:d
    "read an icl8/icl4/ics4/ics8 icon"

    |pixelData img|

    pixelData := (ByteArray new:size) replaceBytesWith:bytes; yourself.
    img := (Image implementorForDepth:d) width:w height:h fromArray:pixelData.
    img photometric:#palette.
    d == 4 ifTrue:[ 
        img colorMap:(Colormap rgbBytesVector:self colormap4).
    ] ifFalse:[ 
        d == 8 ifTrue:[ 
            img colorMap:(Colormap rgbBytesVector:self colormap8).
        ] ifFalse:[ 
            self error:'unsupported depth'
        ].
    ].
    ^ img

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

    "Modified (comment): / 22-02-2017 / 12:09:40 / cg"
!

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

    |img|

    "/ check for PNG header
    (bytes startsWith:(PNGReader pngHeader)) ifTrue:[
        img := PNGReader fromStream:(bytes readStream).
    ].    
    img isNil ifTrue:[
        img := JPEGReader fromStream:(bytes readStream).
        img isNil ifTrue:[^ nil].
    ].
    expectedSizeOrNil notNil ifTrue:[
        self assert:(img width = expectedSizeOrNil).
        self assert:(img height = expectedSizeOrNil).
    ].
    ^ img

    "Modified: / 22-02-2017 / 13:42:48 / cg"
!

readPackBitsImageFrom:compressedData offset:offset width:w height:h depth:depth
    |uncompressed redData greenData blueData bytesPerRow bytesPerChannel n srcStart rowStart|

    uncompressed := (compressedData size - offset) >= (w*h*(depth//8)).
    
    depth == 24 ifTrue:[
        "/ rgb channels separate
        bytesPerRow := w.
        bytesPerChannel := bytesPerRow * h.

        redData := ByteArray new:bytesPerChannel.
        greenData := ByteArray new:bytesPerChannel.
        blueData := ByteArray new:bytesPerChannel.

        "/ uncompressed!!
        uncompressed ifTrue:[
            self halt:'check this'.
            ^ nil
        ].
        
        srcStart := 1+offset.
        n := self class
            decompressPackBitsV2From:compressedData at:srcStart to:redData at:1 count:bytesPerChannel.
        srcStart := srcStart + n.
        n := self class
            decompressPackBitsV2From:compressedData at:srcStart to:greenData at:1 count:bytesPerChannel.
        srcStart := srcStart + n.
        n := self class
            decompressPackBitsV2From:compressedData at:srcStart to:blueData at:1 count:bytesPerChannel.
        photometric := #rgb.
        bitsPerSample := #[8 8 8].
        samplesPerPixel := 3.
        width := w.
        height := h.
        data := ByteArray new:(self bytesPerRow * h).

        rowStart := 1.
        1 to:height do:[:r |
            |ci|

            ci := rowStart.
            1 to:width do:[:c |
                data at:ci put:(redData at:c).
                data at:ci+1 put:(greenData at:c).
                data at:ci+2 put:(blueData at:c).
                ci := ci + 3.
            ].
            rowStart := rowStart + self bytesPerRow.
        ].
        ^ Depth24Image new
            width:width
            height:height
            photometric:photometric
            samplesPerPixel:samplesPerPixel
            bitsPerSample:bitsPerSample
            colorMap:nil
            bits:data
            mask:nil.
    ].
    
    depth == 8 ifTrue:[
        "/ 8bit single channel
        bytesPerRow := w.
        bytesPerChannel := bytesPerRow * h.

        compressedData size == bytesPerChannel ifTrue:[
            data := compressedData.
        ] ifFalse:[
            data := ByteArray new:bytesPerChannel.
            n := self class
                decompressPackBitsV2From:compressedData at:1+offset to:data at:1 count:bytesPerChannel.
        ].
        ^ Depth8Image new
            width:width height:height
            photometric:#blackIs0
            samplesPerPixel:1 bitsPerSample:#(8)
            colorMap:nil
            bits:data mask:nil.
    ].
    self halt:'check this'.
    ^ nil

    "Modified: / 22-02-2017 / 12:06:14 / cg"
!

read_ICN__from:bytes
    "read an ICN# format icon.
     ICN# is 32x32 bit mono with 1-bit mask"

    |pixelData maskData img|

    pixelData := (ByteArray new:128) replaceBytesFrom:1 to:128 with:bytes startingAt:1; yourself.
    maskData := (ByteArray new:128) replaceBytesFrom:1 to:128 with:bytes startingAt:128+1; yourself.
    img := Depth1Image width:32 height:32 fromArray:pixelData.
    img mask:(Depth1Image width:32 height:32 fromArray:maskData).
    ^ img
!

read_ICON_from:bytes
    "read an ICON format icon.
     128 bytes, 32x32x1 monochrome"

    |pixelData img|

    pixelData := (ByteArray new:128) replaceBytesFrom:1 to:128 with:bytes startingAt:1; yourself.
    img := Depth1Image width:32 height:32 fromArray:pixelData.
    img photometric:#whiteIs0.
    ^ img

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

read_TOC__from:bytes
    "read (actually: skip) a table of contents."

    ^ nil
!

read_h8mk_from:bytes
    "read an h8mk packbits format mask icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        self breakPoint:#cg.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:48 height:48 depth:8.

    "Modified: / 24-02-2017 / 01:39:56 / cg"
!

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

    ^ self readPNGOrJPEGFrom:bytes expectedSize:128.

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

    "Modified (comment): / 22-02-2017 / 11:02:50 / cg"
!

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

    ^ self readPNGOrJPEGFrom:bytes expectedSize:256.

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

    "Modified (comment): / 22-02-2017 / 11:02:55 / cg"
!

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

    ^ self readPNGOrJPEGFrom:bytes expectedSize:512.

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

    "Modified (comment): / 22-02-2017 / 11:03:00 / cg"
!

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

    ^ self readPNGOrJPEGFrom:bytes expectedSize:1024.

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

    "Modified (comment): / 22-02-2017 / 11:03:05 / cg"
!

read_ic11_from:bytes
    "read an ic11 (PNG or JPEG, 32x32) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:32.

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

    "Created: / 22-02-2017 / 11:04:18 / cg"
!

read_ic12_from:bytes
    "read an ic12 (PNG or JPEG, 64) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:64.

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

    "Created: / 22-02-2017 / 12:10:10 / cg"
!

read_ic13_from:bytes
    "read an ic12 (PNG or JPEG, 256x256) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:256.

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

    "Created: / 22-02-2017 / 12:11:06 / cg"
!

read_ic14_from:bytes
    "read an ic12 (PNG or JPEG, 512x512) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:512.

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

    "Created: / 22-02-2017 / 12:13:59 / cg"
!

read_ich4_from:bytes
    "read an ich4 format icon;
     1152 bytes; 48x48x4bit"

    ^ self common_read_paletteImage_from:bytes size:1152 width:48 height:48 depth:4

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

read_ich8_from:bytes
    "read an ich8 format icon;
     2304 bytes; 48x48x8bit"

    ^ self common_read_paletteImage_from:bytes size:2304 width:48 height:48 depth:8

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

read_ich__from:bytes
    "read an ich# format icon.
     ich# is 288+288 bytes, 48x48x1 monochrome + mask"

    |pixelData maskData img|

    pixelData := (ByteArray new:288) replaceBytesFrom:1 to:288 with:bytes startingAt:1; yourself.
    maskData := (ByteArray new:288) replaceBytesFrom:1 to:288 with:bytes startingAt:288+1; yourself.
    img := Depth1Image width:48 height:48 fromArray:pixelData.
    img mask:(Depth1Image width:48 height:48 fromArray:maskData).
    ^ img
!

read_icl4_from:bytes
    "read an icl4 format icon;
     512 bytes; 32x32x4bit"

    ^ self common_read_paletteImage_from:bytes size:512 width:32 height:32 depth:4

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

read_icl8_from:bytes
    "read an icl8 format icon;
     1024 bytes; 32x32x8bit"

    ^ self common_read_paletteImage_from:bytes size:1024 width:32 height:32 depth:8

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

read_icm4_from:bytes
    "read (actually: skip) an icm4 record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:40:13 / cg"
!

read_icm8_from:bytes
    "read (actually: skip) an icm8 record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:40:23 / cg"
!

read_icm__from:bytes
    "read (actually: skip) an icm# record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:39:43 / cg"
!

read_icnV_from:bytes
    "read (actually: skip) an icnV record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:43:21 / cg"
!

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

    "Created: / 22-02-2017 / 12:18:02 / cg"
!

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

    ^ self readPNGOrJPEGFrom:bytes expectedSize:32.

    "
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/txt.icns'
     self fromFile:'/Applications/TextEdit.app/Contents/Resources/html.icns'
     self fromFile:'test.icns'
     
     '/Applications' asFilename recursiveDirectoryContentsAsFilenamesDo:[:each |
         (each hasSuffix:'icns') ifTrue:[
             Transcript showCR:'reading ',each pathName.
             self fromFile:each.
         ] 
     ] 
    "

    "Created: / 22-02-2017 / 12:18:07 / cg"
!

read_icp6_from:bytes
    "read an ipc6 (PNG or JPEG, 64x64) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:64.

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

    "Created: / 22-02-2017 / 12:17:52 / cg"
!

read_ics4_from:bytes
    "read an ics4 format icon.
     128 bytes, 16x16x4bit"

    ^ self common_read_paletteImage_from:bytes size:128 width:16 height:16 depth:4

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

read_ics8_from:bytes
    "read an ics8 format icon.
     256 bytes, 16x16x8bit"

    ^ self common_read_paletteImage_from:bytes size:256 width:16 height:16 depth:8

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

read_ics__from:bytes
    "read an ics# format icon.
     ics# is 64 bytes, 16x16x1 monochrome + mask"

    |pixelData maskData img|

    pixelData := (ByteArray new:32) replaceBytesFrom:1 to:32 with:bytes startingAt:1; yourself.
    maskData := (ByteArray new:32) replaceBytesFrom:1 to:32 with:bytes startingAt:32+1; yourself.
    img := Depth1Image width:16 height:16 fromArray:pixelData.
    img mask:(Depth1Image width:16 height:16 fromArray:maskData).
    ^ img

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

read_icsb_from:bytes
    "read (actually: skip) an icsb record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:21:24 / cg"
!

read_icsd_from:bytes
    "read (actually: skip) an icsd record."

    self breakPoint:#cg.
    ^ nil

    "Created: / 24-02-2017 / 01:36:21 / cg"
!

read_ih32_from:bytes
    "read an ih32 packbits format 48x48x24 icon "

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        self halt.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:48 height:48 depth:24.

    "Modified (comment): / 22-02-2017 / 10:58:51 / cg"
!

read_il32_from:bytes
    "read an il32 packbits format 32x32x24 icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        self halt.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:32 height:32 depth:24.

    "Modified (comment): / 22-02-2017 / 10:59:19 / cg"
!

read_ipc4_from:bytes
    <resource: #obsolete>
    "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
    <resource: #obsolete>
    "read an ipc5 (PNG or JPEG, 32x32) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:32.

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

    "Modified (comment): / 22-02-2017 / 11:02:44 / cg"
!

read_ipc6_from:bytes
    <resource: #obsolete>
    "read an ipc6 (PNG or JPEG, 64x64) format icon"

    ^ self readPNGOrJPEGFrom:bytes expectedSize:64.

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

    "Created: / 22-02-2017 / 12:16:33 / cg"
!

read_is32_from:bytes
    "read an is32 packbits format 16x16x24 icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        self halt.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:16 height:16 depth:24.

    "Modified: / 22-02-2017 / 10:32:25 / cg"
!

read_it32_from:bytes
    "read an it32 packbits format 128x128x24 icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        "/ self halt.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:128 height:128 depth:24.

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

    "Modified: / 22-02-2017 / 12:19:56 / cg"
!

read_l8mk_from:bytes
    "read an l8mk packbits format mask icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        "/ self halt.
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:32 height:32 depth:8.

    "Modified: / 22-02-2017 / 12:08:08 / cg"
!

read_name_from:bytes
    "read (actually: skip) a name entry."

    ^ nil

    "Created: / 28-02-2017 / 12:47:27 / cg"
!

read_s8mk_from:bytes
    "read an s8mk packbits format mask icon"

    |offset|

    offset := 0.
    (bytes from:1 to:4) = #[0 0 0 0] ifTrue:[
        offset := 4.
    ].    
    ^ self readPackBitsImageFrom:bytes asByteArray offset:offset width:16 height:16 depth:8.

    "Modified: / 22-02-2017 / 10:34:46 / cg"
!

read_t8mk_from:bytes
    "read an t8mk 128x128x8 mask icon"

    |img|

    self assert:(bytes size == (128*128)).
    img := Depth8Image width:128 height:128 fromArray:bytes.
    img photometric:#whiteIs0.
    ^ img

    "Modified (comment): / 22-02-2017 / 12:00:50 / cg"
! !

!MacOSXIconReader class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


MacOSXIconReader initialize!