module Codec.Ktx2.Level where import Data.Binary (Binary(..)) import Data.Binary.Get (getWord64le) import Data.Binary.Put (putWord64le) import Data.ByteString (ByteString) import Data.ByteString qualified as BS import Data.List (mapAccumR) import Data.Maybe (fromMaybe) import Data.Vector (Vector) import Data.Vector qualified as Vector import Data.Word (Word64) import GHC.Generics (Generic) data Level = Level { byteOffset :: Word64 -- ^ The offset from the start of the file of the first byte of image data for mip level. It is the offset of the first byte after any @mipPadding@. , byteLength :: Word64 -- ^ The total size of the data for supercompressed mip level. , uncompressedByteLength :: Word64 -- ^ the number of bytes of pixel data in LOD level after reflation from supercompression. This includes all z slices, all faces, all rows (or rows of blocks) and all pixels (or blocks) in each row for the mipmap level. When @supercompressionScheme == 0@, @byteLength@ must have the same value as this. When @supercompressionScheme == 1@ (BasisLZ) the value must be 0. } deriving (Eq, Show, Generic) instance Binary Level where get = do byteOffset <- getWord64le byteLength <- getWord64le uncompressedByteLength <- getWord64le pure Level{..} put Level{..} = do putWord64le byteOffset putWord64le byteLength putWord64le uncompressedByteLength -- | Build a level index from level data. -- -- Levels should be placed from largest (mip 0) to smallest. index :: Word64 -> [(Maybe Word64, ByteString)] -> Vector Level index startOffset = Vector.fromList . snd . mapAccumR mkIndex startOffset where mkIndex byteOffset (uncompressed, bytes) = ( byteOffset + byteLength , Level{..} ) where byteLength = fromIntegral $ BS.length bytes uncompressedByteLength = fromMaybe byteLength uncompressed