{-# LANGUAGE UndecidableInstances #-}

module Dahdit.Sizes
  ( ByteCount (..)
  , ElemCount (..)
  , StaticByteSized (..)
  , staticByteSizeFoldable
  , byteSizeViaStatic
  )
where

import Dahdit.Internal (ViaEndianPair (..), ViaFromIntegral (..))
import Dahdit.Nums
  ( DoubleBE
  , DoubleLE
  , FloatBE
  , FloatLE
  , Int16BE
  , Int16LE
  , Int24BE
  , Int24LE
  , Int32BE
  , Int32LE
  , Int64BE
  , Int64LE
  , Word16BE
  , Word16LE
  , Word24BE
  , Word24LE
  , Word32BE
  , Word32LE
  , Word64BE
  , Word64LE
  )
import Dahdit.Proxy (proxyFor, proxyForF)
import Data.Coerce (coerce)
import Data.Default (Default)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Proxy (Proxy (..))
import Data.ShortWord (Int24, Word24)
import Data.Word (Word16, Word32, Word64, Word8)
import GHC.TypeLits (KnownNat, Nat, natVal)

-- Counts

newtype ByteCount = ByteCount {ByteCount -> Int
unByteCount :: Int}
  deriving stock (Int -> ByteCount -> ShowS
[ByteCount] -> ShowS
ByteCount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByteCount] -> ShowS
$cshowList :: [ByteCount] -> ShowS
show :: ByteCount -> String
$cshow :: ByteCount -> String
showsPrec :: Int -> ByteCount -> ShowS
$cshowsPrec :: Int -> ByteCount -> ShowS
Show)
  deriving newtype (ByteCount -> ByteCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteCount -> ByteCount -> Bool
$c/= :: ByteCount -> ByteCount -> Bool
== :: ByteCount -> ByteCount -> Bool
$c== :: ByteCount -> ByteCount -> Bool
Eq, Eq ByteCount
ByteCount -> ByteCount -> Bool
ByteCount -> ByteCount -> Ordering
ByteCount -> ByteCount -> ByteCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ByteCount -> ByteCount -> ByteCount
$cmin :: ByteCount -> ByteCount -> ByteCount
max :: ByteCount -> ByteCount -> ByteCount
$cmax :: ByteCount -> ByteCount -> ByteCount
>= :: ByteCount -> ByteCount -> Bool
$c>= :: ByteCount -> ByteCount -> Bool
> :: ByteCount -> ByteCount -> Bool
$c> :: ByteCount -> ByteCount -> Bool
<= :: ByteCount -> ByteCount -> Bool
$c<= :: ByteCount -> ByteCount -> Bool
< :: ByteCount -> ByteCount -> Bool
$c< :: ByteCount -> ByteCount -> Bool
compare :: ByteCount -> ByteCount -> Ordering
$ccompare :: ByteCount -> ByteCount -> Ordering
Ord, Integer -> ByteCount
ByteCount -> ByteCount
ByteCount -> ByteCount -> ByteCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ByteCount
$cfromInteger :: Integer -> ByteCount
signum :: ByteCount -> ByteCount
$csignum :: ByteCount -> ByteCount
abs :: ByteCount -> ByteCount
$cabs :: ByteCount -> ByteCount
negate :: ByteCount -> ByteCount
$cnegate :: ByteCount -> ByteCount
* :: ByteCount -> ByteCount -> ByteCount
$c* :: ByteCount -> ByteCount -> ByteCount
- :: ByteCount -> ByteCount -> ByteCount
$c- :: ByteCount -> ByteCount -> ByteCount
+ :: ByteCount -> ByteCount -> ByteCount
$c+ :: ByteCount -> ByteCount -> ByteCount
Num, Int -> ByteCount
ByteCount -> Int
ByteCount -> [ByteCount]
ByteCount -> ByteCount
ByteCount -> ByteCount -> [ByteCount]
ByteCount -> ByteCount -> ByteCount -> [ByteCount]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
$cenumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
enumFromTo :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromTo :: ByteCount -> ByteCount -> [ByteCount]
enumFromThen :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromThen :: ByteCount -> ByteCount -> [ByteCount]
enumFrom :: ByteCount -> [ByteCount]
$cenumFrom :: ByteCount -> [ByteCount]
fromEnum :: ByteCount -> Int
$cfromEnum :: ByteCount -> Int
toEnum :: Int -> ByteCount
$ctoEnum :: Int -> ByteCount
pred :: ByteCount -> ByteCount
$cpred :: ByteCount -> ByteCount
succ :: ByteCount -> ByteCount
$csucc :: ByteCount -> ByteCount
Enum, Num ByteCount
Ord ByteCount
ByteCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ByteCount -> Rational
$ctoRational :: ByteCount -> Rational
Real, Enum ByteCount
Real ByteCount
ByteCount -> Integer
ByteCount -> ByteCount -> (ByteCount, ByteCount)
ByteCount -> ByteCount -> ByteCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ByteCount -> Integer
$ctoInteger :: ByteCount -> Integer
divMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$cdivMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
quotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$cquotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
mod :: ByteCount -> ByteCount -> ByteCount
$cmod :: ByteCount -> ByteCount -> ByteCount
div :: ByteCount -> ByteCount -> ByteCount
$cdiv :: ByteCount -> ByteCount -> ByteCount
rem :: ByteCount -> ByteCount -> ByteCount
$crem :: ByteCount -> ByteCount -> ByteCount
quot :: ByteCount -> ByteCount -> ByteCount
$cquot :: ByteCount -> ByteCount -> ByteCount
Integral, ByteCount
forall a. a -> Default a
def :: ByteCount
$cdef :: ByteCount
Default)

