TIFFReader.st
author Claus Gittinger <cg@exept.de>
Fri, 25 Aug 2017 18:07:24 +0200
changeset 3979 5d915912216f
parent 3977 c78bab5f36f2
child 3980 209cd9407fe9
permissions -rw-r--r--
#FEATURE by cg class: TIFFReader class definition added: #positionToTile: #readTiledJPEGTiffImageData changed: #decodeTiffTag:numberType:length: #readThunderScanTiffImageData #readTiledTiffImageData class: TIFFReader class comment/format in: #documentation

"
 COPYRIGHT (c) 1991 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:#TIFFReader
	instanceVariableNames:'planarConfiguration subFileType stripOffsets rowsPerStrip
		fillOrder compression group3options predictor stripByteCounts
		currentOffset stripOffsetsPos stripByteCountsPos bitsPerSamplePos
		colorMapPos orientation isBigTiff'
	classVariableNames:'Verbose'
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

Dictionary subclass:#TIFFMetaData
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:TIFFReader
!

!TIFFReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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
"
    This class knows how to read TIFF files and how to write uncompressed TIFF files.

    Implemented & Missing Features:

      - Only single image files are supported.

      - Not all formats are implemented, and of those that are, not all are tested.
        It should read with most rgb, palette, mono and greyscale images, 
        although the alpha channel is currently not supported and ignored.
        It supports reading of uncompressed, LZW, packbits and CCITT-G3 compressed images
        JPEG and many other formats are currently not implemented.

      - Only writing of uncompressed images is currently implemented.
        It should write (at least) mono, 8-bit palette and 24 bit rgb formats.

      - bigTiff is supported
      - some dng tags are supported

    More formats will come... (will they ever be needed?)

    TODO (?): 
        since I don't want to spend all of my life adding more formats here and
        reinventing the wheel, this code should be changed to use the tiff library.
        That would give us most formats and also writing capabilities for free.

        Late note: 
            I hate C and interfacing to C libraries: it almost always leads to trouble
            w.r.t. memory leaks, non-reentrancy, non-interruptability etc.
            (we recently fixed a malloc-non-reentrant bug for some architecture...)
            So its probably better to do it all in a real programming language ;-)

    [author:]
        Claus Gittinger

    [See also:]
        Image Form Icon
        BlitImageReader FaceReader GIFReader JPEGReader PBMReader PCXReader 
        ST80FormReader SunRasterReader TargaReader WindowsIconReader 
        XBMReader XPMReader XWDReader 
"
! !

!TIFFReader class methodsFor:'initialization'!

initialize
    "install myself in the Image classes fileFormat table
     for the `.tiff' and `.tif' extensions."

    MIMETypes defineImageType:'image/tiff' suffix:'tif'  reader:self.
    MIMETypes defineImageType:nil          suffix:'tiff' reader:self.

    "
     self initialize
    "

    "Modified: 1.2.1997 / 15:00:01 / cg"
! !

!TIFFReader class methodsFor:'testing'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     Any image is supported."

    ^ true
!

isValidImageFile:aFileName
    "return true, if aFileName contains a GIF image"

    |inStream char1 char2 version|

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

    char1 := inStream next.
    char2 := inStream next.

    ((char1 ~~ char2) or:[(char1 ~~ $I) and:[char1 ~~ $M]]) ifTrue:[
        inStream close.
        ^ false
    ].

    inStream binary.
    version := inStream nextInt16MSB:(char1 == $M).
    inStream close.

    "/ 43 is bigTiff
    ^ (version == 42) or:[ (version == 43) ]

    "Modified: / 25-08-2017 / 08:39:20 / cg"
! !

!TIFFReader methodsFor:'private-data reading'!

readCCITT3RLETiffImageData
    ^ self fileFormatError:'ccitt G3 mod Huffman (rle) compression not implemented'

    "Modified: / 3.2.1998 / 18:03:14 / cg"
!

readCCITT3RLEWTiffImageData
    ^ self fileFormatError:'ccitt G3 mod Huffman (rlew) compression not implemented'.

    "Modified: / 3.2.1998 / 18:03:30 / cg"
!

readCCITTGroup3TiffImageData
    "not really tested - all I got is a single fax from NeXT step"

    |bytesPerRow bitsPerRow compressedStrip nPlanes 
     stripNr       "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }"
     bytesPerStrip "{ Class: SmallInteger }" |

    nPlanes := samplesPerPixel.
    (nPlanes ~~ 1) ifTrue:[
        (nPlanes == 2) ifTrue:[
            (planarConfiguration ~~ 2) ifTrue:[
                ^ self fileFormatError:'only separate planes are supported'.
            ].
            'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
            nPlanes := 1
        ] ifFalse:[
            ^ self fileFormatError:'only monochrome/greyscale ccitt3supported'.
        ].   
    ].

"/    (rowsPerStrip ~~ 1) ifTrue:[
"/        ^ self fileFormatError:'currently require rowsPerStrip to be 1'.
"/    ].

    "/ 'TIFFReader: decompressing CCITT-3 ...' infoPrintNL.

    bitsPerRow := width * (bitsPerSample at:1).
    bytesPerRow := bitsPerRow // 8.
    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
        bytesPerRow := bytesPerRow + 1
    ].

    data := ByteArray new:(bytesPerRow * height).

    "/ if the number of rows per strip is unknown (-1),
    "/ make it one big strip and decompress that
    rowsPerStrip = 16rFFFFFFFF ifTrue:[
        compressedStrip := ByteArray uninitializedNew:(stripByteCounts sum).
        self positionToStrip:1.
        inStream nextBytes:(compressedStrip size) into:compressedStrip.
        self class 
            decompressCCITT3From:compressedStrip
            into:data
            startingAt:1
            count:compressedStrip size.
        ^ self 
    ].
    
    compressedStrip := ByteArray uninitializedNew:bytesPerRow.

    offset := 1.
    stripNr := 0.

    row := 1.
    bytesPerStrip := bytesPerRow * rowsPerStrip.
    [row <= height] whileTrue:[
        stripNr := stripNr + 1.
        self positionToStrip:stripNr.
        inStream nextBytes:(stripByteCounts at:stripNr) into:compressedStrip.
        self class 
            decompressCCITT3From:compressedStrip
            into:data
            startingAt:offset
            count:width.
        offset := offset + bytesPerStrip.
        row := row + rowsPerStrip
    ]

    "Modified: / 25-08-2017 / 11:09:02 / cg"
!

readCCITTGroup4TiffImageData
    ^ self fileFormatError:'ccitt group4 fax compression not implemented'.

    "Modified: / 3.2.1998 / 18:04:34 / cg"
!

readCCITTRLEWTiffImageData
    ^ self fileFormatError:'ccitt mod Huffman (rlew) compression not implemented'
!

readDCSTiffImageData
    ^ self fileFormatError:'dcs compression not implemented'.

    "Modified: / 3.2.1998 / 18:04:44 / cg"
!

readDeflateTiffImageData
    ^ self fileFormatError:'deflate compression not implemented'.

    "Modified: / 3.2.1998 / 18:04:54 / cg"
!

readJBIGTiffImageData
    ^ self fileFormatError:'jbig compression not implemented'.

    "Modified: / 3.2.1998 / 18:05:04 / cg"
!

readJPEGTiffImageData
    ^ self fileFormatError:'jpeg compression not implemented'.

    "Modified: / 3.2.1998 / 18:05:12 / cg"
!

readLZWTiffImageData
    "read LZW compressed tiff data; 
     this method only handles 8+8+8 and 8+8+8+8 rgb 
     and 2bit or 2+2bit greyscale images.
     For 2+2bit greyscale images, the alpha plane is ignored.
     (maybe other formats work also - but simply not tested)"

    |bytesPerRow compressedStrip nPlanes overAllBytes
     bytesPerStrip "{ Class: SmallInteger }"
     nBytes        "{ Class: SmallInteger }"
     prevSize      "{ Class: SmallInteger }"
     stripNr       "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }" |

    nPlanes := samplesPerPixel.

    (nPlanes >= 3) ifTrue:[
        (bitsPerSample conform:[:each | each == 8]) ifFalse:[
            ^ self fileFormatError:'only 8/8/8(/8) bits/sample are supported'.
        ].
        bytesPerRow := width * samplesPerPixel.
    ] ifFalse:[
        (nPlanes == 2) ifTrue:[
            (planarConfiguration ~~ 2) ifTrue:[
                ^ self fileFormatError:'only separate planes are supported'.
            ].
            'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
            nPlanes := 1
        ].
        (nPlanes == 1) ifFalse:[
            ^ self fileFormatError:'unsupported nPlanes: ' , nPlanes printString, '; only 3-sample rgb / monochrome supported'.
        ].
        bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.
    ].

    "/ 'TIFFReader: decompressing LZW ...' infoPrintNL.

    overAllBytes := bytesPerRow * height.
    bytesPerRow == width ifTrue:[
        data := ByteArray uninitializedNew:overAllBytes.
    ] ifFalse:[
        data := ByteArray new:overAllBytes.
    ].

    offset := 1.
    stripNr := 0.

    row := 1.
    bytesPerStrip := bytesPerRow * rowsPerStrip.
    prevSize := 0.
    [row <= height] whileTrue:[
        stripNr := stripNr + 1.
        self positionToStrip:stripNr.
        nBytes := stripByteCounts at:stripNr.
        (nBytes > prevSize) ifTrue:[
            compressedStrip := ByteArray uninitializedNew:nBytes.
            prevSize := nBytes
        ].
        inStream nextBytes:nBytes into:compressedStrip.
        self class 
            decompressLZWFrom:compressedStrip count:nBytes
            into:data startingAt:offset.
        offset := offset + bytesPerStrip.
        row := row + rowsPerStrip
    ].

    (predictor == 2) ifTrue:[
        self class decodeDelta:nPlanes in:data width:width height:height
    ]

    "Modified: / 25-08-2017 / 10:09:03 / cg"
!

readNeXTJPEGTiffImageData
    ^ self fileFormatError:'next jpeg compression not implemented'.

    "Modified: / 3.2.1998 / 18:10:45 / cg"
!

readNeXTRLE2TiffImageData
    ^ self fileFormatError:'next 2bit rle compression not implemented'.

    "Modified: / 3.2.1998 / 18:10:54 / cg"
!

readNewJPEGTiffImageData
    ^ self fileFormatError:'new jpeg compression not implemented'.
!

