{-# 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)
newtype ByteCount = ByteCount {ByteCount -> Int
unByteCount :: Int}
deriving stock (Int -> ByteCount -> ShowS
[ByteCount] -> ShowS
ByteCount -> String
(Int -> ByteCount -> ShowS)
-> (ByteCount -> String)
-> ([ByteCount] -> ShowS)
-> Show ByteCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByteCount -> ShowS
showsPrec :: Int -> ByteCount -> ShowS
$cshow :: ByteCount -> String
show :: ByteCount -> String
$cshowList :: [ByteCount] -> ShowS
showList :: [ByteCount] -> ShowS
Show)
deriving newtype (ByteCount -> ByteCount -> Bool
(ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool) -> Eq ByteCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ByteCount -> ByteCount -> Bool
== :: ByteCount -> ByteCount -> Bool
$c/= :: ByteCount -> ByteCount -> Bool
/= :: ByteCount -> ByteCount -> Bool
Eq, Eq ByteCount
Eq ByteCount =>
(ByteCount -> ByteCount -> Ordering)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> Ord 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
$ccompare :: ByteCount -> ByteCount -> Ordering
compare :: ByteCount -> ByteCount -> Ordering
$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
>= :: ByteCount -> ByteCount -> Bool
$cmax :: ByteCount -> ByteCount -> ByteCount
max :: ByteCount -> ByteCount -> ByteCount
$cmin :: ByteCount -> ByteCount -> ByteCount
min :: ByteCount -> ByteCount -> ByteCount
Ord, Integer -> ByteCount
ByteCount -> ByteCount
ByteCount -> ByteCount -> ByteCount
(ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (Integer -> ByteCount)
-> Num ByteCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ByteCount -> ByteCount -> ByteCount
+ :: ByteCount -> ByteCount -> ByteCount
$c- :: ByteCount -> ByteCount -> ByteCount
- :: ByteCount -> ByteCount -> ByteCount
$c* :: ByteCount -> ByteCount -> ByteCount
* :: ByteCount -> ByteCount -> ByteCount
$cnegate :: ByteCount -> ByteCount
negate :: ByteCount -> ByteCount
$cabs :: ByteCount -> ByteCount
abs :: ByteCount -> ByteCount
$csignum :: ByteCount -> ByteCount
signum :: ByteCount -> ByteCount
$cfromInteger :: Integer -> ByteCount
fromInteger :: Integer -> ByteCount
Num, Int -> ByteCount
ByteCount -> Int
ByteCount -> [ByteCount]
ByteCount -> ByteCount
ByteCount -> ByteCount -> [ByteCount]
ByteCount -> ByteCount -> ByteCount -> [ByteCount]
(ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (Int -> ByteCount)
-> (ByteCount -> Int)
-> (ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> ByteCount -> [ByteCount])
-> Enum 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
$csucc :: ByteCount -> ByteCount
succ :: ByteCount -> ByteCount
$cpred :: ByteCount -> ByteCount
pred :: ByteCount -> ByteCount
$ctoEnum :: Int -> ByteCount
toEnum :: Int -> ByteCount
$cfromEnum :: ByteCount -> Int
fromEnum :: ByteCount -> Int
$cenumFrom :: ByteCount -> [ByteCount]
enumFrom :: ByteCount -> [ByteCount]
$cenumFromThen :: ByteCount -> ByteCount -> [ByteCount]
enumFromThen :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromTo :: ByteCount -> ByteCount -> [ByteCount]
enumFromTo :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
enumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
Enum, Num ByteCount
Ord ByteCount
(Num ByteCount, Ord ByteCount) =>
(ByteCount -> Rational) -> Real ByteCount
ByteCount -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: ByteCount -> Rational
toRational :: ByteCount -> Rational
Real, Enum ByteCount
Real ByteCount
(Real ByteCount, Enum ByteCount) =>
(ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> (ByteCount, ByteCount))
-> (ByteCount -> ByteCount -> (ByteCount, ByteCount))
-> (ByteCount -> Integer)
-> Integral 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
$cquot :: ByteCount -> ByteCount -> ByteCount
quot :: ByteCount -> ByteCount -> ByteCount
$crem :: ByteCount -> ByteCount -> ByteCount
rem :: ByteCount -> ByteCount -> ByteCount
$cdiv :: ByteCount -> ByteCount -> ByteCount
div :: ByteCount -> ByteCount -> ByteCount
$cmod :: ByteCount -> ByteCount -> ByteCount
mod :: ByteCount -> ByteCount -> ByteCount
$cquotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
quotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$cdivMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
divMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$ctoInteger :: ByteCount -> Integer
toInteger :: ByteCount -> Integer
Integral, ByteCount
ByteCount -> Default ByteCount
forall a. a -> Default a
$cdef :: ByteCount
def :: ByteCount
Default)
newtype ElemCount = ElemCount {ElemCount -> Int
unElemCount :: Int}
deriving stock (Int -> ElemCount -> ShowS
[ElemCount] -> ShowS
ElemCount -> String
(Int -> ElemCount -> ShowS)
-> (ElemCount -> String)
-> ([ElemCount] -> ShowS)
-> Show ElemCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElemCount -> ShowS
showsPrec :: Int -> ElemCount -> ShowS
$cshow :: ElemCount -> String
show :: ElemCount -> String
$cshowList :: [ElemCount] -> ShowS
showList :: [ElemCount] -> ShowS
Show)
deriving newtype (ElemCount -> ElemCount -> Bool
(ElemCount -> ElemCount -> Bool)
-> (ElemCount -> ElemCount -> Bool) -> Eq ElemCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElemCount -> ElemCount -> Bool
== :: ElemCount -> ElemCount -> Bool
$c/= :: ElemCount -> ElemCount -> Bool
/= :: ElemCount -> ElemCount -> Bool
Eq, Eq ElemCount
Eq ElemCount =>
(ElemCount -> ElemCount -> Ordering)
-> (ElemCount -> ElemCount -> Bool)
-> (ElemCount -> ElemCount -> Bool)
-> (ElemCount -> ElemCount -> Bool)
-> (ElemCount -> ElemCount -> Bool)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> Ord 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
$ccompare :: ElemCount -> ElemCount -> Ordering
compare :: ElemCount -> ElemCount -> Ordering
$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
>= :: ElemCount -> ElemCount -> Bool
$cmax :: ElemCount -> ElemCount -> ElemCount
max :: ElemCount -> ElemCount -> ElemCount
$cmin :: ElemCount -> ElemCount -> ElemCount
min :: ElemCount -> ElemCount -> ElemCount
Ord, Integer -> ElemCount
ElemCount -> ElemCount
ElemCount -> ElemCount -> ElemCount
(ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount)
-> (ElemCount -> ElemCount)
-> (ElemCount -> ElemCount)
-> (Integer -> ElemCount)
-> Num ElemCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ElemCount -> ElemCount -> ElemCount
+ :: ElemCount -> ElemCount -> ElemCount
$c- :: ElemCount -> ElemCount -> ElemCount
- :: ElemCount -> ElemCount -> ElemCount
$c* :: ElemCount -> ElemCount -> ElemCount
* :: ElemCount -> ElemCount -> ElemCount
$cnegate :: ElemCount -> ElemCount
negate :: ElemCount -> ElemCount
$cabs :: ElemCount -> ElemCount
abs :: ElemCount -> ElemCount
$csignum :: ElemCount -> ElemCount
signum :: ElemCount -> ElemCount
$cfromInteger :: Integer -> ElemCount
fromInteger :: Integer -> ElemCount
Num, Int -> ElemCount
ElemCount -> Int
ElemCount -> [ElemCount]
ElemCount -> ElemCount
ElemCount -> ElemCount -> [ElemCount]
ElemCount -> ElemCount -> ElemCount -> [ElemCount]
(ElemCount -> ElemCount)
-> (ElemCount -> ElemCount)
-> (Int -> ElemCount)
-> (ElemCount -> Int)
-> (ElemCount -> [ElemCount])
-> (ElemCount -> ElemCount -> [ElemCount])
-> (ElemCount -> ElemCount -> [ElemCount])
-> (ElemCount -> ElemCount -> ElemCount -> [ElemCount])
-> Enum 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
$csucc :: ElemCount -> ElemCount
succ :: ElemCount -> ElemCount
$cpred :: ElemCount -> ElemCount
pred :: ElemCount -> ElemCount
$ctoEnum :: Int -> ElemCount
toEnum :: Int -> ElemCount
$cfromEnum :: ElemCount -> Int
fromEnum :: ElemCount -> Int
$cenumFrom :: ElemCount -> [ElemCount]
enumFrom :: ElemCount -> [ElemCount]
$cenumFromThen :: ElemCount -> ElemCount -> [ElemCount]
enumFromThen :: ElemCount -> ElemCount -> [ElemCount]
$cenumFromTo :: ElemCount -> ElemCount -> [ElemCount]
enumFromTo :: ElemCount -> ElemCount -> [ElemCount]
$cenumFromThenTo :: ElemCount -> ElemCount -> ElemCount -> [ElemCount]
enumFromThenTo :: ElemCount -> ElemCount -> ElemCount -> [ElemCount]
Enum, Num ElemCount
Ord ElemCount
(Num ElemCount, Ord ElemCount) =>
(ElemCount -> Rational) -> Real ElemCount
ElemCount -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: ElemCount -> Rational
toRational :: ElemCount -> Rational
Real, Enum ElemCount
Real ElemCount
(Real ElemCount, Enum ElemCount) =>
(ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> ElemCount)
-> (ElemCount -> ElemCount -> (ElemCount, ElemCount))
-> (ElemCount -> ElemCount -> (ElemCount, ElemCount))
-> (ElemCount -> Integer)
-> Integral 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
$cquot :: ElemCount -> ElemCount -> ElemCount
quot :: ElemCount -> ElemCount -> ElemCount
$crem :: ElemCount -> ElemCount -> ElemCount
rem :: ElemCount -> ElemCount -> ElemCount
$cdiv :: ElemCount -> ElemCount -> ElemCount
div :: ElemCount -> ElemCount -> ElemCount
$cmod :: ElemCount -> ElemCount -> ElemCount
mod :: ElemCount -> ElemCount -> ElemCount
$cquotRem :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
quotRem :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
$cdivMod :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
divMod :: ElemCount -> ElemCount -> (ElemCount, ElemCount)
$ctoInteger :: ElemCount -> Integer
toInteger :: ElemCount -> Integer
Integral, ElemCount
ElemCount -> Default ElemCount
forall a. a -> Default a
$cdef :: ElemCount
def :: ElemCount
Default)
class (KnownNat (StaticSize a)) => StaticByteSized a where
type StaticSize a :: Nat
staticByteSize :: Proxy a -> ByteCount
staticByteSize = Integer -> ByteCount
forall a. Num a => Integer -> a
fromInteger (Integer -> ByteCount)
-> (Proxy a -> Integer) -> Proxy a -> ByteCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy (StaticSize a) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (StaticSize a) -> Integer)
-> (Proxy a -> Proxy (StaticSize a)) -> Proxy a -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> Proxy (StaticSize a)
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
_ = Proxy (StaticSize 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)
_ = Proxy x -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (Proxy x
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)
_ = Proxy le -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (Proxy le
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 = Proxy a -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (f a -> Proxy a
forall (f :: * -> *) a. f a -> Proxy a
proxyForF f a
fa) ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* Int -> ByteCount
forall a b. Coercible a b => a -> b
coerce (f a -> Int
forall a. f a -> Int
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 = Proxy a -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (Proxy a -> ByteCount) -> (a -> Proxy a) -> a -> ByteCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Proxy a
forall a. a -> Proxy a
proxyFor