newtype ElemCount = ElemCount {ElemCount -> Int
unElemCount :: Int}
  deriving stock (Int -> ElemCount -> ShowS
[ElemCount] -> ShowS
ElemCount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElemCount] -> ShowS
$cshowList :: [ElemCount] -> ShowS
show :: ElemCount -> String
$cshow :: ElemCount -> String
showsPrec :: Int -> ElemCount -> ShowS
$cshowsPrec :: Int -> ElemCount -> ShowS
Show)
  deriving newtype (ElemCount -> ElemCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElemCount -> ElemCount -> Bool
$c/= :: ElemCount -> ElemCount -> Bool
== :: ElemCount -> ElemCount -> Bool
$c== :: ElemCount -> ElemCount -> Bool
Eq, Eq ElemCount
ElemCount -> ElemCount -> Bool
ElemCount -> ElemCount -> Ordering
ElemCount -> ElemCount -> ElemCount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ElemCount -> ElemCount -> ElemCount
$cmin :: ElemCount -> ElemCount -> ElemCount
max :: ElemCount -> ElemCount -> ElemCount
$cmax :: ElemCount -> ElemCount -> ElemCount
>= :: ElemCount -> ElemCount -> Bool
$c>= :: ElemCount -> ElemCount -> Bool
> :: ElemCount -> ElemCount -> Bool
$c> :: ElemCount -> ElemCount -> Bool
<= :: ElemCount -> ElemCount -> Bool
$c<= :: ElemCount -> ElemCount -> Bool
< :: ElemCount -> ElemCount -> Bool
$c< :: ElemCount -> ElemCount -> Bool
compare :: ElemCount -> ElemCount -> Ordering
$ccompare :: ElemCount -> ElemCount -> Ordering
Ord, Integer -> ElemCount
ElemCount -> ElemCount
ElemCount -> ElemCount -> ElemCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ElemCount
$cfromInteger :: Integer -> ElemCount
signum :: ElemCount -> ElemCount
$csignum :: ElemCount -> ElemCount
abs :: ElemCount -> ElemCount
$cabs :: ElemCount -> ElemCount
negate :: ElemCount -> ElemCount
$cnegate :: ElemCount -> ElemCount
* :: ElemCount -> ElemCount -> ElemCount
$c* :: ElemCount -> ElemCount -> ElemCount
- :: ElemCount -> ElemCount -> ElemCount
$c- :: ElemCount -> ElemCount -> ElemCount
+ :: ElemCount -> ElemCount -> ElemCount
$c+ :: ElemCount -> ElemCount -> ElemCount
Num, Int -> ElemCount
ElemCount -> Int
ElemCount -> [ElemCount]
ElemCount -> ElemCount
ElemCount -> ElemCount -> [ElemCount]
ElemCount -> ElemCount -> ElemCount -> [ElemCount]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ElemCount -> ElemCount -> ElemCount -> [ElemCount]
$cenumFromThenTo :: ElemCount -> ElemCount -> ElemCount -> [ElemCount]
enumFromTo :: ElemCount -> ElemCount -> [ElemCount]
$cenumFromTo :: ElemCount -> ElemCount -> [ElemCount]
enumFromThen :: ElemCount -> ElemCount -> [ElemCount]
$cenumFromThen :: ElemCount -> ElemCount -> [ElemCount]
enumFrom :: ElemCount -> [ElemCount]
$cenumFrom :: ElemCount -> [ElemCount]
fromEnum :: ElemCount -> Int
$cfromEnum :: ElemCount -> Int
toEnum :: Int -> ElemCount
$ctoEnum :: Int -> ElemCount
pred :: ElemCount -> ElemCount
$cpred :: ElemCount -> ElemCount
succ :: ElemCount -> ElemCount
$csucc :: ElemCount -> ElemCount
Enum, Num ElemCount
Ord ElemCount
ElemCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ElemCount -> Rational
$ctoRational :: ElemCount -> Rational
Real, Enum ElemCount
Real ElemCount
ElemCount -> Integer
ElemCount -> ElemCount -> (ElemCount, ElemCount)
ElemCount -> ElemCount -> ElemCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ElemCount -> Integer
$ctoInteger :: ElemCount -> Integer
divMod :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
$cdivMod :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
quotRem :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
$cquotRem :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
mod :: ElemCount -> ElemCount -> ElemCount
$cmod :: ElemCount -> ElemCount -> ElemCount
div :: ElemCount -> ElemCount -> ElemCount
$cdiv :: ElemCount -> ElemCount -> ElemCount
rem :: ElemCount -> ElemCount -> ElemCount
$crem :: ElemCount -> ElemCount -> ElemCount
quot :: ElemCount -> ElemCount -> ElemCount
$cquot :: ElemCount -> ElemCount -> ElemCount
Integral, ElemCount
forall a. a -> Default a
def :: ElemCount
$cdef :: ElemCount
Default)