readPackbitsTiffImageData
    "this has only been tested with monochrome images"

    |bytesPerRow bitsPerRow nPlanes 
     stripNr       "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }" 
     nBytes        "{ Class: SmallInteger }"
     nDecompressedBytes  "{ Class: SmallInteger }"
     bitsPerPixel overAllBytes buffer|

    nPlanes := samplesPerPixel.

    "only support 1-sample/pixel,
     with alpha - if separate planes,
     or rgb - if non separate planes and no alpha"

    (nPlanes == 2) ifTrue:[
        (planarConfiguration ~~ 2) ifTrue:[
            ^ self fileFormatError:'with alpha, only separate planes supported'.
        ].
        'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
        nPlanes := 1.
        bitsPerPixel := bitsPerSample at:1.
        bitsPerSample := Array with:bitsPerPixel.
        samplesPerPixel := 1.
    ] ifFalse:[
        (nPlanes == 3) ifTrue:[
            (planarConfiguration ~~ 1) ifTrue:[
                ^ self fileFormatError:'only non separate planes supported'.
            ].
            bitsPerSample ~= #(8 8 8) ifTrue:[
                ^ self fileFormatError:'only 8/8/8 rgb images supported'.
            ].
            bitsPerPixel := 24
        ] ifFalse:[
            (nPlanes ~~ 1) ifTrue:[
                ^ self fileFormatError:'format not supported'.
            ].
            bitsPerPixel := bitsPerSample at:1.
        ]
    ].

    bitsPerRow := width * bitsPerPixel.
    bytesPerRow := bitsPerRow // 8.
    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
        bytesPerRow := bytesPerRow + 1
    ].

    overAllBytes := bytesPerRow * height.
    bytesPerRow == width ifTrue:[
        data := ByteArray uninitializedNew:overAllBytes.
    ] ifFalse:[
        data := ByteArray new:overAllBytes.
    ].

    offset := 1.
    stripNr := 0.

    buffer := nil.
    row := 1.
    [row <= height] whileTrue:[
        stripNr := stripNr + 1.
        nBytes := stripByteCounts at:stripNr.
        self positionToStrip:stripNr.

        nBytes > buffer size ifTrue:[
            "/ realloc
            buffer := ByteArray uninitializedNew:nBytes.
        ].
        inStream nextBytes:nBytes into:buffer.
        nDecompressedBytes := self class decompressPackBitsFrom:buffer at:1 to:data at:offset count:nBytes.
        "/ nDecompressedBytes := self class decompressPackBits:nBytes from:buffer to:data startingAt:offset.

        offset := offset + nDecompressedBytes.
        row := row + rowsPerStrip
    ]

    "Modified: / 25-08-2017 / 02:02:20 / cg"
!

readPixarFilmTiffImageData
    ^ self fileFormatError:'pixar film compression not implemented'.

    "Modified: / 3.2.1998 / 18:11:45 / cg"
!

readPixarLogTiffImageData
    ^ self fileFormatError:'pixar log compression not implemented'.

    "Modified: / 3.2.1998 / 18:11:53 / cg"
!

readSGI24TiffImageData
    ^ self fileFormatError:'SGI 24-bit Log Luminance encoding not implemented' .

    "Created: / 25-08-2017 / 11:17:25 / cg"
!

readSGI32TiffImageData
    ^ self fileFormatError:'SGI 32-bit Log Luminance encoding not implemented' .

    "Created: / 25-08-2017 / 11:17:21 / cg"
!

readThunderScanTiffImageData
    |bytesPerRow compressedStrip nPlanes overAllBytes
     bytesPerStrip "{ Class: SmallInteger }"
     nBytes        "{ Class: SmallInteger }"
     prevSize      "{ Class: SmallInteger }"
     stripNr       "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }"
     pixelIndex
     i even gen highNibble lastPixel d1 d2 d3|

    nPlanes := samplesPerPixel.

    (nPlanes == 2) ifTrue:[
        (planarConfiguration ~~ 2) ifTrue:[
            ^ self fileFormatError:'only separate planes are supported'.
        ].
        'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
        nPlanes := 1
    ].
    (nPlanes == 1) ifFalse:[
        ^ self fileFormatError:'unsupported nPlanes: ' , nPlanes printString.
    ].
    (bitsPerSample at:1) == 4 ifFalse:[
        ^ self fileFormatError:('unsupported bitsPerSample: %1 (only 4 supported)' bindWith:(bitsPerSample at:1)).
    ].    
    bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.

    "/ 'TIFFReader: decompressing ThunderScan ...' infoPrintNL.

    overAllBytes := bytesPerRow * height.
    bytesPerRow == width ifTrue:[
        data := ByteArray uninitializedNew:overAllBytes.
    ] ifFalse:[
        data := ByteArray new:overAllBytes.
    ].

    offset := 1.
    stripNr := 0.
    
    gen := [:pixel | 
                even ifTrue:[
                    highNibble := pixel. 
                    even := false.
                ] ifFalse:[    
                    data at:pixelIndex put:((highNibble bitShift:4) bitOr:pixel).
                    pixelIndex := pixelIndex + 1.
                    even := true.
                ].
            ].    
    even := true.
    lastPixel := 0.
    
    row := 1.
    bytesPerStrip := bytesPerRow * rowsPerStrip.
    prevSize := 0.
    [row <= height] whileTrue:[
        stripNr := stripNr + 1.
        self positionToStrip:stripNr.
        nBytes := stripByteCounts at:stripNr.
        (nBytes > prevSize) ifTrue:[
            compressedStrip := ByteArray uninitializedNew:nBytes.
            prevSize := nBytes
        ].
        (inStream nextBytes:nBytes into:compressedStrip) == nBytes ifFalse:[ self error:'short read' ].

        "/ RLE decode... (see http://fileformats.archiveteam.org/wiki/ThunderScan_compression)
        i := 1.
        pixelIndex := offset.
        
        [i <= nBytes] whileTrue:[
            |code|

            code := compressedStrip at:i.
            i := i + 1.
            code >= 2r11000000 ifTrue:[
                "/ a single pixel
                lastPixel := code bitAnd:2r00111111.
                self assert:(lastPixel <= 2r1111).
                
                gen value:lastPixel.
            ] ifFalse:[
                code >= 2r10000000 ifTrue:[
                    "/ three bit deltas (2 pixels)

                    d1 := (code rightShift:3) bitAnd:2r111.
                    d2 := code bitAnd:2r111.
                    d1 ~~ 4 ifTrue:[
                        lastPixel := lastPixel + (#(0 1 2 3 0 -3 -2 -1) at:d1+1).
                        gen value:lastPixel.
                    ].
                    d2 ~~ 4 ifTrue:[
                        lastPixel := lastPixel + (#(0 1 2 3 0 -3 -2 -1) at:d2+1).
                        gen value:lastPixel.
                    ].
                ] ifFalse:[
                    code >= 2r01000000 ifTrue:[
                        "/ two bit deltas (3 pixels)    
                        d1 := (code rightShift:4) bitAnd:2r11.
                        d2 := (code rightShift:2) bitAnd:2r11.
                        d3 := code bitAnd:2r11.
                        d1 ~~ 2 ifTrue:[
                            lastPixel := lastPixel + (#(0 1 0 -1) at:d1+1).
                            gen value:lastPixel.
                        ].
                        d2 ~~ 2 ifTrue:[
                            lastPixel := lastPixel + (#(0 1 0 -1) at:d2+1).
                            gen value:lastPixel.
                        ].
                        d3 ~~ 2 ifTrue:[
                            lastPixel := lastPixel + (#(0 1 0 -1) at:d3+1).
                            gen value:lastPixel.
                        ].
                    ] ifFalse:[
                        code timesRepeat:[ gen value:lastPixel ].
                    ].
                ].
            ].
        ].
        "/ self assert:(pixelIndex == (offset + bytesPerStrip)).
        
        offset := offset + bytesPerStrip.
        row := row + rowsPerStrip
    ].

    (predictor ~~ 1) ifTrue:[
        ^ self fileFormatError:('unsupported predictor: %1' bindWith:predictor).
    ].

    "Modified: / 25-08-2017 / 17:43:00 / cg"
!

readTiffImageData
    (compression == 1) ifTrue:[
        ^ self readUncompressedTiffImageData.
    ].
    (compression == 2) ifTrue:[
        ^ self readCCITT3RLETiffImageData.
    ].
    (compression == 3) ifTrue:[
        ^ self readCCITTGroup3TiffImageData.
    ]. 
    (compression == 4) ifTrue:[
        ^ self readCCITTGroup4TiffImageData.
    ]. 
    (compression == 5) ifTrue:[
        ^ self readLZWTiffImageData.
    ].
    (compression == 6) ifTrue:[
        ^ self readJPEGTiffImageData.
    ].
    (compression == 7) ifTrue:[
        ^ self readNewJPEGTiffImageData.
    ].

    (compression == 32766) ifTrue:[
        ^ self readNeXTRLE2TiffImageData.
    ].
    (compression == 32771) ifTrue:[
        ^ self readCCITTRLEWTiffImageData.
    ].
    (compression == 32773) ifTrue:[
        ^ self readPackbitsTiffImageData.
    ].
    (compression == 32809) ifTrue:[
        ^ self readThunderScanTiffImageData.
    ].
    (compression == 32908) ifTrue:[
        ^ self readPixarFilmTiffImageData.
    ].
    (compression == 32909) ifTrue:[
        ^ self readPixarLogTiffImageData.
    ].
    (compression == 32946) ifTrue:[
        ^ self readDeflateTiffImageData.
    ].
    (compression == 32947) ifTrue:[
        ^ self readDCSTiffImageData.
    ].
    (compression == 32865) ifTrue:[
        ^ self readNeXTJPEGTiffImageData.
    ].
    (compression == 34661) ifTrue:[
        ^ self readJBIGTiffImageData.
    ].
    (compression == 34676) ifTrue:[
        ^ self readSGI32TiffImageData.
    ].
    (compression == 34677) ifTrue:[
        ^ self readSGI24TiffImageData.
    ].

    ^ self fileFormatError:('compression type ' , compression printString , ' not known').

    "Created: / 11-04-1997 / 00:19:44 / cg"
    "Modified: / 25-08-2017 / 11:17:25 / cg"
!

readTiledJPEGTiffImageData
    ^ self fileFormatError:'jpeg compression not implemented (in tile mode)'.

    "Created: / 25-08-2017 / 16:27:28 / cg"
!

readTiledLZWTiffImageData
    ^ self fileFormatError:'tiled LZW data not implemented' .

    "Created: / 25-08-2017 / 01:05:13 / cg"
!

readTiledTiffImageData
    (compression == 1) ifTrue:[
        ^ self readTiledUncompressedTiffImageData.
    ].
    (compression == 5) ifTrue:[
        ^ self readTiledLZWTiffImageData.
    ].
    (compression == 6) ifTrue:[
        ^ self readTiledJPEGTiffImageData.
    ].

    ^ self fileFormatError:('compression type ' , compression printString , ' not supported (in tile mode)').

    "Created: / 25-08-2017 / 00:19:14 / cg"
    "Modified: / 25-08-2017 / 16:27:40 / cg"
!

readTiledUncompressedTiffImageData
    |bytesPerRow   "{ Class: SmallInteger }"
     bitsPerRow    "{ Class: SmallInteger }"
     bytesPerTileRow   "{ Class: SmallInteger }"
     bitsPerTileRow    "{ Class: SmallInteger }" 
     nPlanes 
     tileNr        "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }" 
     nBytes        "{ Class: SmallInteger }"
     bitsPerPixel 
     overAllBytes  "{ Class: SmallInteger }"
     where         "{ Class: SmallInteger }"
     x             "{ Class: SmallInteger }"       
     y             "{ Class: SmallInteger }" 
     imageRowOffset  "{ Class: SmallInteger }" 
     imageOffset     "{ Class: SmallInteger }" 
     tileOffset      "{ Class: SmallInteger }"   
     dataOffset      "{ Class: SmallInteger }"   
     tilePos tile     
     tileWidth tileLength tileOffsets tileByteCounts|

    tileWidth := metaData at:#TileWidth.
    tileLength := metaData at:#TileLength.
    tileOffsets := metaData at:#TileOffsets.
    tileByteCounts := metaData at:#TileByteCounts.

    nPlanes := samplesPerPixel.

    "/ not all formats are supported here,

    (nPlanes == 2) ifTrue:[
        (planarConfiguration ~~ 2) ifTrue:[
            ^ self fileFormatError:'with alpha, only separate planes supported'.
        ].
        'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
        nPlanes := 1.
        bitsPerPixel := bitsPerSample at:1.
        bitsPerSample := Array with:bitsPerPixel.
        samplesPerPixel := 1.
    ] ifFalse:[
        (nPlanes == 4) ifTrue:[
            (planarConfiguration ~~ 1) ifTrue:[
                ^ self fileFormatError:'only non separate planes supported'.
            ].
            bitsPerSample ~= #(8 8 8 8) ifTrue:[
                ^ self fileFormatError:'only 8/8/8/8 cmyk images supported'.
            ].
            bitsPerPixel := 32.
        ] ifFalse:[
            (nPlanes == 3) ifTrue:[
                (planarConfiguration ~~ 1) ifTrue:[
                    ^ self fileFormatError:'only non separate planes supported'.
                ].
                bitsPerSample ~= #(8 8 8) ifTrue:[
                    ^ self fileFormatError:'only 8/8/8 rgb images supported (is: ' , bitsPerSample printString , ')'.
                ].
                bitsPerPixel := 24
            ] ifFalse:[
                (nPlanes ~~ 1) ifTrue:[
                    ^ self fileFormatError:('unsupported format: nplanes=' , nPlanes printString).
                ].
                bitsPerPixel := bitsPerSample at:1.
            ]
        ]
    ].

    bitsPerRow := width * bitsPerPixel.
    bytesPerRow := bitsPerRow // 8.
    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
        bytesPerRow := bytesPerRow + 1
    ].
    
    bitsPerTileRow := tileWidth * bitsPerPixel.
    bytesPerTileRow := bitsPerTileRow // 8.
    ((bitsPerTileRow \\ 8) ~~ 0) ifTrue:[
        bytesPerTileRow := bytesPerTileRow + 1
    ].

    overAllBytes := bytesPerRow * height.
    data := ByteArray new:overAllBytes.
    
    tileNr := 1.
    where := -1.
    y := 0.
    imageRowOffset := 1.
    [ y < height ] whileTrue:[
        x := 0.
        imageOffset := imageRowOffset.
        [ x < width ] whileTrue:[
            nBytes := tileByteCounts at:tileNr.
            tilePos := tileOffsets at:tileNr.
            tileNr := tileNr + 1.
            
            where ~~ tilePos ifTrue:[
                inStream position:tilePos.
                where := tilePos.
            ].
            tile := ByteArray new:nBytes.
            inStream nextBytes:nBytes into:tile startingAt:1 blockSize:4096.

            "/ copy the tile.
            tileOffset := 1.
            dataOffset := imageOffset. 
            1 to:tileLength do:[:yT |
                data replaceFrom:dataOffset to:dataOffset+bytesPerTileRow-1 with:tile startingAt:tileOffset.
                dataOffset := dataOffset + bytesPerRow.
                tileOffset := tileOffset + bytesPerTileRow.
            ].
            
            "/ offset := offset + nBytes.
            "/ row := row + rowsPerStrip.
            where := where + nBytes.

            x := x + tileWidth.
            imageOffset := imageOffset + bytesPerTileRow.
        ].
        y := y + tileLength.
        imageRowOffset := imageRowOffset + (bytesPerRow*tileLength).
    ].

    "Created: / 25-08-2017 / 00:22:31 / cg"
!

readUncompressedTiffImageData
    |bytesPerRow   "{ Class: SmallInteger }"
     bitsPerRow    "{ Class: SmallInteger }"
     nPlanes 
     stripNr       "{ Class: SmallInteger }"
     offset        "{ Class: SmallInteger }"
     row           "{ Class: SmallInteger }" 
     nBytes        "{ Class: SmallInteger }"
     bitsPerPixel 
     overAllBytes  "{ Class: SmallInteger }"
     where         "{ Class: SmallInteger }"
     stripPos      |

    nPlanes := samplesPerPixel.

    "/ not all formats are supported here,

    (nPlanes == 2) ifTrue:[
        (planarConfiguration ~~ 2) ifTrue:[
            ^ self fileFormatError:'with alpha, only separate planes supported'.
        ].
        'TIFFReader [info]: ignoring alpha plane' infoPrintCR.
        nPlanes := 1.
        bitsPerPixel := bitsPerSample at:1.
        bitsPerSample := Array with:bitsPerPixel.
        samplesPerPixel := 1.
    ] ifFalse:[
        (nPlanes == 4) ifTrue:[
            (planarConfiguration ~~ 1) ifTrue:[
                ^ self fileFormatError:'only non separate planes supported'.
            ].
            bitsPerSample ~= #(8 8 8 8) ifTrue:[
                ^ self fileFormatError:'only 8/8/8/8 cmyk images supported'.
            ].
            bitsPerPixel := 32.
        ] ifFalse:[
            (nPlanes == 3) ifTrue:[
                (planarConfiguration ~~ 1) ifTrue:[
                    ^ self fileFormatError:'only non separate planes supported'.
                ].
                bitsPerSample ~= #(8 8 8) ifTrue:[
                    ^ self fileFormatError:'only 8/8/8 rgb images supported (is: ' , bitsPerSample printString , ')'.
                ].
                bitsPerPixel := 24
            ] ifFalse:[
                (nPlanes ~~ 1) ifTrue:[
                    ^ self fileFormatError:('unsupported format: nplanes=' , nPlanes printString).
                ].
                bitsPerPixel := bitsPerSample at:1.
            ]
        ]
    ].

    bitsPerRow := width * bitsPerPixel.
    bytesPerRow := bitsPerRow // 8.
    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
        bytesPerRow := bytesPerRow + 1
    ].

    overAllBytes := bytesPerRow * height.
    bytesPerRow == width ifTrue:[
        data := ByteArray uninitializedNew:overAllBytes.
    ] ifFalse:[
        data := ByteArray new:overAllBytes.
    ].

    offset := 0.
    stripNr := 0.
    where := -1.
    row := 1.
    [row <= height] whileTrue:[
        stripNr := stripNr + 1.
        nBytes := stripByteCounts at:stripNr.
        stripPos := stripOffsets at:stripNr.
        where ~~ stripPos ifTrue:[
            inStream position:stripPos.
            where := stripPos.
        ].
        
        offset + nBytes > overAllBytes ifTrue:[
            nBytes := overAllBytes - offset.
        ].

        "/ read it 4k-wise; this leads to a better behavior,
        "/ when reading big images from a slow device (such as a cdrom)
        inStream nextBytes:nBytes into:data startingAt:offset+1 blockSize:4096.

        offset := offset + nBytes.
        row := row + rowsPerStrip.
        where := where + nBytes.
    ].

    "Modified: / 12.8.1998 / 13:57:14 / cg"
