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
{ Level -> Word64
byteOffset :: Word64
, Level -> Word64
byteLength :: Word64
, Level -> Word64
uncompressedByteLength :: Word64
} deriving (Level -> Level -> Bool
(Level -> Level -> Bool) -> (Level -> Level -> Bool) -> Eq Level
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Level -> Level -> Bool
== :: Level -> Level -> Bool
$c/= :: Level -> Level -> Bool
/= :: Level -> Level -> Bool
Eq, Int -> Level -> ShowS
[Level] -> ShowS
Level -> String
(Int -> Level -> ShowS)
-> (Level -> String) -> ([Level] -> ShowS) -> Show Level
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Level -> ShowS
showsPrec :: Int -> Level -> ShowS
$cshow :: Level -> String
show :: Level -> String
$cshowList :: [Level] -> ShowS
showList :: [Level] -> ShowS
Show, (forall x. Level -> Rep Level x)
-> (forall x. Rep Level x -> Level) -> Generic Level
forall x. Rep Level x -> Level
forall x. Level -> Rep Level x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Level -> Rep Level x
from :: forall x. Level -> Rep Level x
$cto :: forall x. Rep Level x -> Level
to :: forall x. Rep Level x -> Level
Generic)
instance Binary Level where
get :: Get Level
get = do
Word64
byteOffset <- Get Word64
getWord64le
Word64
byteLength <- Get Word64
getWord64le
Word64
uncompressedByteLength <- Get Word64
getWord64le
pure Level{Word64
byteOffset :: Word64
byteLength :: Word64
uncompressedByteLength :: Word64
byteOffset :: Word64
byteLength :: Word64
uncompressedByteLength :: Word64
..}
put :: Level -> Put
put Level{Word64
byteOffset :: Level -> Word64
byteLength :: Level -> Word64
uncompressedByteLength :: Level -> Word64
byteOffset :: Word64
byteLength :: Word64
uncompressedByteLength :: Word64
..} = do
Word64 -> Put
putWord64le Word64
byteOffset
Word64 -> Put
putWord64le Word64
byteLength
Word64 -> Put
putWord64le Word64
uncompressedByteLength
index :: Word64 -> [(Maybe Word64, ByteString)] -> Vector Level
index :: Word64 -> [(Maybe Word64, ByteString)] -> Vector Level
index Word64
startOffset = [Level] -> Vector Level
forall a. [a] -> Vector a
Vector.fromList ([Level] -> Vector Level)
-> ([(Maybe Word64, ByteString)] -> [Level])
-> [(Maybe Word64, ByteString)]
-> Vector Level
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word64, [Level]) -> [Level]
forall a b. (a, b) -> b
snd ((Word64, [Level]) -> [Level])
-> ([(Maybe Word64, ByteString)] -> (Word64, [Level]))
-> [(Maybe Word64, ByteString)]
-> [Level]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word64 -> (Maybe Word64, ByteString) -> (Word64, Level))
-> Word64 -> [(Maybe Word64, ByteString)] -> (Word64, [Level])
forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR Word64 -> (Maybe Word64, ByteString) -> (Word64, Level)
mkIndex Word64
startOffset
where
mkIndex :: Word64 -> (Maybe Word64, ByteString) -> (Word64, Level)
mkIndex Word64
byteOffset (Maybe Word64
uncompressed, ByteString
bytes) =
( Word64
byteOffset Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
byteLength
, Level{Word64
byteOffset :: Word64
byteLength :: Word64
uncompressedByteLength :: Word64
byteOffset :: Word64
byteLength :: Word64
uncompressedByteLength :: Word64
..}
)
where
byteLength :: Word64
byteLength = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
BS.length ByteString
bytes
uncompressedByteLength :: Word64
uncompressedByteLength = Word64 -> Maybe Word64 -> Word64
forall a. a -> Maybe a -> a
fromMaybe Word64
byteLength Maybe Word64
uncompressed