TIFFReader.st
changeset 3975 1315fd14851b
parent 3974 b4f7c8442dd8
child 3976 5eda7dd4846b
--- a/TIFFReader.st	Thu Aug 24 22:46:23 2017 +0200
+++ b/TIFFReader.st	Fri Aug 25 00:53:54 2017 +0200
@@ -17,7 +17,7 @@
 	instanceVariableNames:'planarConfiguration subFileType stripOffsets rowsPerStrip
 		fillOrder compression group3options predictor stripByteCounts
 		currentOffset stripOffsetsPos stripByteCountsPos bitsPerSamplePos
-		colorMapPos orientation'
+		colorMapPos orientation isBigTiff'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Graphics-Images-Readers'
@@ -143,7 +143,7 @@
      i2 "{ Class: SmallInteger }"
      i3 "{ Class: SmallInteger }" |
 
-"/ 'tiffTag: ' print. tagType printCR.
+    "/ 'tiffTag: ' print. tagType printCR.
 
     (numberType == 3 "TIFF_SHORT") ifTrue:[
         "16 bit ushort"
@@ -168,34 +168,49 @@
         value := self readBytes:length  signed:true
     ] ifFalse:[(numberType == 8 "TIFF_SSHORT") ifTrue:[
         "TIFF6: 16bit signed integer"
-        value := self readShorts:length signed:true
+        valueArray := self readShorts:length signed:true.
+        value := valueArray at:1
     ] ifFalse:[(numberType == 9 "TIFF_SLONG") ifTrue:[
         "TIFF6: 32bit signed integer"
-        value := self readLongs:length signed:true
+        valueArray := self readLongs:length signed:true.
+        value := valueArray at:1
     ] ifFalse:[(numberType == 10 "TIFF_SRATIONAL") ifTrue:[
         "TIFF6: 64 (32+32) bit signed fraction"
-        value := self readFracts:length signed:true
+        valueArray := self readFracts:length signed:true.
+        value := valueArray at:1
     ] ifFalse:[(numberType == 11 "TIFF_FLOAT") ifTrue:[
         "TIFF6: 32 bit IEEE float"
-        value := self readFloats:length
+        valueArray := self readFloats:length.
+        value := valueArray at:1
     ] ifFalse:[(numberType == 12 "TIFF_DOUBLE") ifTrue:[
         "TIFF6: 64 bit IEEE double"
-        value := self readDoubles:length
+        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"
-        value := self readLong8s:length signed:false
+        valueArray := self readLong8s:length signed:false.
+        value := valueArray at:1.
     ] ifFalse:[(numberType == 17 "TIFF_SLONG8") ifTrue:[
         "BIGTIFF: 8-byte signed integer"
-        value := self readLong8s:length signed:true
+        valueArray := self readLong8s:length signed:true.
+        value := valueArray at:1.
     ] ifFalse:[(numberType == 18 "TIFF_IFD8") ifTrue:[
         "BIGTIFF: 8-byte unsigned IFD offset"
-        value := self readLong8s:length signed:false
-
+        valueArray := self readLong8s:length signed:false.
+        value := valueArray at:1.
     ] ifFalse:[
-        offset := (inStream nextInt32MSB:(byteOrder ~~ #lsb))
-    ]]]]]]]]]]]]]].
+        isBigTiff ifTrue:[
+            offset := (inStream nextInt64MSB:(byteOrder ~~ #lsb))
+        ] ifFalse:[    
+            offset := (inStream nextInt32MSB:(byteOrder ~~ #lsb))
+        ]
+    ]]]]]]]]]]]]]]].
 
     (tagType between:200 and:299) ifTrue:[
         (tagType == 254) ifTrue:[
@@ -618,12 +633,12 @@
         ].
         (tagType == 324) ifTrue:[
             "/ 'tileoffsets' print. value printNewline.
-            metaData at:#TileOffsets put:value.
+            metaData at:#TileOffsets put:valueArray.
             ^ self
         ].
         (tagType == 325) ifTrue:[
             "/ 'tilebytecounts' print. value printNewline.
-            metaData at:#TileByteCounts put:value.
+            metaData at:#TileByteCounts put:valueArray.
             ^ self
         ].
         (tagType == 326) ifTrue:[
@@ -961,7 +976,7 @@
     'TIFFReader [warning]: unknown tag type ' errorPrint. tagType errorPrintCR
 
     "Modified (format): / 23-05-2017 / 16:12:58 / mawalch"
-    "Modified: / 24-08-2017 / 22:02:33 / cg"
+    "Modified: / 25-08-2017 / 00:24:44 / cg"
 ! !
 
 !TIFFReader methodsFor:'private-data reading'!
@@ -1323,6 +1338,120 @@
     "Modified: / 3.2.1998 / 18:12:36 / cg"
 !
 
+readTiledTiffImageData
+    (compression == 1) ifTrue:[
+        ^ self readTiledUncompressedTiffImageData.
+    ].
+    (compression == 5) ifTrue:[
+        ^ self readTiledLZWTiffImageData.
+    ].
+
+    ^ self fileFormatError:('compression type ' , compression printString , ' not known').
+
+    "Created: / 25-08-2017 / 00:19:14 / cg"
+!
+
+readTiledUncompressedTiffImageData
+    |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      
+     tileWidth tileLength tileOffsets tileByteCounts|
+
+    tileWidth := metaData at:#TileWidth.
+    tileLength := metaData at:#TileLength.
+    tileOffsets := metaData at:#TileOffsets.
+    tileByteCounts := metaData at:#TileByteCounts.
+self halt.    
+    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.
+    ].
+
+    "Created: / 25-08-2017 / 00:22:31 / cg"
+!
+
 readUncompressedTiffImageData
     |bytesPerRow   "{ Class: SmallInteger }"
      bitsPerRow    "{ Class: SmallInteger }"
@@ -1427,19 +1556,20 @@
 readBytes:n signed:isSigned
     "read n 8bit signed or unsigned integers and return them in an array or byteArray"
 
-    |oldPos offset bytes|
+    |oldPos offset bytes nInline|
 
     n == 0 ifTrue:[^ ''].
 
+    nInline := isBigTiff ifTrue:[8] ifFalse:[4].
     bytes := (isSigned ifTrue:[Array] ifFalse:[ByteArray]) new:n.
-    (n <= 4) ifTrue:[
+    (n <= nInline) ifTrue:[
         isSigned ifTrue:[
             1 to:n do:[:i | bytes at:i put:(inStream nextSignedByte) ].
         ] ifFalse:[
             inStream nextBytes:n into:bytes.
         ].
-        (n < 4) ifTrue:[
-            inStream skip:(4 - n).
+        (n < nInline) ifTrue:[
+            inStream skip:(nInline - n).
         ]
     ] ifFalse:[
         offset := inStream nextInt32MSB:(byteOrder ~~ #lsb).
@@ -1453,20 +1583,24 @@
         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|
+    |oldPos offset string nInline|
 
     n == 0 ifTrue:[^ ''].
 
+    nInline := isBigTiff ifTrue:[8] ifFalse:[4].
+    
     string := String new:(n - 1).
-    (n <= 4) ifTrue:[
+    (n <= nInline) ifTrue:[
         inStream nextBytes:(n - 1) into:string.
-        (n < 4) ifTrue:[
-            inStream skip:(4 - n).
+        (n < nInline) ifTrue:[
+            inStream skip:(nInline - n).
         ]
     ] ifFalse:[
         offset := inStream nextInt32MSB:(byteOrder ~~ #lsb).
@@ -1477,7 +1611,7 @@
     ].
     ^ string
 
-    "Modified: 5.9.1996 / 12:21:08 / cg"
+    "Modified: / 24-08-2017 / 23:25:03 / cg"
 !
 
 readDoubles:nFloats
@@ -1504,32 +1638,45 @@
         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 msb 
+    |oldPos offset values val val1 val2 msb 
      n "{ Class: SmallInteger }" |
 
     n := nFloats.
 
     msb := byteOrder ~~ #lsb.
     values := FloatArray basicNew:n.
-    (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 |
+    (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:index put:val
+            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
         ].
-        inStream position:oldPos
     ].
     ^ values
+
+    "Modified: / 24-08-2017 / 23:36:39 / cg"
 !
 
 readFracts:nFracts signed:isSigned
@@ -1585,66 +1732,103 @@
 readLongs:nLongs signed:isSigned
     "read nLongs signed or unsigned long numbers (32bit) and return them in an array"
 
-    |oldPos offset values val msb 
+    |oldPos offset values val val1 val2 msb 
      n "{ Class: SmallInteger }" |
 
     n := nLongs.
 
     msb := byteOrder ~~ #lsb.
     values := Array basicNew:n.
-    (n == 1) ifTrue:[
-        val := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
-        values at:1 put:val.
+    (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:[
-        offset := inStream nextInt32MSB:msb.
-        oldPos := inStream position.
-        inStream position:offset.
-        1 to:n do:[:index |
+        (n == 1) ifTrue:[
             val := isSigned ifTrue:[inStream nextInt32MSB:msb] ifFalse:[inStream nextUnsignedInt32MSB:msb].
-            values at:index put:val
+            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
         ].
-        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
+    |oldPos offset values msb val1 val2 val3 val4
      n "{ Class: SmallInteger }" |
 
     n := nShorts.
 
     msb := (byteOrder ~~ #lsb).
     values := Array basicNew:n.
-    (n <= 2) ifTrue:[
+    (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 >= 2) ifTrue:[
+            values at:2 put:val2.
+            (n >= 3) ifTrue:[
+                values at:3 put:val3.
+                (n == 4) ifTrue:[
+                    values at:4 put:val4.
+                ]
+            ]
         ]
     ] ifFalse:[
-        offset := inStream nextInt32MSB:msb.
-        oldPos := inStream position.
-        inStream position:offset.
-        1 to:n do:[:index |
+        (n <= 2) ifTrue:[
             isSigned ifTrue:[
                 val1 := inStream nextInt16MSB:msb.
+                val2 := inStream nextInt16MSB:msb.
             ] ifFalse:[
                 val1 := inStream nextUnsignedInt16MSB:msb.
+                val2 := inStream nextUnsignedInt16MSB:msb.
             ].
-            values at:index put:val1
+            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
         ].
-        inStream position:oldPos
     ].
     ^ values
+
+    "Modified: / 24-08-2017 / 23:33:09 / cg"
 ! !
 
 !TIFFReader methodsFor:'private-writing'!
@@ -2038,13 +2222,17 @@
      numberType   "{ Class: SmallInteger }"
      length       "{ Class: SmallInteger }"
      result offset msb
-     bytesPerRow offset1 offset2 tmp|
+     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'.
     ].
@@ -2059,7 +2247,8 @@
             ^ self fileFormatError:'not a tiff file'.
         ]
     ].
-
+    isBigTiff := false.
+    
     version := aStream nextUnsignedInt16MSB:msb.
     (version == 42) ifTrue:[
         offset := aStream nextUnsignedInt32MSB:msb.
@@ -2067,14 +2256,15 @@
     ] 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 == 8 ifFalse:[
+            always0 == 0 ifFalse:[
                 ^ self fileFormatError:'version of bigtiff-file not supported'.
             ].
             offset := aStream nextUnsignedInt64MSB:msb.
@@ -2118,7 +2308,8 @@
             tagType := aStream nextUnsignedInt16MSB:msb.
             numberType := aStream nextUnsignedInt16MSB:msb.
             length := aStream nextInt64MSB:msb.
-            self decodeTiffTag:tagType numberType:numberType length:length
+            pos1 := aStream position.
+            self decodeTiffTag:tagType numberType:numberType length:length.
         ].
         offset := aStream nextInt32MSB:msb.
     ].
@@ -2139,29 +2330,34 @@
         ^ self fileFormatError:'missing photometric tag'.
     ].
 
+    "given all the information, read the bits"
     stripOffsets isNil ifTrue:[
-        ^ self fileFormatError:'missing stripOffsets tag'.
-    ].
-
-    stripByteCounts isNil ifTrue:[
-        stripOffsets size == 1 ifTrue:[
-            stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
-        ]
-    ].
+        (metaData notNil 
+            and:[(metaData includesKey:#TileWidth) 
+            and:[(metaData includesKey:#TileLength)
+            and:[(metaData includesKey:#TileOffsets)
+            and:[(metaData includesKey:#TileByteCounts) ]]]]
+        ) ifFalse:[    
+            ^ self fileFormatError:'missing stripOffsets 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 tag'.
+            ].    
+        ].
+        self reportDimension.
+        rowsPerStrip isNil ifTrue:[
+            rowsPerStrip := height
+        ].
 
-    stripByteCounts isNil ifTrue:[
-        ^ self fileFormatError:'missing stripByteCounts tag'.
+        result := self readTiffImageData.
     ].
-
-    self reportDimension.
-
-    "given all the information, read the bits"
-
-    rowsPerStrip isNil ifTrue:[
-        rowsPerStrip := height
-    ].
-
-    result := self readTiffImageData.
+    
     result isNil ifTrue:[
         "/ unsupported format.
         ^ nil
@@ -2175,12 +2371,9 @@
         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.
+            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.
         ].
@@ -2191,7 +2384,7 @@
 
     ^ result
 
-    "Modified: / 24-08-2017 / 22:07:23 / cg"
+    "Modified: / 25-08-2017 / 00:20:58 / cg"
 ! !
 
 !TIFFReader methodsFor:'writing'!