-- StaticByteSized

class (KnownNat (StaticSize a)) => StaticByteSized a where
  type StaticSize a :: Nat
  staticByteSize :: Proxy a -> ByteCount
  staticByteSize = forall a. Num a => Integer -> a
fromInteger forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Proxy a -> Proxy (StaticSize a)
staticByteProxy

staticByteProxy :: Proxy a -> Proxy (StaticSize a)
staticByteProxy :: forall a. Proxy a -> Proxy (StaticSize a)
staticByteProxy Proxy a
_ = forall {k} (t :: k). Proxy t
Proxy

instance StaticByteSized () where
  type StaticSize () = 0
  staticByteSize :: Proxy () -> ByteCount
staticByteSize Proxy ()
_ = ByteCount
0

instance StaticByteSized Word8 where
  type StaticSize Word8 = 1
  staticByteSize :: Proxy Word8 -> ByteCount
staticByteSize Proxy Word8
_ = ByteCount
1

instance StaticByteSized Int8 where
  type StaticSize Int8 = 1
  staticByteSize :: Proxy Int8 -> ByteCount
staticByteSize Proxy Int8
_ = ByteCount
1

instance StaticByteSized Word16 where
  type StaticSize Word16 = 2
  staticByteSize :: Proxy Word16 -> ByteCount
staticByteSize Proxy Word16
_ = ByteCount
2

instance StaticByteSized Int16 where
  type StaticSize Int16 = 2
  staticByteSize :: Proxy Int16 -> ByteCount
staticByteSize Proxy Int16
_ = ByteCount
2

instance StaticByteSized Word24 where
  type StaticSize Word24 = 3
  staticByteSize :: Proxy Word24 -> ByteCount
staticByteSize Proxy Word24
_ = ByteCount
3

instance StaticByteSized Int24 where
  type StaticSize Int24 = 3
  staticByteSize :: Proxy Int24 -> ByteCount
staticByteSize Proxy Int24
_ = ByteCount
3

instance StaticByteSized Word32 where
  type StaticSize Word32 = 4
  staticByteSize :: Proxy Word32 -> ByteCount
staticByteSize Proxy Word32
_ = ByteCount
4

instance StaticByteSized Int32 where
  type StaticSize Int32 = 4
  staticByteSize :: Proxy Int32 -> ByteCount
staticByteSize Proxy Int32
_ = ByteCount
4

instance StaticByteSized Word64 where
  type StaticSize Word64 = 8
  staticByteSize :: Proxy Word64 -> ByteCount
staticByteSize Proxy Word64
_ = ByteCount
8

instance StaticByteSized Int64 where
  type StaticSize Int64 = 8
  staticByteSize :: Proxy Int64 -> ByteCount
staticByteSize Proxy Int64
_ = ByteCount
8

instance StaticByteSized Float where
  type StaticSize Float = 4
  staticByteSize :: Proxy Float -> ByteCount
staticByteSize Proxy Float
_ = ByteCount
4

instance StaticByteSized Double where
  type StaticSize Double = 8
  staticByteSize :: Proxy Double -> ByteCount
staticByteSize Proxy Double
_ = ByteCount
8

instance StaticByteSized Bool where
  type StaticSize Bool = 1
  staticByteSize :: Proxy Bool -> ByteCount
staticByteSize Proxy Bool
_ = ByteCount
1

instance StaticByteSized Char where
  type StaticSize Char = 1
  staticByteSize :: Proxy Char -> ByteCount
staticByteSize Proxy Char
_ = ByteCount
1

instance StaticByteSized Int where
  type StaticSize Int = 8
  staticByteSize :: Proxy Int -> ByteCount
staticByteSize Proxy Int
_ = ByteCount
8