! !

!TIFFReader methodsFor:'private-reading'!

decodeTiffTag:tagType numberType:numberType length:length
    |offset value valueArray 
     val scaleFactor rV gV bV
     n  "{ Class: SmallInteger }"
     i2 "{ Class: SmallInteger }"
     i3 "{ Class: SmallInteger }" |

    Verbose == true ifTrue:[ Logger info:'tiffTag: %1' with:tagType ].

    (numberType == 3 "TIFF_SHORT") ifTrue:[
        "16 bit ushort"
        valueArray := self readShorts:length signed:false.
        value := valueArray at:1
    ] ifFalse:[(numberType == 4 "TIFF_LONG") ifTrue:[
        "32 bit uinteger"
        valueArray := self readLongs:length signed:false.
        value := valueArray at:1
    ] ifFalse:[(numberType == 2 "TIFF_ASCII") ifTrue:[
        "ascii characters"
        value := self readChars:length
    ] ifFalse:[(numberType == 5 "TIFF_RATIONAL") ifTrue:[
        "64 (32+32) bit ufraction"
        valueArray := self readFracts:length signed:false.
        value := valueArray at:1
    ] ifFalse:[(numberType == 1 "TIFF_BYTE") ifTrue:[
        "8bit uinteger"
        value := self readBytes:length signed:false
    ] ifFalse:[(numberType == 6 "TIFF_SBYTE") ifTrue:[
        "TIFF6: 8bit signed integer"
        value := self readBytes:length  signed:true
    ] ifFalse:[(numberType == 8 "TIFF_SSHORT") ifTrue:[
        "TIFF6: 16bit signed integer"
        valueArray := self readShorts:length signed:true.
        value := valueArray at:1
    ] ifFalse:[(numberType == 9 "TIFF_SLONG") ifTrue:[
        "TIFF6: 32bit signed integer"
        valueArray := self readLongs:length signed:true.
        value := valueArray at:1
    ] ifFalse:[(numberType == 10 "TIFF_SRATIONAL") ifTrue:[
        "TIFF6: 64 (32+32) bit signed fraction"
        valueArray := self readFracts:length signed:true.
        value := valueArray at:1
    ] ifFalse:[(numberType == 11 "TIFF_FLOAT") ifTrue:[
        "TIFF6: 32 bit IEEE float"
        valueArray := self readFloats:length.
        value := valueArray at:1
    ] ifFalse:[(numberType == 12 "TIFF_DOUBLE") ifTrue:[
        "TIFF6: 64 bit IEEE double"
        valueArray := self readDoubles:length.
        value := valueArray at:1
        
    ] ifFalse:[(numberType == 7 "TIFF_UNDEFINED") ifTrue:[
        "8bit anything"
        value := self readBytes:length signed:false

    "/ the following are preps for the propsed bigTiff format    
    ] ifFalse:[(numberType == 16 "TIFF_LONG8") ifTrue:[
        "BIGTIFF: 8-byte unsigned integer"
        valueArray := self readLong8s:length signed:false.
        value := valueArray at:1.
    ] ifFalse:[(numberType == 17 "TIFF_SLONG8") ifTrue:[
        "BIGTIFF: 8-byte signed integer"
        valueArray := self readLong8s:length signed:true.
        value := valueArray at:1.
    ] ifFalse:[(numberType == 18 "TIFF_IFD8") ifTrue:[
        "BIGTIFF: 8-byte unsigned IFD offset"
        valueArray := self readLong8s:length signed:false.
        value := valueArray at:1.
    ] ifFalse:[
        isBigTiff ifTrue:[
            offset := (inStream nextInt64MSB:(byteOrder ~~ #lsb))
        ] ifFalse:[    
            offset := (inStream nextInt32MSB:(byteOrder ~~ #lsb))
        ]
    ]]]]]]]]]]]]]]].

    (tagType between:200 and:299) ifTrue:[
        (tagType == 254) ifTrue:[
            "/ New SubfileType
            "/      REDUCEDIMAGE    -> 1
            "/      PAGE            -> 2
            "/      MASK            -> 4
            "newSubFileType := value."

            "/ 'newSubfiletype ' print. value printNewline.
            Verbose == true ifTrue:[ 
                Logger info:'      newSubfiletype: %1' with:value
            ].
            ^ self
        ].
        (tagType == 255) ifTrue:[
            "/ Old SubfileType
            "/      IMAGE           -> 1
            "/      REDUCEDIMAGE    -> 2
            "/      PAGE            -> 3
            subFileType := value.

            Verbose == true ifTrue:[ 
                Logger info:'      oldSubfiletype: %1' with:value 
            ].

            ^ self
        ].
        (tagType == 256) ifTrue:[
            "ImageWidth"
            width := value.

            Verbose == true ifTrue:[ 
                Logger info:'      width: %1' with:value 
            ].

            ^ self
        ].
        (tagType == 257) ifTrue:[
            "ImageHeight"
            height := value.

            Verbose == true ifTrue:[ 
                Logger info:'      height: %1' with:value 
            ].

            ^ self
        ].
        (tagType == 258) ifTrue:[
            "bitspersample"  
             bitsPerSample := valueArray.

            Verbose == true ifTrue:[ 
                Logger info:'      bitspersample: %1' with:valueArray 
            ].

            ^ self
        ].
        (tagType == 259) ifTrue:[
            "/ compression
            "/      NONE            -> 1
            "/      CCITTRLE        -> 2
            "/      CCITTFAX3       -> 3
            "/      CCITTFAX4       -> 4
            "/      LZW             -> 5
            "/      OJPEG           -> 6 (old style jpeg)
            "/      JPEG            -> 7 (new style jpeg)
            "/      ADOBE_DEFLATE   -> 8
            "/      JBIG            -> 9 (ITU-T T85)
            "/      JBIG            -> 10 (ITU-T T43)

            "/      NEXT            -> 32766 (NeXT 2-bit encoding)
            "/      CCITTRLEW       -> 32771
            "/      PACKBITS        -> 32773
            "/      THUNDERSCAN     -> 32809 (ThunderScan 4-bit encoding)
            "/      IT8CTPAD        -> 32895  
            "/      IT8LW           -> 32896  
            "/      IT8MP           -> 32897  
            "/      IT8BL           -> 32898  
            "/      PIXARFILM       -> 32908
            "/      PIXARLOG        -> 32909 (Pixar companded 11-bit ZIP encoding)
            "/      DEFLATE         -> 32946 (PKZIP-style Deflate encoding)
            "/      DCS             -> 32947 (kodac)
            "/      JBIG            -> 34661
            "/      SGI32           -> 34676 (SGI 32-bit Log Luminance encoding)
            "/      SGI24           -> 34677 (SGI 24-bit Log Luminance encoding)
            "/      JPEG2000        -> 34712 JPEG2000
            "/      NIKON_NEF       -> 34713 
            "/      JBIG2           -> 34715 
            compression := value.

            Verbose == true ifTrue:[ 
                Logger info:'      compression: %1' with:value 
            ].

            ^ self
        ].
        (tagType == 262) ifTrue:[
            "photometric"

            (value between:0 and:10) ifTrue:[
                photometric := #(
                    whiteIs0            "/  0 - grayscale or monochrome; faxes
                    blackIs0            "/  1 - grayscale or monochrome; faxes
                    rgb                 "/  2
                    palette             "/  3
                    transparencyMask    "/  4
                    cmyk                "/  5 - color separations
                    YCbCr               "/  6 - CCIR 601
                    nil                 "/  7
                    CIElab              "/  8 - 1976 CIE L*a*b*
                    ICClab              "/  9 - ICC L*a*b*
                    ITUlab              "/ 10 - see ITO-T- Rec T42 (RFC 2301)
                ) at:(value + 1)    
            ] ifFalse:[
                (value == 32803) ifTrue:[
                    photometric := #ColorFilterArray    "/ camera rw format
                ].
                (value == 32844) ifTrue:[
                    photometric := #PixarLogL   
                ].
                (value == 32845) ifTrue:[
                    photometric := #PixarLogLuv    
                ].
                (value == 34892) ifTrue:[
                    photometric := #LinearRaw           "/ camera rw format
                ].
            ].
            Verbose == true ifTrue:[ 
                Logger info:'      photometric: %1 (%2)' with:photometric with:value
            ].
            ^ self
        ].
        (tagType == 263) ifTrue:[
            "/ Thresholding
            "/      BILEVEL         -> 1
            "/      HALFTONE        -> 2
            "/      ERRORDIFFUSE    -> 3

            "thresholding := value."

            "/ 'thresholding ' print. value printNewline.

            ^ self
        ].
        (tagType == 264) ifTrue:[
            "CellWidth"
            "/ 'cellWidth ' print. value printNewline.
            metaData at:#CellWidth put:value.

            ^ self
        ].
        (tagType == 265) ifTrue:[
            "CellLength"
            "/ 'cellLength ' print. value printNewline.
            metaData at:#CellLength put:value.
            ^ self
        ].
        (tagType == 266) ifTrue:[
            "fillOrder"
            (value == 1) ifTrue:[
              fillOrder := #msb
            ] ifFalse:[
              (value == 2) ifTrue:[
                fillOrder := #lsb
              ] ifFalse:[
                fillOrder := nil
              ]
            ].
            "/ 'fillorder ' print. fillOrder printNewline.
            ^ self
        ].
        (tagType == 269) ifTrue:[
            "documentName - info only"
            "/ 'documentName ' print. value printNewline.
            metaData at:#DocumentName put:value.
            ^ self
        ].
        (tagType == 270) ifTrue:[
            "imageDescription - info only"
            "/ 'imageDescription ' print. value printNewline.
            metaData at:#ImageDescription put:value.
            ^ self
        ].
        (tagType == 271) ifTrue:[
            "make - info only"
            metaData at:#Make put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      make: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 272) ifTrue:[
            "model - info only"
            metaData at:#Model put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      model: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 273) ifTrue:[
            "stripOffsets"
            stripOffsets := valueArray.
            Verbose == true ifTrue:[ 
                Logger info:'      stripOffsets: %1' with:valueArray 
            ].
            ^ self
        ].
        (tagType == 274) ifTrue:[
            "Orientation"

            orientation :=
                            #( nil          "/ 1 normal (topLeft)
                               unsupported  "/ 2 horizontal flip
                               unsupported  "/ 3 horizontal & vertical flip
                               vFlip        "/ 4 vertical flip
                               unsupported  "/ 5 rot 90' counter clock-wise
                               unsupported  "/ 6 rot 90' clock-wise
                               unsupported  "/ 7 rot 90' & flip
                               unsupported  "/ 8 rot 90' ccw & flip
                             ) at:value ifAbsent:#unsupported.
            metaData at:#Orientation put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      orientation: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 277) ifTrue:[
            samplesPerPixel := value.
            Verbose == true ifTrue:[ 
                Logger info:'      samplesperpixel: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 278) ifTrue:[
            rowsPerStrip := value.
            Verbose == true ifTrue:[ 
                Logger info:'      rowsPerStrip: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 279) ifTrue:[
            "stripbytecount"
            stripByteCounts := valueArray.
            "/        'stripByteCounts Array(' print. 
            "/        stripByteCounts size print.
            "/        ')' printNewline.
            Verbose == true ifTrue:[ 
                Logger info:'      stripByteCounts: %1' with:valueArray 
            ].
            ^ self
        ].
        (tagType == 280) ifTrue:[
            "/ 'minSampleValue ' print. value printNewline.
            metaData at:#MinSampleValue put:value.
            ^ self
        ].
        (tagType == 281) ifTrue:[
            "/ 'maxSampleValue ' print. value printNewline.
            metaData at:#MaxSampleValue put:value.
            ^ self
        ].
        (tagType == 282) ifTrue:[
            "/ xResolution
            metaData at:#ResolutionX put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      xResolution: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 283) ifTrue:[
            "/ yResolution
            metaData at:#ResolutionY put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      yResolution: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 284) ifTrue:[
            (value == 1) ifTrue:[
                planarConfiguration := 1
            ] ifFalse:[
                (value == 2) ifTrue:[
                    planarConfiguration := 2
                ] ifFalse:[
                    planarConfiguration := nil
                ]
            ].
            Verbose == true ifTrue:[ 
                Logger info:'      planarConfiguration: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 285) ifTrue:[
            "/ 'pageName ' print. value printNewline.
            metaData at:#PageName put:value.
            ^ self
        ].
        (tagType == 286) ifTrue:[
            "/ 'xPosition ' print. value printNewline.
            metaData at:#PositionX put:value.
            ^ self
        ].
        (tagType == 287) ifTrue:[
            "/ 'yPosition ' print. value printNewline.
            metaData at:#PositionY put:value.
            ^ self
        ].
        (tagType == 288) ifTrue:[
            "/ 'freeOffsets ' print. value printNewline.
            ^ self
        ].
        (tagType == 289) ifTrue:[
            "/ 'freeByteCounts ' print. value printNewline.
            ^ self
        ].
        (tagType == 290) ifTrue:[
            "/ 'grayResponceUnit' print. value printNewline.
            metaData at:#GrayResponceUnit put:value.
            ^ self
        ].
        (tagType == 291) ifTrue:[
            "/ 'grayResponceCurve' print. value printNewline.
            metaData at:#GrayResponceCurve put:value.
            ^ self
        ].
        (tagType == 292) ifTrue:[
            "/ group3options (now called T4Options)
            "/      2DENCODING      -> 1
            "/      UNCOMPRESSED    -> 2
            "/      FILLBITS        -> 4

            group3options := value.
            "/ 'group3options ' print. group3options printNewline.
            ^ self
        ].
        (tagType == 293) ifTrue:[
            "/ group4options (now called T6Options)
            "/      UNCOMPRESSED    -> 2

            "group4options := value."
            "/ 'group4options ' print. value printNewline.
            ^ self
        ].
        (tagType == 296) ifTrue:[
            "resolutionunit"

            "/        (value == 1) ifTrue:[
            "/            'res-unit pixel' printNewline
            "/        ] ifFalse:[
            "/            (value == 2) ifTrue:[
            "/                'res-unit inch' printNewline
            "/            ] ifFalse:[
            "/                (value == 3) ifTrue:[
            "/                    'res-unit mm' printNewline
            "/                ] ifFalse:[
            "/                    'res-unit invalid' printNewline
            "/                ]
            "/            ]
            "/        ].
            metaData at:#ResolutionUnit put:value.
            Verbose == true ifTrue:[ 
                Logger info:'      resolutionUnit: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 297) ifTrue:[
            "/ 'pageNumber ' print. value printNewline.
            metaData at:#PageNumber put:value.
            ^ self
        ].
    ].
    
    (tagType between:300 and:399) ifTrue:[
        (tagType == 300) ifTrue:[
            "/ 'colorResponceUnit' print. value printNewline.
            metaData at:#ColorResponceUnit put:value.
            ^ self
        ].
        (tagType == 301) ifTrue:[
            "/ 'colorResponceCurve' print. value printNewline.
            metaData at:#ColorResponceCurve put:value.
            ^ self
        ].
        (tagType == 305) ifTrue:[
            "software - info only"
            metaData at:#Software put:value asString.
            Verbose == true ifTrue:[ 
                Logger info:'      software: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 306) ifTrue:[
            "dateTime - info only"
            metaData at:#DateTime put:value asString.
            Verbose == true ifTrue:[ 
                Logger info:'      dateTime: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 315) ifTrue:[
            "artist - info only"
            metaData at:#Artist put:value asString.
            Verbose == true ifTrue:[ 
                Logger info:'      artist: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 316) ifTrue:[
            "host computer - info only"
            metaData at:#HostComputer put:value asString.
            Verbose == true ifTrue:[ 
                Logger info:'      host: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 317) ifTrue:[
            "/ 'predictor ' print. predictor printNewline.
            "/ 1 -> no predictor
            "/ 2 -> horiz. difference (see tiff spec 6.0)
            "/ 3 -> flt pnt (see adobe tech notes)
            "/ 34892 -> horiz difference x2
            "/ 34893 -> horiz difference x4
            "/ 34894 -> flt pnt x2
            "/ 34895 -> flt pnt x4
            predictor := value.
            ^ self
        ].
        (tagType == 318) ifTrue:[
            "/ 'whitePoint ' print. value printNewline.
            metaData at:#WhitePoint put:value.
            ^ self
        ].
        (tagType == 319) ifTrue:[
            "/ 'primaryChromatics ' print. value printNewline.
            metaData at:#PrimaryChromatics put:value.
            ^ self
        ].
        (tagType == 320) ifTrue:[
            "/ 'colorMap (size=' print. valueArray size print. ')' printNewline.

            "
             the tiff colormap contains 16bit values;
             our colormap expects 8bit values
            "
            n := valueArray size // 3.

            rV := ByteArray uninitializedNew:n.
            gV := ByteArray uninitializedNew:n.
            bV := ByteArray uninitializedNew:n.
            scaleFactor := 255.0 / 16rFFFF.
            i2 := n+1.
            i3 := 2*n+1.
            1 to:n do:[:vi |
                val := ((valueArray at:vi) * scaleFactor) rounded.
                rV at:vi put:val.
                val := ((valueArray at:i2) * scaleFactor) rounded.
                gV at:vi put:val.
                val := ((valueArray at:i3) * scaleFactor) rounded.
                bV at:vi put:val.
                i2 := i2 + 1.
                i3 := i3 + 1.
            ].
            colorMap := MappedPalette redVector:rV greenVector:gV blueVector:bV.
            ^ self
        ].
        (tagType == 321) ifTrue:[
            "/ 'halftonehints' print. value printNewline.
            metaData at:#HalftoneHints put:value.
            ^ self
        ].
        (tagType == 322) ifTrue:[
            "/ 'tilewidth' print. value printNewline.
            metaData at:#TileWidth put:value.
            ^ self
        ].
        (tagType == 323) ifTrue:[
            "/ 'tilelength' print. value printNewline.
            metaData at:#TileLength put:value.
            ^ self
        ].
        (tagType == 324) ifTrue:[
            "/ 'tileoffsets' print. value printNewline.
            metaData at:#TileOffsets put:valueArray.
            ^ self
        ].
        (tagType == 325) ifTrue:[
            "/ 'tilebytecounts' print. value printNewline.
            metaData at:#TileByteCounts put:valueArray.
            ^ self
        ].
        (tagType == 326) ifTrue:[
            "/ 'badFaxLines' print. value printNewline.
            ^ self
        ].
        (tagType == 327) ifTrue:[
            "CleanFaxData"

            "/        'cleanfaxdata' print. value printNewline.
            "/        (value == 0) ifTrue:[
            "/            'no lines with incorrect pixel counts' printNewline
            "/        ] ifFalse:[
            "/            (value == 1) ifTrue:[
            "/                'incorrect lines were regenerated' printNewline
            "/            ] ifFalse:[
            "/                (value == 2) ifTrue:[
            "/                    'incorrect lines were not regenerated' printNewline
            "/                ] ifFalse:[
            "/                    'cleanfaxdata invalid' printNewline
            "/                ]
            "/            ]
            "/        ].

            ^ self
        ].
        (tagType == 328) ifTrue:[
            "/ 'consecutiveBadFaxLines' print. value printNewline.
            ^ self
        ].
        (tagType == 330) ifTrue:[
            "/ subifd
            Verbose == true ifTrue:[ 
                Logger info:'      subifd: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 332) ifTrue:[
            "/ 'ink set' print. value printNewline.
            ^ self
        ].
        (tagType == 333) ifTrue:[
            "/ 'ink names' print. value printNewline.
            metaData at:#IncNames put:value.
            ^ self
        ].
        (tagType == 334) ifTrue:[
            "/ 'numinks' print. value printNewline.
            ^ self
        ].
        (tagType == 336) ifTrue:[
            "/ 'dot range' print. value printNewline.
            ^ self
        ].
        (tagType == 337) ifTrue:[
            "/ 'target printer' print. value printNewline.
            ^ self
        ].
        (tagType == 338) ifTrue:[
            "/ 'extrasamples' print. value printNewline.
            ^ self
        ].
        (tagType == 339) ifTrue:[
            "/ 'sample format' print. value printNewline.
            ^ self
        ].
        (tagType == 340) ifTrue:[
            "/ 'min sample value' print. value printNewline.
            ^ self
        ].
        (tagType == 341) ifTrue:[
            "/ 'max sample value' print. value printNewline.
            ^ self
        ].
        (tagType == 342) ifTrue:[
            "/ 'transfer range' print. value printNewline.
            ^ self
        ].
        (tagType == 343) ifTrue:[
            "/ 'clip path' print. value printNewline.
            ^ self
        ].
        (tagType == 344) ifTrue:[
            "/ 'xclip path units' print. value printNewline.
            ^ self
        ].
        (tagType == 345) ifTrue:[
            "/ 'yclip path units' print. value printNewline.
            ^ self
        ].
        (tagType == 347) ifTrue:[
            "/ 'jpegtables' print. value printNewline.
            ^ self
        ].
    ].

    (tagType between:400 and:499) ifTrue:[
        (tagType == 400) ifTrue:[
            "/ 'GlobalParametersIFD' print. value printNewline.
            ^ self
        ].
        (tagType == 401) ifTrue:[
            "/ 'ProfileType' print. value printNewline.
            ^ self
        ].
        (tagType == 402) ifTrue:[
            "/ 'FaxProfile' print. value printNewline.
            ^ self
        ].
        (tagType == 403) ifTrue:[
            "/ 'CodingMethods' print. value printNewline.
            ^ self
        ].
        (tagType == 404) ifTrue:[
            "/ 'VersionYear' print. value printNewline.
            ^ self
        ].
        (tagType == 405) ifTrue:[
            "/ 'ModeNumber' print. value printNewline.
            ^ self
        ].
        (tagType == 433) ifTrue:[
            "/ 'Decode' print. value printNewline.
            ^ self
        ].
        (tagType == 434) ifTrue:[
            "/ 'DefaultImageColor' print. value printNewline.
            ^ self
        ].
    ].
    
    (tagType between:500 and:599) ifTrue:[
        "/ obsolete JPEG tags
        (tagType == 512) ifTrue:[
            "/ 'jpeg proc' print. value printNewline.
            ^ self
        ].
        (tagType == 513) ifTrue:[
            "/ 'jpeg proc' print. value printNewline.
            ^ self
        ].
        (tagType == 514) ifTrue:[
            "/ 'jpeg ifByteCount' print. value printNewline.
            ^ self
        ].
        (tagType == 515) ifTrue:[
            "/ 'jpeg restartInterval' print. value printNewline.
            ^ self
        ].
        (tagType == 517) ifTrue:[
            "/ 'jpeg glossLessPredictors' print. value printNewline.
            ^ self
        ].
        (tagType == 518) ifTrue:[
            "/ 'jpeg pointTransform' print. value printNewline.
            ^ self
        ].
        (tagType == 519) ifTrue:[
            "/ 'jpeg qTables' print. value printNewline.
            ^ self
        ].
        (tagType == 520) ifTrue:[
            "/ 'jpeg dcTables' print. value printNewline.
             ^ self
        ].
        (tagType == 521) ifTrue:[
            "/ 'jpeg acTables' print. value printNewline.
            ^ self
        ].


        (tagType == 529) ifTrue:[
            "/ ycbr coeff
            Verbose == true ifTrue:[ 
                Logger info:'      ycbr coeff: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 530) ifTrue:[
            "/ ycbr subsampling
            Verbose == true ifTrue:[ 
                Logger info:'      ycbr subsampling: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 531) ifTrue:[
            "/ ycbr positioning
            Verbose == true ifTrue:[ 
                Logger info:'      ycbr positioning: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 532) ifTrue:[
            "/ referenceBlackWhite
            Verbose == true ifTrue:[ 
                Logger info:'      referenceBlackWhite: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 559) ifTrue:[
            "/ 'stripRowCounts' print. value printNewline.
            ^ self
        ].
    ].

    (tagType between:700 and:799) ifTrue:[
        (tagType == 700) ifTrue:[
            "XMLPACKET"

            "/ In TIFF files, the XML Packet containing XMP metadata is pointed to
            "/ by an entry in the Image File Directory (IFD). That entry has a Tag
            "/ value of 700, as shown in Table 1.1, "TIFF IFD Directory Entry for
            "/ XML Packets
            
            Verbose == true ifTrue:[ 
                Logger info:'      XMLPACKET: %1' with:value asString
            ].
            ^ self
        ].
    ].
    
    (tagType between:32000 and:32999) ifTrue:[
        (tagType == 32781) ifTrue:[
            "/'imageid' print. value printNewline.
            ^ self
        ].
        (tagType == 32932) ifTrue:[
            "/'wang annotation' print. value printNewline.
            ^ self
        ].

        "/ Private Island graphics tags
        (tagType == 32953) ifTrue:[
            "/'ref points' print. value printNewline.
            ^ self
        ].
        (tagType == 32954) ifTrue:[
            "/ 'regionTagPoint' print. value printNewline.
            ^ self
        ].
        (tagType == 32955) ifTrue:[
            "/ 'regionWarpCorners' print. value printNewline.
            ^ self
        ].
        (tagType == 32956) ifTrue:[
            "/ 'regionAffine' print. value printNewline.
            ^ self
        ].


        "/ Private SGI tags
        (tagType == 32995) ifTrue:[
            "/ 'matteing' print. value printNewline.
            ^ self
        ].
        (tagType == 32996) ifTrue:[
            "/ 'datatype' print. value printNewline.
            ^ self
        ].
        (tagType == 32997) ifTrue:[
            "/ 'imagedepth' print. value printNewline.
            ^ self
        ].
        (tagType == 32998) ifTrue:[
            "/ 'tiledepth' print. value printNewline.
            ^ self
        ].
    ].
    
    (tagType between:33000 and:33999) ifTrue:[
        "/ Private Pixar tags
        (tagType == 33300) ifTrue:[
            "/ 'image full width' print. value printNewline.
            ^ self
        ].
        (tagType == 33301) ifTrue:[
            "/ 'image full length' print. value printNewline.
            ^ self
        ].

        "/ Private Eastman Kodak tags
        (tagType == 33405) ifTrue:[
            "/ 'write serial number' print. value printNewline.
            ^ self
        ].

        "/ unknown
        (tagType == 33432) ifTrue:[
            "/ 'copyright' print. value printNewline.
            ^ self
        ].

        (tagType == 33550) ifTrue:[
            "/ 'geotiff modelpixelscaletag' print. value printNewline.
            ^ self
        ].

        (tagType == 33723) ifTrue:[
            "/ 'RICHTIFFIPTC' print. value printNewline.
            ^ self
        ].
    ].
    
    (tagType between:34000 and:34999) ifTrue:[
        "/ Private Texas instruments
        (tagType == 34232) ifTrue:[
            "/ 'sequence frame count' print. value printNewline.
            ^ self
        ].

        "/ Private Pixel magic
        (tagType == 34232) ifTrue:[
            "/ 'jbig options' print. value printNewline.
            ^ self
        ].

        "/ private Photoshop
        (tagType == 34377) ifTrue:[
            "/ 'photoshop RICHTIFFIPTC' print. value printNewline.
            ^ self
        ].
        (tagType == 34665) ifTrue:[
            "/ EXIFIFD
            Verbose == true ifTrue:[ 
                Logger info:'      EXIFIFD: %1' with:value 
            ].
            ^ self
        ].
        (tagType == 34675) ifTrue:[
            "/ 'ICCPROFILE' print. value printNewline.
            ^ self
        ].
        
        (tagType == 34732) ifTrue:[
            "/ 'ImageLayer' print. value printNewline.
            ^ self
        ].
        (tagType == 34859) ifTrue:[
            "/ '???' print. value printNewline.
            Verbose == true ifTrue:[ 
                Logger info:'      ?: %1' with:value 
            ].
            ^ self
        ].
        
        "/ More Private SGI
        (tagType == 34908) ifTrue:[
            "/ 'fax recv params' print. value printNewline.
            ^ self
        ].
        (tagType == 34909) ifTrue:[
            "/ 'fax subaddress' print. value printNewline.
            ^ self
        ].
        (tagType == 34910) ifTrue:[
            "/ 'fax recv time' print. value printNewline.
            ^ self
        ].
    ].

    (tagType between:36000 and:36999) ifTrue:[
        (tagType == 36867) ifTrue:[
            "/ '???' print. value printNewline.
            ^ self
        ].
    ].

    (tagType between:37000 and:37999) ifTrue:[
        (tagType == 37390) ifTrue:[
            "/ '???' print. value printNewline.
            ^ self
        ].
        (tagType == 37391) ifTrue:[
            "/ '???' print. value printNewline.
            ^ self
        ].
        (tagType == 37392) ifTrue:[
            "/ '???' print. value printNewline.
            ^ self
        ].
        (tagType == 37398) ifTrue:[
            "/ '???' print. value printNewline.
            ^ self
        ].
    ].

    (tagType between:42000 and:42999) ifTrue:[
        (tagType == 42112) ifTrue:[
            "/ 'GDAL_METADATA' print. value printNewline.
            ^ self
        ].
    ].

    "/ dng tags (see http://wwwimages.adobe.com/content/dam/Adobe/en/products/photoshop/pdfs/dng_spec_1.4.0.0.pdf)
    (tagType between:50000 and:50999) ifTrue:[
        (tagType == 50706) ifTrue:[
            "/ DNGVersion
            Verbose == true ifTrue:[ 
                Logger info:'      DNGVersion: %1' with:value
            ].
            ^ self
        ].
        (tagType == 50707) ifTrue:[
            "/ DNGBackwardVersion
            ^ self
        ].
        (tagType == 50708) ifTrue:[
            "/ UniqueCameraModel
            Verbose == true ifTrue:[ 
                Logger info:'      UniqueCameraModel: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 50709) ifTrue:[
            "/ LocalizedCameraModel
            Verbose == true ifTrue:[ 
                Logger info:'      LocalizedCameraModel: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 50710) ifTrue:[
            "/ 'CFAPlaneColor' print. value printNewline.
            ^ self
        ].
        (tagType == 50711) ifTrue:[
            "/ 'CFALayout' print. value printNewline.
            ^ self
        ].
        (tagType == 50712) ifTrue:[
            "/ 'LinearizationTable' print. value printNewline.
            ^ self
        ].
        (tagType == 50713) ifTrue:[
            "/ 'BlackLevelRepeatDim' print. value printNewline.
            ^ self
        ].
        (tagType == 50714) ifTrue:[
            "/ 'BlackLevel' print. value printNewline.
            ^ self
        ].
        (tagType == 50715) ifTrue:[
            "/ 'BlackLevelDeltaH' print. value printNewline.
            ^ self
        ].
        (tagType == 50716) ifTrue:[
            "/ 'BlackLevelDeltaV' print. value printNewline.
            ^ self
        ].
        (tagType == 50717) ifTrue:[
            "/ 'WhiteLevel' print. value printNewline.
            ^ self
        ].
        (tagType == 50718) ifTrue:[
            "/ 'DefaultScale' print. value printNewline.
            ^ self
        ].
        (tagType == 50719) ifTrue:[
            "/ 'DefaultCropOrigin' print. value printNewline.
            ^ self
        ].
        (tagType == 50720) ifTrue:[
            "/ 'DefaultCropSize' print. value printNewline.
            ^ self
        ].
        (tagType == 50721) ifTrue:[
            "/ 'ColorMatrix1' print. value printNewline.
            ^ self
        ].
        (tagType == 50722) ifTrue:[
            "/ 'ColorMatrix2' print. value printNewline.
            ^ self
        ].
        (tagType == 50723) ifTrue:[
            "/ 'CameraCalibrarion1' print. value printNewline.
            ^ self
        ].
        (tagType == 50724) ifTrue:[
            "/ 'CameraCalibrarion2' print. value printNewline.
            ^ self
        ].
        (tagType == 50725) ifTrue:[
            "/ 'ReductionMatrix1' print. value printNewline.
            ^ self
        ].
        (tagType == 50726) ifTrue:[
            "/ 'ReductionMatrix2' print. value printNewline.
            ^ self
        ].
        (tagType == 50727) ifTrue:[
            "/ 'AnalogBalance' print. value printNewline.
            ^ self
        ].
        (tagType == 50728) ifTrue:[
            "/ 'AsShotNeutral' print. value printNewline.
            ^ self
        ].
        (tagType == 50729) ifTrue:[
            "/ 'AsShotWhiteXY' print. value printNewline.
            ^ self
        ].
        (tagType == 50730) ifTrue:[
            "/ 'BaselineExposure' print. value printNewline.
            ^ self
        ].
        (tagType == 50731) ifTrue:[
            "/ 'BaselineNoise' print. value printNewline.
            ^ self
        ].
        (tagType == 50732) ifTrue:[
            "/ 'BaselineSharpness' print. value printNewline.
            ^ self
        ].
        (tagType == 50733) ifTrue:[
            "/ 'ByerGreenSplit' print. value printNewline.
            ^ self
        ].
        (tagType == 50734) ifTrue:[
            "/ 'LinearResponseLimit' print. value printNewline.
            ^ self
        ].
        (tagType == 50735) ifTrue:[
            "/ 'CameraSerialNumber' print. value printNewline.
            Verbose == true ifTrue:[ 
                Logger info:'      CameraSerialNumber: %1' with:value asString
            ].
            ^ self
        ].
        (tagType == 50736) ifTrue:[
            "/ 'LensInfo' print. value printNewline.
            ^ self
        ].
        (tagType == 50737) ifTrue:[
            "/ 'ChromaBlurRadius' print. value printNewline.
            ^ self
        ].
        (tagType == 50738) ifTrue:[
            "/ 'AntiAliasStrength' print. value printNewline.
            ^ self
        ].
        (tagType == 50739) ifTrue:[
            "/ 'ShadowScale' print. value printNewline.
            ^ self
        ].
        (tagType == 50740) ifTrue:[
            "/ 'DNGPrivateData' print. value printNewline.
            ^ self
        ].
        (tagType == 50741) ifTrue:[
            "/ 'MakerNoteSafety' print. value printNewline.
            ^ self
        ].
        (tagType == 50778) ifTrue:[
            "/ 'CalibrationIlluminant1' print. value printNewline.
            ^ self
        ].
        (tagType == 50779) ifTrue:[
            "/ 'CalibrationIlluminant2' print. value printNewline.
            ^ self
        ].
        (tagType == 50780) ifTrue:[
            "/ 'BestQualityScale' print. value printNewline.
            ^ self
        ].
        (tagType == 50781) ifTrue:[
            "/ 'RawDataUniqueID' print. value printNewline.
            ^ self
        ].
        (tagType == 50827) ifTrue:[
            "/ 'OriginalRawFileName' print. value printNewline.
            ^ self
        ].
    ].
    
"/
"/ 'TIFFReader: tag:' print. tagType print. ' typ:' print. numberType print.
"/ ' len:' print. length print. ' offs:' print. offset print. 
"/ ' val:' print. value print. ' valArr:' print. valueArray printNewline.  
"/
    'TIFFReader [warning]: unknown tag type ' errorPrint. tagType errorPrintCR

    "Modified (format): / 23-05-2017 / 16:12:58 / mawalch"
    "Modified (format): / 25-08-2017 / 17:02:57 / cg"
!

positionToStrip:stripNr
    inStream position:(stripOffsets at:stripNr).
!

positionToTile:tileNr
    inStream position:((metaData at:#'TileOffsets') at:tileNr).

    "Created: / 25-08-2017 / 13:43:30 / cg"
!

readBytes:n signed:isSigned
    "read n 8bit signed or unsigned integers and return them in an array or byteArray"

    |oldPos offset bytes nInline|

    n == 0 ifTrue:[^ ''].

    nInline := isBigTiff ifTrue:[8] ifFalse:[4].
    bytes := (isSigned ifTrue:[Array] ifFalse:[ByteArray]) new:n.
    (n <= nInline) ifTrue:[
        isSigned ifTrue:[
            1 to:n do:[:i | bytes at:i put:(inStream nextSignedByte) ].
        ] ifFalse:[
            inStream nextBytes:n into:bytes.
        ].
        (n < nInline) ifTrue:[
            inStream skip:(nInline - n).
        ]
    ] ifFalse:[
        offset := inStream nextInt32MSB:(byteOrder ~~ #lsb).
        oldPos := inStream position.
        inStream position:offset.
        isSigned ifTrue:[
            1 to:n do:[:i | bytes at:i put:(inStream nextSignedByte) ].
        ] ifFalse:[
            inStream nextBytes:n into:bytes.
        ].
        inStream position:oldPos
    ].
    ^ bytes

    "Modified: / 24-08-2017 / 23:25:30 / cg"
!

readChars:n
    "read n characters and return them in a string"

    |oldPos offset string nInline|

    n == 0 ifTrue:[^ ''].

    nInline := isBigTiff ifTrue:[8] ifFalse:[4].
    
    string := String new:(n - 1).
    (n <= nInline) ifTrue:[
        inStream nextBytes:(n - 1) into:string.
        (n < nInline) ifTrue:[
            inStream skip:(nInline - n).
        ]
    ] ifFalse:[
        offset := inStream nextInt32MSB:(byteOrder ~~ #lsb).
        oldPos := inStream position.
        inStream position:offset.
        inStream nextBytes:(n - 1) into:string.
        inStream position:oldPos
    ].
    ^ string

    "Modified: / 24-08-2017 / 23:25:03 / cg"
!

readDoubles:nFloats
    "read nFloats IEEE 64bit doubles and return them in an array"

    |oldPos offset values val msb 
     n "{ Class: SmallInteger }" |

    n := nFloats.

    msb := byteOrder ~~ #lsb.
    values := DoubleArray basicNew:n.
    (n == 1) ifTrue:[
        val := Float readBinaryIEEEDoubleFrom:inStream MSB:msb.
        values at:1 put:val.
    ] ifFalse:[
        offset := inStream nextInt32MSB:msb.
        oldPos := inStream position.
        inStream position:offset.
        1 to:n do:[:index |
            val := Float readBinaryIEEEDoubleFrom:inStream MSB:msb.
            values at:index put:val
        ].
        inStream position:oldPos
    ].
    ^ values

    "Modified: / 24-08-2017 / 23:28:22 / cg"
!

readFloats:nFloats
    "read nFloats IEEE 32bit floats and return them in an array"

    |oldPos offset values val val1 val2 msb 
     n "{ Class: SmallInteger }" |

    n := nFloats.

    msb := byteOrder ~~ #lsb.
    values := FloatArray basicNew:n.
    (isBigTiff and:[ n == 2 ]) ifTrue:[
        val1 := ShortFloat readBinaryIEEESingleFrom:inStream MSB:msb.
        val2 := ShortFloat readBinaryIEEESingleFrom:inStream MSB:msb.
        values at:1 put:val1.
        n == 2 ifTrue:[
            values at:2 put:val2.
        ].
    ] ifFalse:[    
        (n == 1) ifTrue:[
            val := ShortFloat readBinaryIEEESingleFrom:inStream MSB:msb.
            values at:1 put:val.
        ] ifFalse:[
            offset := inStream nextInt32MSB:msb.
            oldPos := inStream position.
            inStream position:offset.
            1 to:n do:[:index |
                val := ShortFloat readBinaryIEEESingleFrom:inStream MSB:msb.
                values at:index put:val
            ].
            inStream position:oldPos
        ].
    ].
    ^ values

    "Modified: / 24-08-2017 / 23:36:39 / cg"
!

readFracts:nFracts signed:isSigned
    "read nFracts fractions (2 32bit words) and return them in an array"

    |oldPos offset values numerator denominator msb
     n "{ Class: SmallInteger }" |

    n := nFracts.

    msb := byteOrder ~~ #lsb.
    values := Array basicNew:n.
    offset := inStream nextInt32MSB:msb.
    oldPos := inStream position.
    inStream position:offset.
    1 to:n do:[:index |
        numerator := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
        denominator := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
        values at:index put:(Fraction numerator:numerator denominator:denominator)
    ].
    inStream position:oldPos.
    ^ values
!

readLong8s:nLongs signed:isSigned
    "read nLongs signed or unsigned long8 numbers (64bit) and return them in an array"

    |oldPos offset values val msb 
     n "{ Class: SmallInteger }" |

    n := nLongs.

    msb := byteOrder ~~ #lsb.
    values := Array basicNew:n.
    (n == 1) ifTrue:[
        val := isSigned ifTrue:[inStream nextInt64MSB:msb] ifFalse:[inStream nextUnsignedInt64MSB:msb].
        values at:1 put:val.
    ] ifFalse:[
        offset := inStream nextInt64MSB:msb.
        oldPos := inStream position.
        inStream position:offset.
        1 to:n do:[:index |
            val := isSigned ifTrue:[inStream nextInt64MSB:msb] ifFalse:[inStream nextUnsignedInt64MSB:msb].
            values at:index put:val
        ].
        inStream position:oldPos
    ].
    ^ values

    "Created: / 24-08-2017 / 22:01:26 / cg"
!

readLongs:nLongs signed:isSigned
    "read nLongs signed or unsigned long numbers (32bit) and return them in an array"

    |oldPos offset values val val1 val2 msb 
     n "{ Class: SmallInteger }" |

    n := nLongs.

    msb := byteOrder ~~ #lsb.
    values := Array basicNew:n.
    (isBigTiff and:[ n <= 2 ]) ifTrue:[
        val1 := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
        val2 := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
        values at:1 put:val1.
        n == 2 ifTrue:[
            values at:2 put:val2.
        ].
    ] ifFalse:[
        (n == 1) ifTrue:[
            val := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
            values at:1 put:val.
        ] ifFalse:[
            offset := inStream nextInt32MSB:msb.
            oldPos := inStream position.
            inStream position:offset.
            1 to:n do:[:index |
                val := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
                values at:index put:val
            ].
            inStream position:oldPos
        ].
    ].
    ^ values

    "Modified: / 24-08-2017 / 23:35:38 / cg"
!

readShorts:nShorts signed:isSigned
    "read nShorts signed or unsigned short numbers (16bit) and return them in an array"

    |oldPos offset values msb val1 val2 val3 val4
     n "{ Class: SmallInteger }" |

    n := nShorts.

    msb := (byteOrder ~~ #lsb).
    values := Array basicNew:n.
    (isBigTiff and:[ (n <= 4) ]) ifTrue:[ 
        isSigned ifTrue:[
            val1 := inStream nextInt16MSB:msb.
            val2 := inStream nextInt16MSB:msb.
            val3 := inStream nextInt16MSB:msb.
            val4 := inStream nextInt16MSB:msb.
        ] ifFalse:[
            val1 := inStream nextUnsignedInt16MSB:msb.
            val2 := inStream nextUnsignedInt16MSB:msb.
            val3 := inStream nextUnsignedInt16MSB:msb.
            val4 := inStream nextUnsignedInt16MSB:msb.
        ].
        values at:1 put:val1.
        (n >= 2) ifTrue:[
            values at:2 put:val2.
            (n >= 3) ifTrue:[
                values at:3 put:val3.
                (n == 4) ifTrue:[
                    values at:4 put:val4.
                ]
            ]
        ]
    ] ifFalse:[
        (n <= 2) ifTrue:[
            isSigned ifTrue:[
                val1 := inStream nextInt16MSB:msb.
                val2 := inStream nextInt16MSB:msb.
            ] ifFalse:[
                val1 := inStream nextUnsignedInt16MSB:msb.
                val2 := inStream nextUnsignedInt16MSB:msb.
            ].
            values at:1 put:val1.
            (n == 2) ifTrue:[
                values at:2 put:val2
            ]
        ] ifFalse:[
            offset := inStream nextInt32MSB:msb.
            oldPos := inStream position.
            inStream position:offset.
            1 to:n do:[:index |
                isSigned ifTrue:[
                    val1 := inStream nextInt16MSB:msb.
                ] ifFalse:[
                    val1 := inStream nextUnsignedInt16MSB:msb.
                ].
                values at:index put:val1
            ].
            inStream position:oldPos
        ].
    ].
    ^ values

    "Modified: / 24-08-2017 / 23:33:09 / cg"
! !

!TIFFReader methodsFor:'private-writing'!

writeBitsPerSample
"
'bitsPerSample: ' print. bitsPerSample printNewline.
'store bitspersample at: ' print. outStream position printNewline.
"
    bitsPerSamplePos := outStream position.
    bitsPerSample do:[:n |
        self writeShort:n
    ]
!

writeColorMap
    |n|

    colorMapPos := outStream position.
    #(red green blue) do:[:component |
        n := 0.
        colorMap do:[:clr |
            |entry|

            clr isNil ifTrue:[
                entry := 0
            ] ifFalse:[
                entry := clr perform:component.
                "
                 tiff map is 16 bit - scale from percent to 0..16rFFFF
                "
                entry := (entry * 16rFFFF / 100) rounded.
            ].
            self writeShort:entry.
            n := n + 1
        ].

        "
         fill to 256 entries
        "
        [n < 256] whileTrue:[
            self writeShort:0.
            n := n + 1.
        ]
    ]

    "Modified: 20.2.1997 / 18:06:10 / cg"
!

writeStripByteCounts
"
'stripByteCounts: ' print. stripByteCounts printNewline.
'store stripbytecounts at: ' print. outStream position printNewline.
"
    stripByteCountsPos := outStream position.
    stripByteCounts do:[:c |
        self writeShort:c
    ]
!

writeStripOffsets
"
'stripOffsets: ' print. stripOffsets printNewline.
'store stripoffsets at: ' print. outStream position printNewline.
"
    stripOffsetsPos := outStream position.
    stripOffsets do:[:o |
        self writeLong:o
    ]
!

writeTag:tagType
    self writeTiffTag:tagType.
!

writeTiffTag:tagType
    |value valueArray numberType count address|

    count := 1.
    address := nil.
    (tagType == 253) ifTrue:[
        "tiff class"
    ].
    (tagType == 254) ifTrue:[
    ].
    (tagType == 255) ifTrue:[
        "SubfileType"
        value := subFileType.
        numberType := #long.
    ].
    (tagType == 256) ifTrue:[
        "ImageWidth"
        value := width.
        numberType := #short.
    ].
    (tagType == 257) ifTrue:[
        "ImageHeight"
        value := height.
        numberType := #short.
    ].
    (tagType == 258) ifTrue:[
        "bitspersample"
        address := bitsPerSamplePos.
        numberType := #short.
        count := bitsPerSample size.
        valueArray := bitsPerSample
    ].
    (tagType == 259) ifTrue:[
        "compression"
        value := compression.
        numberType := #short.
    ].
    (tagType == 262) ifTrue:[
        "photometric"
        (photometric == #whiteIs0) ifTrue:[
            value := 0
        ] ifFalse:[
            (photometric == #blackIs0) ifTrue:[
                value := 1
            ] ifFalse:[
                (photometric == #rgb) ifTrue:[
                    value := 2
                ] ifFalse:[
                    (photometric == #palette) ifTrue:[
                        value := 3
                    ] ifFalse:[
                        (photometric == #transparency) ifTrue:[
                            value := 4
                        ] ifFalse:[
                            self error:'bad photometric' mayProceed:true.
                        ]
                    ]
                ]
            ]
        ].
        numberType := #short.
    ].
    (tagType == 263) ifTrue:[
    ].
    (tagType == 264) ifTrue:[
    ].
    (tagType == 265) ifTrue:[
    ].
    (tagType == 266) ifTrue:[
        "fillOrder"
        (fillOrder == #msb) ifTrue:[
            value := 1
        ] ifFalse:[
            (fillOrder == #lsb) ifTrue:[
                value := 2
            ] ifFalse:[
                self error:'bad fillOrder' mayProceed:true
            ]
        ].
        numberType := #short.
    ].
    (tagType == 269) ifTrue:[
    ].
    (tagType == 270) ifTrue:[
    ].
    (tagType == 271) ifTrue:[
    ].
    (tagType == 272) ifTrue:[
    ].
    (tagType == 273) ifTrue:[
        "stripoffsets"
        address := stripOffsetsPos.
        numberType := #long.
        count := stripOffsets size.
        valueArray := stripOffsets
    ].
    (tagType == 274) ifTrue:[
    ].
    (tagType == 277) ifTrue:[
        "samplesPerPixel"
        value := samplesPerPixel.
        numberType := #short.
    ].
    (tagType == 278) ifTrue:[
        "rowsperstrip"
        value := rowsPerStrip.
        numberType := #short.
    ].
    (tagType == 279) ifTrue:[
        "stripbytecount"
        address := stripByteCountsPos.
        numberType := #short.
        count := stripByteCounts size.
        valueArray := stripByteCounts
    ].
    (tagType == 280) ifTrue:[
        "min sample value"
    ].
    (tagType == 281) ifTrue:[
        "max sample value"
    ].
    (tagType == 282) ifTrue:[
        "x resolution"
    ].
    (tagType == 283) ifTrue:[
        "y resolution"
    ].
    (tagType == 284) ifTrue:[
        "planarconfig"
        value := planarConfiguration.
        numberType := #short.
    ].
    (tagType == 285) ifTrue:[
        "pageName"
    ].
    (tagType == 286) ifTrue:[
        "xPosition"
    ].
    (tagType == 287) ifTrue:[
        "yPosition"
    ].
    (tagType == 288) ifTrue:[
        "freeOffsets"
    ].
    (tagType == 289) ifTrue:[
        "freeByteCounts"
    ].
    (tagType == 290) ifTrue:[
        "grayResponceUnit"
    ].
    (tagType == 291) ifTrue:[
        "grayResponceCurve"
    ].
    (tagType == 292) ifTrue:[
        "group3options"
        value := group3options.
        numberType := #long.
    ].
    (tagType == 293) ifTrue:[
        "group4options"
    ].
    (tagType == 296) ifTrue:[
        "resolutionunit"
        ^ self
    ].
    (tagType == 297) ifTrue:[
        "pageNumber"
    ].
    (tagType == 300) ifTrue:[
        "colorResponceUnit"
    ].
    (tagType == 301) ifTrue:[
        "colorResponceCurve"
    ].
    (tagType == 306) ifTrue:[
        "dateTime"
    ].
    (tagType == 315) ifTrue:[
        "artist"
    ].
    (tagType == 317) ifTrue:[
        "predictor"
    ].
    (tagType == 320) ifTrue:[
        "colormap"
        address := colorMapPos.
        numberType := #short.
        count := 256 "(colorMap at:1) size" * 3.
    ].

    (value isNil and:[address isNil]) ifTrue:[
        self error:'unhandled tag' mayProceed:true.
        ^ self
    ].

"
'tag:' print. tagType print. ' typ:' print. numberType print.
' len:' print. count print.
' val:' print. value printNewline.  
"

    self writeShort:tagType.
    numberType == #short ifTrue:[
        self writeShort:3.
        self writeLong:count.
    ] ifFalse:[
        numberType == #long ifTrue:[
            self writeShort:4.
            self writeLong:count.
        ] ifFalse:[
            numberType == #byte ifTrue:[
                self writeShort:1.
                self writeLong:count.
            ] ifFalse:[
                self error:'bad numbertype'
            ]
        ]
    ].
    address notNil ifTrue:[
        (numberType == #long and:[count == 1]) ifTrue:[
            self writeLong:(valueArray at:1).
            ^ self
        ].
        (numberType == #short and:[count <= 2]) ifTrue:[
            self writeShort:(valueArray at:1).
            count == 2 ifTrue:[
                self writeShort:(valueArray at:2).
            ] ifFalse:[
                self writeShort:0
            ].
            ^ self
        ].
        (numberType == #byte and:[count <= 4]) ifTrue:[
            outStream nextPut:(valueArray at:1).
            count > 1 ifTrue:[
                outStream nextPut:(valueArray at:2).
                count > 2 ifTrue:[
                    outStream nextPut:(valueArray at:3).
                    count > 3 ifTrue:[
                        outStream nextPut:(valueArray at:4).
                    ] ifFalse:[
                        outStream nextPut:0
                    ].
                ] ifFalse:[
                    outStream nextPut:0
                ].
            ] ifFalse:[
                outStream nextPut:0
            ].
            ^ self
        ].
        self writeLong:address.
        ^ self
    ].
    numberType == #short ifTrue:[
        self writeShort:value.
        self writeShort:0
    ] ifFalse:[
        numberType == #long ifTrue:[
            self writeLong:value
        ] ifFalse:[
            numberType == #byte ifTrue:[
                outStream nextPut:value.
                outStream nextPut:0.
                outStream nextPut:0.
                outStream nextPut:0.
            ] ifFalse:[
                self error:'bad numbertype'
            ]
        ]
    ].
!

writeUncompressedBits
    "write bits as one or multiple strips"

    |offs bytesPerRow nBytes
     h "{ Class: SmallInteger }"|

    nBytes := data size.
    nBytes < 16rFFFF ifTrue:[
        stripOffsets := Array with:(outStream position).
        stripByteCounts := Array with:nBytes.
        outStream nextPutBytes:nBytes from:data.
        rowsPerStrip := height
    ] ifFalse:[
        stripOffsets := Array basicNew:height.
        bytesPerRow := nBytes // height.
        stripByteCounts := (Array basicNew:height) atAllPut:bytesPerRow.

        offs := 1.
        h := height.
        1 to:h do:[:row |
            stripOffsets at:row put:(outStream position).
            outStream nextPutBytes:bytesPerRow from:data startingAt:offs.
            offs := offs + bytesPerRow
        ].
        rowsPerStrip := 1
    ].
"
    'stripOffsets: ' print. stripOffsets printNewline.
    'stripByteCounts: ' print. stripByteCounts printNewline.
"
! !

!TIFFReader methodsFor:'reading'!

fromStream:aStream
    "read a stream containing a TIFF image.
     Leave image description in instance variables.
     (i.e. to get the image, ask with image)."

    |char1 char2 version 
     numberOfTags "{ Class: SmallInteger }"
     tagType      "{ Class: SmallInteger }"
     numberType   "{ Class: SmallInteger }"
     length       "{ Class: SmallInteger }"
     result offset msb
     bytesPerRow offset1 offset2 tmp
     pos1|

    inStream := aStream.
    aStream binary.

    char1 := aStream next.
    char2 := aStream next.
    
    "/ first two chars are either II (intel byte order) 
    "/ or MM (motorola byte orrder)
    (char1 ~~ char2) ifTrue:[
        ^ self fileFormatError:'not a tiff file'.
    ].
    (char1 == $I codePoint) ifTrue:[
        byteOrder := #lsb.
        msb := false.
    ] ifFalse:[
        (char1 == $M codePoint) ifTrue:[
            byteOrder := #msb.
            msb := true.
        ] ifFalse:[
            ^ self fileFormatError:'not a tiff file'.
        ]
    ].
    isBigTiff := false.
    
    version := aStream nextUnsignedInt16MSB:msb.
    (version == 42) ifTrue:[
        offset := aStream nextUnsignedInt32MSB:msb.
        aStream position:offset.
    ] ifFalse:[
       (version == 43) ifTrue:[
            |byteSizeOfOffsets always0|

            "/ 43 is the proposed bigtiff format
            isBigTiff := true.
            byteSizeOfOffsets := aStream nextUnsignedInt16MSB:msb.
            byteSizeOfOffsets == 8 ifFalse:[
                ^ self fileFormatError:'version of bigtiff-file not supported'.
            ].
            always0 := aStream nextUnsignedInt16MSB:msb.
            always0 == 0 ifFalse:[
                ^ self fileFormatError:'version of bigtiff-file not supported'.
            ].
            offset := aStream nextUnsignedInt64MSB:msb.
            aStream position:offset.
        ] ifFalse:[    
            ^ self fileFormatError:'version of tiff-file not supported'.
        ].
    ].

    "setup default values"
    metaData := TIFFMetaData new.
    
    compression := 1. "none"
    fillOrder := #msb.
    planarConfiguration := 1.
    photometric := nil.
    bitsPerSample := 1.
    samplesPerPixel := 1.
    width := nil.
    height := nil.
    stripOffsets := nil.
    rowsPerStrip := nil.
    "resolutionUnit := 2."
    predictor := 1.
    orientation := nil.

    (version == 42) ifTrue:[
        numberOfTags := aStream nextUnsignedInt16MSB:msb.

        1 to:numberOfTags do:[:index |
            tagType := aStream nextUnsignedInt16MSB:msb.
            numberType := aStream nextUnsignedInt16MSB:msb.
            length := aStream nextInt32MSB:msb.
            self decodeTiffTag:tagType numberType:numberType length:length
        ].
        offset := aStream nextInt32MSB:msb.
    ] ifFalse:[
        numberOfTags := aStream nextUnsignedInt64MSB:msb.

        1 to:numberOfTags do:[:index |
            tagType := aStream nextUnsignedInt16MSB:msb.
            numberType := aStream nextUnsignedInt16MSB:msb.
            length := aStream nextInt64MSB:msb.
            pos1 := aStream position.
            self decodeTiffTag:tagType numberType:numberType length:length.
        ].
        offset := aStream nextInt32MSB:msb.
    ].
    (offset ~~ 0) ifTrue:[
        'TIFFReader [info]: more tags ignored' infoPrintCR
    ].

    "check for required tags"
    width isNil ifTrue:[
        ^ self fileFormatError:'missing width tag'.
    ].

    height isNil ifTrue:[
        ^ self fileFormatError:'missing length tag'.
    ].

    photometric isNil ifTrue:[
        ^ self fileFormatError:'missing photometric tag'.
    ].

    "given all the information, read the bits"
    stripOffsets isNil ifTrue:[
        (metaData notNil 
            and:[(metaData includesKey:#TileWidth) 
            and:[(metaData includesKey:#TileLength)
            and:[(metaData includesKey:#TileOffsets)
            and:[(metaData includesKey:#TileByteCounts) ]]]]
        ) ifFalse:[    
            ^ self fileFormatError:'missing stripOffsets or tileOffsets tag'.
        ].
        self reportDimension.
        result := self readTiledTiffImageData.
    ] ifFalse:[
        stripByteCounts isNil ifTrue:[
            stripOffsets size == 1 ifTrue:[
                stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
            ] ifFalse:[
                ^ self fileFormatError:'missing stripByteCounts'.
            ].    
        ].
        self reportDimension.
        rowsPerStrip isNil ifTrue:[
            rowsPerStrip := height
        ].

        result := self readTiffImageData.
    ].
    
    result isNil ifTrue:[
        "/ unsupported format.
        ^ nil
    ].

    orientation == #vFlip ifTrue:[
        "/ reverse rows to top-to bottom

        bytesPerRow := self bytesPerRow.
        tmp := ByteArray new:bytesPerRow.
        offset1 := 1.
        offset2 := (height-1)*bytesPerRow + 1.
        0 to:((height-1)//2) do:[:row |
            tmp replaceFrom:1 to:bytesPerRow with:data startingAt:offset1.
            data replaceFrom:offset1 to:(offset1+bytesPerRow-1) with:data startingAt:offset2.
            data replaceFrom:offset2 to:(offset2+bytesPerRow-1) with:tmp startingAt:1.
            offset1 := offset1 + bytesPerRow.
            offset2 := offset2 - bytesPerRow.
        ].
    ].
    orientation == #unsupported ifTrue:[
        'TIFFReader [warning]: unsupported orientation' errorPrintCR
    ].

    ^ result

    "Modified: / 25-08-2017 / 10:08:30 / cg"
! !

!TIFFReader methodsFor:'writing'!

save:image onStream:aStream
    "save image as (uncompressed) TIFF file on aFileName"

    |pos1 pos indicator|

    image mask notNil ifTrue:[
        Image informationLostQuerySignal
            raiseWith:image
            errorString:('TIFF writer does not (yet) support an imageMask').
    ].

    outStream := aStream.
    outStream binary.

    "save as msb"

    byteOrder := #msb.
"
    byteOrder := #lsb.
"
    fillOrder := #msb.
    width := image width.
    height := image height.
    photometric := image photometric.
    samplesPerPixel := image samplesPerPixel.
    bitsPerSample := image bitsPerSample.

    colorMap := image colorMap.
    planarConfiguration := 1.
    compression := 1.   "none"
    data := image bits.

    currentOffset := 0.

    (byteOrder == #msb) ifTrue:[
        indicator := $M codePoint.
    ] ifFalse:[
        indicator := $I codePoint.
    ].
    outStream nextPut:indicator; nextPut:indicator.
    currentOffset := currentOffset + 2.

    self writeShort:42.
    currentOffset := currentOffset + 2.

    pos1 := outStream position.
    self writeLong:0.           "start of tags - filled in later"
    currentOffset := currentOffset + 4.

    "output strips"

    self writeUncompressedBits. "this outputs bits as strips, sets stripOffsets and stripByteCounts"
    self writeStripOffsets.     "this outputs strip offsets, sets stripOffsetsPos"
    self writeStripByteCounts.  "this outputs strip bytecounts, sets stripByteCountPos"
    self writeBitsPerSample.    "this outputs bitsPerSample, sets bitsPerSamplePos"
    photometric == #palette ifTrue:[
        self writeColorMap      "this outputs colorMap, sets colorMapPos"
    ].

    pos := outStream position.        "backpatch tag offset"
    outStream position:pos1.
    self writeLong:pos.                     "fill in tag offset"
    outStream position:pos.
"
('patch tag offset at: ', (pos1 printStringRadix:16) , ' to ',
                         (pos printStringRadix:16)) printNewline.
"
    "output tag data"

    photometric == #palette ifTrue:[
        self writeShort:11.  "11 tags"
    ] ifFalse:[
        self writeShort:10.  "10 tags"
    ].
    self writeTag:256.               "image width"
    self writeTag:257.               "image height"
    self writeTag:258.               "bits per sample"
    self writeTag:259.               "compression"
    self writeTag:262.               "photometric"
    self writeTag:273.               "strip offsets"
    self writeTag:277.               "samplesPerPixel"
    self writeTag:278.               "rowsPerStrip"
    self writeTag:279.               "strip byte counts"
    self writeTag:284.               "planarconfig"
    photometric == #palette ifTrue:[
        self writeTag:320            "colorMap"
    ].
    self writeLong:0.                "end of tags mark"
! !

!TIFFReader class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


TIFFReader initialize!