instance StaticByteSized Word16LE where
  type StaticSize Word16LE = 2
  staticByteSize :: Proxy Word16LE -> ByteCount
staticByteSize Proxy Word16LE
_ = ByteCount
2

instance StaticByteSized Int16LE where
  type StaticSize Int16LE = 2
  staticByteSize :: Proxy Int16LE -> ByteCount
staticByteSize Proxy Int16LE
_ = ByteCount
2

instance StaticByteSized Word24LE where
  type StaticSize Word24LE = 3
  staticByteSize :: Proxy Word24LE -> ByteCount
staticByteSize Proxy Word24LE
_ = ByteCount
3

instance StaticByteSized Int24LE where
  type StaticSize Int24LE = 3
  staticByteSize :: Proxy Int24LE -> ByteCount
staticByteSize Proxy Int24LE
_ = ByteCount
3

instance StaticByteSized Word32LE where
  type StaticSize Word32LE = 4
  staticByteSize :: Proxy Word32LE -> ByteCount
staticByteSize Proxy Word32LE
_ = ByteCount
4

instance StaticByteSized Int32LE where
  type StaticSize Int32LE = 4
  staticByteSize :: Proxy Int32LE -> ByteCount
staticByteSize Proxy Int32LE
_ = ByteCount
4

instance StaticByteSized Word64LE where
  type StaticSize Word64LE = 8
  staticByteSize :: Proxy Word64LE -> ByteCount
staticByteSize Proxy Word64LE
_ = ByteCount
8

instance StaticByteSized Int64LE where
  type StaticSize Int64LE = 8
  staticByteSize :: Proxy Int64LE -> ByteCount
staticByteSize Proxy Int64LE
_ = ByteCount
8

instance StaticByteSized FloatLE where
  type StaticSize FloatLE = 4
  staticByteSize :: Proxy FloatLE -> ByteCount
staticByteSize Proxy FloatLE
_ = ByteCount
4

instance StaticByteSized DoubleLE where
  type StaticSize DoubleLE = 8
  staticByteSize :: Proxy DoubleLE -> ByteCount
staticByteSize Proxy DoubleLE
_ = ByteCount
8

instance (StaticByteSized x, n ~ StaticSize x) => StaticByteSized (ViaFromIntegral n x y) where
  type StaticSize (ViaFromIntegral n x y) = n
  staticByteSize :: Proxy (ViaFromIntegral n x y) -> ByteCount
staticByteSize Proxy (ViaFromIntegral n x y)
_ = forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (forall {k} (t :: k). Proxy t
Proxy :: Proxy x)

instance (StaticByteSized le, n ~ StaticSize le) => StaticByteSized (ViaEndianPair n le be) where
  type StaticSize (ViaEndianPair n le be) = n
  staticByteSize :: Proxy (ViaEndianPair n le be) -> ByteCount
staticByteSize Proxy (ViaEndianPair n le be)
_ = forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (forall {k} (t :: k). Proxy t
Proxy :: Proxy le)

deriving via (ViaEndianPair 2 Word16LE Word16BE) instance StaticByteSized Word16BE

deriving via (ViaEndianPair 2 Int16LE Int16BE) instance StaticByteSized Int16BE

deriving via (ViaEndianPair 3 Word24LE Word24BE) instance StaticByteSized Word24BE

deriving via (ViaEndianPair 3 Int24LE Int24BE) instance StaticByteSized Int24BE

deriving via (ViaEndianPair 4 Word32LE Word32BE) instance StaticByteSized Word32BE

deriving via (ViaEndianPair 4 Int32LE Int32BE) instance StaticByteSized Int32BE

deriving via (ViaEndianPair 8 Word64LE Word64BE) instance StaticByteSized Word64BE

deriving via (ViaEndianPair 8 Int64LE Int64BE) instance StaticByteSized Int64BE

deriving via (ViaEndianPair 4 FloatLE FloatBE) instance StaticByteSized FloatBE

deriving via (ViaEndianPair 8 DoubleLE DoubleBE) instance StaticByteSized DoubleBE

staticByteSizeFoldable :: (Foldable f, StaticByteSized a) => f a -> ByteCount
staticByteSizeFoldable :: forall (f :: * -> *) a.
(Foldable f, StaticByteSized a) =>
f a -> ByteCount
staticByteSizeFoldable f a
fa = forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (forall (f :: * -> *) a. f a -> Proxy a
proxyForF f a
fa) forall a. Num a => a -> a -> a
* coerce :: forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) a. Foldable t => t a -> Int
length f a
fa)

byteSizeViaStatic :: (StaticByteSized a) => a -> ByteCount
byteSizeViaStatic :: forall a. StaticByteSized a => a -> ByteCount
byteSizeViaStatic = forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Proxy a
proxyFor