{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# OPTIONS_GHC -fno-prof-auto #-}
module Basement.Types.OffsetSize
( FileSize(..)
, Offset(..)
, Offset8
, sentinel
, offsetOfE
, offsetPlusE
, offsetMinusE
, offsetRecast
, offsetCast
, offsetSub
, offsetShiftL
, offsetShiftR
, sizeCast
, sizeLastOffset
, sizeAsOffset
, sizeSub
, countOfRoundUp
, offsetAsSize
, (+.)
, (.==#)
, CountOf(..)
, sizeOfE
, csizeOfOffset
, csizeOfSize
, sizeOfCSSize
, sizeOfCSize
, Countable
, Offsetable
, natValCountOf
, natValOffset
) where
#include "MachDeps.h"
import GHC.Types
import GHC.Word
import GHC.Int
import GHC.Prim
import System.Posix.Types (CSsize (..))
import Data.Bits
import Basement.Compat.Base
import Basement.Compat.C.Types
import Basement.Compat.Semigroup
import Data.Proxy
import Basement.Numerical.Number
import Basement.Numerical.Additive
import Basement.Numerical.Subtractive
import Basement.Numerical.Multiplicative
import Basement.Numerical.Conversion (intToWord)
import Basement.Nat
import Basement.IntegralConv
import Data.List (foldl')
import qualified Prelude
#if WORD_SIZE_IN_BITS < 64
import GHC.IntWord64
#endif
newtype FileSize = FileSize Word64
deriving (Int -> FileSize -> ShowS
[FileSize] -> ShowS
FileSize -> String
(Int -> FileSize -> ShowS)
-> (FileSize -> String) -> ([FileSize] -> ShowS) -> Show FileSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileSize] -> ShowS
$cshowList :: [FileSize] -> ShowS
show :: FileSize -> String
$cshow :: FileSize -> String
showsPrec :: Int -> FileSize -> ShowS
$cshowsPrec :: Int -> FileSize -> ShowS
Show,FileSize -> FileSize -> Bool
(FileSize -> FileSize -> Bool)
-> (FileSize -> FileSize -> Bool) -> Eq FileSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileSize -> FileSize -> Bool
$c/= :: FileSize -> FileSize -> Bool
== :: FileSize -> FileSize -> Bool
$c== :: FileSize -> FileSize -> Bool
Eq,Eq FileSize
Eq FileSize
-> (FileSize -> FileSize -> Ordering)
-> (FileSize -> FileSize -> Bool)
-> (FileSize -> FileSize -> Bool)
-> (FileSize -> FileSize -> Bool)
-> (FileSize -> FileSize -> Bool)
-> (FileSize -> FileSize -> FileSize)
-> (FileSize -> FileSize -> FileSize)
-> Ord FileSize
FileSize -> FileSize -> Bool
FileSize -> FileSize -> Ordering
FileSize -> FileSize -> FileSize
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 :: FileSize -> FileSize -> FileSize
$cmin :: FileSize -> FileSize -> FileSize
max :: FileSize -> FileSize -> FileSize
$cmax :: FileSize -> FileSize -> FileSize
>= :: FileSize -> FileSize -> Bool
$c>= :: FileSize -> FileSize -> Bool
> :: FileSize -> FileSize -> Bool
$c> :: FileSize -> FileSize -> Bool
<= :: FileSize -> FileSize -> Bool
$c<= :: FileSize -> FileSize -> Bool
< :: FileSize -> FileSize -> Bool
$c< :: FileSize -> FileSize -> Bool
compare :: FileSize -> FileSize -> Ordering
$ccompare :: FileSize -> FileSize -> Ordering
$cp1Ord :: Eq FileSize
Ord)
type Offset8 = Offset Word8
newtype Offset ty = Offset Int
deriving (Int -> Offset ty -> ShowS
[Offset ty] -> ShowS
Offset ty -> String
(Int -> Offset ty -> ShowS)
-> (Offset ty -> String)
-> ([Offset ty] -> ShowS)
-> Show (Offset ty)
forall ty. Int -> Offset ty -> ShowS
forall ty. [Offset ty] -> ShowS
forall ty. Offset ty -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Offset ty] -> ShowS
$cshowList :: forall ty. [Offset ty] -> ShowS
show :: Offset ty -> String
$cshow :: forall ty. Offset ty -> String
showsPrec :: Int -> Offset ty -> ShowS
$cshowsPrec :: forall ty. Int -> Offset ty -> ShowS
Show,Offset ty -> Offset ty -> Bool
(Offset ty -> Offset ty -> Bool)
-> (Offset ty -> Offset ty -> Bool) -> Eq (Offset ty)
forall ty. Offset ty -> Offset ty -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Offset ty -> Offset ty -> Bool
$c/= :: forall ty. Offset ty -> Offset ty -> Bool
== :: Offset ty -> Offset ty -> Bool
$c== :: forall ty. Offset ty -> Offset ty -> Bool
Eq,Eq (Offset ty)
Eq (Offset ty)
-> (Offset ty -> Offset ty -> Ordering)
-> (Offset ty -> Offset ty -> Bool)
-> (Offset ty -> Offset ty -> Bool)
-> (Offset ty -> Offset ty -> Bool)
-> (Offset ty -> Offset ty -> Bool)
-> (Offset ty -> Offset ty -> Offset ty)
-> (Offset ty -> Offset ty -> Offset ty)
-> Ord (Offset ty)
Offset ty -> Offset ty -> Bool
Offset ty -> Offset ty -> Ordering
Offset ty -> Offset ty -> Offset ty
forall ty. Eq (Offset ty)
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
forall ty. Offset ty -> Offset ty -> Bool
forall ty. Offset ty -> Offset ty -> Ordering
forall ty. Offset ty -> Offset ty -> Offset ty
min :: Offset ty -> Offset ty -> Offset ty
$cmin :: forall ty. Offset ty -> Offset ty -> Offset ty
max :: Offset ty -> Offset ty -> Offset ty
$cmax :: forall ty. Offset ty -> Offset ty -> Offset ty
>= :: Offset ty -> Offset ty -> Bool
$c>= :: forall ty. Offset ty -> Offset ty -> Bool
> :: Offset ty -> Offset ty -> Bool
$c> :: forall ty. Offset ty -> Offset ty -> Bool
<= :: Offset ty -> Offset ty -> Bool
$c<= :: forall ty. Offset ty -> Offset ty -> Bool
< :: Offset ty -> Offset ty -> Bool
$c< :: forall ty. Offset ty -> Offset ty -> Bool
compare :: Offset ty -> Offset ty -> Ordering
$ccompare :: forall ty. Offset ty -> Offset ty -> Ordering
$cp1Ord :: forall ty. Eq (Offset ty)
Ord,Int -> Offset ty
Offset ty -> Int
Offset ty -> [Offset ty]
Offset ty -> Offset ty
Offset ty -> Offset ty -> [Offset ty]
Offset ty -> Offset ty -> Offset ty -> [Offset ty]
(Offset ty -> Offset ty)
-> (Offset ty -> Offset ty)
-> (Int -> Offset ty)
-> (Offset ty -> Int)
-> (Offset ty -> [Offset ty])
-> (Offset ty -> Offset ty -> [Offset ty])
-> (Offset ty -> Offset ty -> [Offset ty])
-> (Offset ty -> Offset ty -> Offset ty -> [Offset ty])
-> Enum (Offset ty)
forall ty. Int -> Offset ty
forall ty. Offset ty -> Int
forall ty. Offset ty -> [Offset ty]
forall ty. Offset ty -> Offset ty
forall ty. Offset ty -> Offset ty -> [Offset ty]
forall ty. Offset ty -> Offset ty -> Offset ty -> [Offset ty]
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 :: Offset ty -> Offset ty -> Offset ty -> [Offset ty]
$cenumFromThenTo :: forall ty. Offset ty -> Offset ty -> Offset ty -> [Offset ty]
enumFromTo :: Offset ty -> Offset ty -> [Offset ty]
$cenumFromTo :: forall ty. Offset ty -> Offset ty -> [Offset ty]
enumFromThen :: Offset ty -> Offset ty -> [Offset ty]
$cenumFromThen :: forall ty. Offset ty -> Offset ty -> [Offset ty]
enumFrom :: Offset ty -> [Offset ty]
$cenumFrom :: forall ty. Offset ty -> [Offset ty]
fromEnum :: Offset ty -> Int
$cfromEnum :: forall ty. Offset ty -> Int
toEnum :: Int -> Offset ty
$ctoEnum :: forall ty. Int -> Offset ty
pred :: Offset ty -> Offset ty
$cpred :: forall ty. Offset ty -> Offset ty
succ :: Offset ty -> Offset ty
$csucc :: forall ty. Offset ty -> Offset ty
Enum,Offset ty
n -> Offset ty -> Offset ty
Offset ty -> Offset ty -> Offset ty
Offset ty
-> (Offset ty -> Offset ty -> Offset ty)
-> (forall n. IsNatural n => n -> Offset ty -> Offset ty)
-> Additive (Offset ty)
forall ty. Offset ty
forall a.
a
-> (a -> a -> a)
-> (forall n. IsNatural n => n -> a -> a)
-> Additive a
forall n. IsNatural n => n -> Offset ty -> Offset ty
forall ty. Offset ty -> Offset ty -> Offset ty
forall ty n. IsNatural n => n -> Offset ty -> Offset ty
scale :: n -> Offset ty -> Offset ty
$cscale :: forall ty n. IsNatural n => n -> Offset ty -> Offset ty
+ :: Offset ty -> Offset ty -> Offset ty
$c+ :: forall ty. Offset ty -> Offset ty -> Offset ty
azero :: Offset ty
$cazero :: forall ty. Offset ty
Additive,Typeable,Integer -> Offset ty
(Integer -> Offset ty) -> Integral (Offset ty)
forall ty. Integer -> Offset ty
forall a. (Integer -> a) -> Integral a
fromInteger :: Integer -> Offset ty
$cfromInteger :: forall ty. Integer -> Offset ty
Integral,Integer -> Offset ty
Offset ty -> Offset ty
Offset ty -> Offset ty -> Offset ty
(Offset ty -> Offset ty -> Offset ty)
-> (Offset ty -> Offset ty -> Offset ty)
-> (Offset ty -> Offset ty -> Offset ty)
-> (Offset ty -> Offset ty)
-> (Offset ty -> Offset ty)
-> (Offset ty -> Offset ty)
-> (Integer -> Offset ty)
-> Num (Offset ty)
forall ty. Integer -> Offset ty
forall ty. Offset ty -> Offset ty
forall ty. Offset ty -> Offset ty -> Offset ty
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Offset ty
$cfromInteger :: forall ty. Integer -> Offset ty
signum :: Offset ty -> Offset ty
$csignum :: forall ty. Offset ty -> Offset ty
abs :: Offset ty -> Offset ty
$cabs :: forall ty. Offset ty -> Offset ty
negate :: Offset ty -> Offset ty
$cnegate :: forall ty. Offset ty -> Offset ty
* :: Offset ty -> Offset ty -> Offset ty
$c* :: forall ty. Offset ty -> Offset ty -> Offset ty
- :: Offset ty -> Offset ty -> Offset ty
$c- :: forall ty. Offset ty -> Offset ty -> Offset ty
+ :: Offset ty -> Offset ty -> Offset ty
$c+ :: forall ty. Offset ty -> Offset ty -> Offset ty
Prelude.Num)
sentinel :: Offset ty
sentinel = Int -> Offset ty
forall ty. Int -> Offset ty
Offset (-Int
1)
instance IsIntegral (Offset ty) where
toInteger :: Offset ty -> Integer
toInteger (Offset Int
i) = Int -> Integer
forall a. IsIntegral a => a -> Integer
toInteger Int
i
instance IsNatural (Offset ty) where
toNatural :: Offset ty -> Natural
toNatural (Offset Int
i) = Word -> Natural
forall a. IsNatural a => a -> Natural
toNatural (Int -> Word
intToWord Int
i)
instance Subtractive (Offset ty) where
type Difference (Offset ty) = CountOf ty
(Offset Int
a) - :: Offset ty -> Offset ty -> Difference (Offset ty)
- (Offset Int
b) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int
aInt -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
-Int
b)
(+.) :: Offset ty -> Int -> Offset ty
+. :: Offset ty -> Int -> Offset ty
(+.) (Offset Int
a) Int
b = Int -> Offset ty
forall ty. Int -> Offset ty
Offset (Int
a Int -> Int -> Int
forall a. Additive a => a -> a -> a
+ Int
b)
{-# INLINE (+.) #-}
(.==#) :: Offset ty -> CountOf ty -> Bool
.==# :: Offset ty -> CountOf ty -> Bool
(.==#) (Offset Int
ofs) (CountOf Int
sz) = Int
ofs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
sz
{-# INLINE (.==#) #-}
offsetOfE :: CountOf Word8 -> Offset ty -> Offset8
offsetOfE :: CountOf Word8 -> Offset ty -> Offset8
offsetOfE (CountOf Int
sz) (Offset Int
ty) = Int -> Offset8
forall ty. Int -> Offset ty
Offset (Int
ty Int -> Int -> Int
forall a. Multiplicative a => a -> a -> a
* Int
sz)
offsetPlusE :: Offset ty -> CountOf ty -> Offset ty
offsetPlusE :: Offset ty -> CountOf ty -> Offset ty
offsetPlusE (Offset Int
ofs) (CountOf Int
sz) = Int -> Offset ty
forall ty. Int -> Offset ty
Offset (Int
ofs Int -> Int -> Int
forall a. Additive a => a -> a -> a
+ Int
sz)
offsetMinusE :: Offset ty -> CountOf ty -> Offset ty
offsetMinusE :: Offset ty -> CountOf ty -> Offset ty
offsetMinusE (Offset Int
ofs) (CountOf Int
sz) = Int -> Offset ty
forall ty. Int -> Offset ty
Offset (Int
ofs Int -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
- Int
sz)
offsetSub :: Offset a -> Offset a -> Offset a
offsetSub :: Offset a -> Offset a -> Offset a
offsetSub (Offset Int
m) (Offset Int
n) = Int -> Offset a
forall ty. Int -> Offset ty
Offset (Int
m Int -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
- Int
n)
offsetRecast :: CountOf Word8 -> CountOf Word8 -> Offset ty -> Offset ty2
offsetRecast :: CountOf Word8 -> CountOf Word8 -> Offset ty -> Offset ty2
offsetRecast CountOf Word8
szTy (CountOf Int
szTy2) Offset ty
ofs =
let (Offset Int
bytes) = CountOf Word8 -> Offset ty -> Offset8
forall ty. CountOf Word8 -> Offset ty -> Offset8
offsetOfE CountOf Word8
szTy Offset ty
ofs
in Int -> Offset ty2
forall ty. Int -> Offset ty
Offset (Int
bytes Int -> Int -> Int
forall a. IDivisible a => a -> a -> a
`div` Int
szTy2)
offsetShiftR :: Int -> Offset ty -> Offset ty2
offsetShiftR :: Int -> Offset ty -> Offset ty2
offsetShiftR Int
n (Offset Int
o) = Int -> Offset ty2
forall ty. Int -> Offset ty
Offset (Int
o Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
n)
offsetShiftL :: Int -> Offset ty -> Offset ty2
offsetShiftL :: Int -> Offset ty -> Offset ty2
offsetShiftL Int
n (Offset Int
o) = Int -> Offset ty2
forall ty. Int -> Offset ty
Offset (Int
o Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
n)
offsetCast :: Proxy (a -> b) -> Offset a -> Offset b
offsetCast :: Proxy (a -> b) -> Offset a -> Offset b
offsetCast Proxy (a -> b)
_ (Offset Int
o) = Int -> Offset b
forall ty. Int -> Offset ty
Offset Int
o
{-# INLINE offsetCast #-}
sizeCast :: Proxy (a -> b) -> CountOf a -> CountOf b
sizeCast :: Proxy (a -> b) -> CountOf a -> CountOf b
sizeCast Proxy (a -> b)
_ (CountOf Int
sz) = Int -> CountOf b
forall ty. Int -> CountOf ty
CountOf Int
sz
{-# INLINE sizeCast #-}
sizeSub :: CountOf a -> CountOf a -> CountOf a
sizeSub :: CountOf a -> CountOf a -> CountOf a
sizeSub (CountOf Int
m) (CountOf Int
n)
| Int
Difference Int
diff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = Int -> CountOf a
forall ty. Int -> CountOf ty
CountOf Int
Difference Int
diff
| Bool
otherwise = String -> CountOf a
forall a. HasCallStack => String -> a
error String
"sizeSub negative size"
where
diff :: Difference Int
diff = Int
m Int -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
- Int
n
sizeLastOffset :: CountOf a -> Offset a
sizeLastOffset :: CountOf a -> Offset a
sizeLastOffset (CountOf Int
s)
| Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int -> Offset a
forall ty. Int -> Offset ty
Offset (Int -> Int
forall a. Enum a => a -> a
pred Int
s)
| Bool
otherwise = String -> Offset a
forall a. HasCallStack => String -> a
error String
"last offset on size 0"
sizeAsOffset :: CountOf a -> Offset a
sizeAsOffset :: CountOf a -> Offset a
sizeAsOffset (CountOf Int
a) = Int -> Offset a
forall ty. Int -> Offset ty
Offset Int
a
{-# INLINE sizeAsOffset #-}
offsetAsSize :: Offset a -> CountOf a
offsetAsSize :: Offset a -> CountOf a
offsetAsSize (Offset Int
a) = Int -> CountOf a
forall ty. Int -> CountOf ty
CountOf Int
a
{-# INLINE offsetAsSize #-}
newtype CountOf ty = CountOf Int
deriving (Int -> CountOf ty -> ShowS
[CountOf ty] -> ShowS
CountOf ty -> String
(Int -> CountOf ty -> ShowS)
-> (CountOf ty -> String)
-> ([CountOf ty] -> ShowS)
-> Show (CountOf ty)
forall ty. Int -> CountOf ty -> ShowS
forall ty. [CountOf ty] -> ShowS
forall ty. CountOf ty -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CountOf ty] -> ShowS
$cshowList :: forall ty. [CountOf ty] -> ShowS
show :: CountOf ty -> String
$cshow :: forall ty. CountOf ty -> String
showsPrec :: Int -> CountOf ty -> ShowS
$cshowsPrec :: forall ty. Int -> CountOf ty -> ShowS
Show,CountOf ty -> CountOf ty -> Bool
(CountOf ty -> CountOf ty -> Bool)
-> (CountOf ty -> CountOf ty -> Bool) -> Eq (CountOf ty)
forall ty. CountOf ty -> CountOf ty -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CountOf ty -> CountOf ty -> Bool
$c/= :: forall ty. CountOf ty -> CountOf ty -> Bool
== :: CountOf ty -> CountOf ty -> Bool
$c== :: forall ty. CountOf ty -> CountOf ty -> Bool
Eq,Eq (CountOf ty)
Eq (CountOf ty)
-> (CountOf ty -> CountOf ty -> Ordering)
-> (CountOf ty -> CountOf ty -> Bool)
-> (CountOf ty -> CountOf ty -> Bool)
-> (CountOf ty -> CountOf ty -> Bool)
-> (CountOf ty -> CountOf ty -> Bool)
-> (CountOf ty -> CountOf ty -> CountOf ty)
-> (CountOf ty -> CountOf ty -> CountOf ty)
-> Ord (CountOf ty)
CountOf ty -> CountOf ty -> Bool
CountOf ty -> CountOf ty -> Ordering
CountOf ty -> CountOf ty -> CountOf ty
forall ty. Eq (CountOf ty)
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
forall ty. CountOf ty -> CountOf ty -> Bool
forall ty. CountOf ty -> CountOf ty -> Ordering
forall ty. CountOf ty -> CountOf ty -> CountOf ty
min :: CountOf ty -> CountOf ty -> CountOf ty
$cmin :: forall ty. CountOf ty -> CountOf ty -> CountOf ty
max :: CountOf ty -> CountOf ty -> CountOf ty
$cmax :: forall ty. CountOf ty -> CountOf ty -> CountOf ty
>= :: CountOf ty -> CountOf ty -> Bool
$c>= :: forall ty. CountOf ty -> CountOf ty -> Bool
> :: CountOf ty -> CountOf ty -> Bool
$c> :: forall ty. CountOf ty -> CountOf ty -> Bool
<= :: CountOf ty -> CountOf ty -> Bool
$c<= :: forall ty. CountOf ty -> CountOf ty -> Bool
< :: CountOf ty -> CountOf ty -> Bool
$c< :: forall ty. CountOf ty -> CountOf ty -> Bool
compare :: CountOf ty -> CountOf ty -> Ordering
$ccompare :: forall ty. CountOf ty -> CountOf ty -> Ordering
$cp1Ord :: forall ty. Eq (CountOf ty)
Ord,Int -> CountOf ty
CountOf ty -> Int
CountOf ty -> [CountOf ty]
CountOf ty -> CountOf ty
CountOf ty -> CountOf ty -> [CountOf ty]
CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty]
(CountOf ty -> CountOf ty)
-> (CountOf ty -> CountOf ty)
-> (Int -> CountOf ty)
-> (CountOf ty -> Int)
-> (CountOf ty -> [CountOf ty])
-> (CountOf ty -> CountOf ty -> [CountOf ty])
-> (CountOf ty -> CountOf ty -> [CountOf ty])
-> (CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty])
-> Enum (CountOf ty)
forall ty. Int -> CountOf ty
forall ty. CountOf ty -> Int
forall ty. CountOf ty -> [CountOf ty]
forall ty. CountOf ty -> CountOf ty
forall ty. CountOf ty -> CountOf ty -> [CountOf ty]
forall ty. CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty]
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 :: CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty]
$cenumFromThenTo :: forall ty. CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty]
enumFromTo :: CountOf ty -> CountOf ty -> [CountOf ty]
$cenumFromTo :: forall ty. CountOf ty -> CountOf ty -> [CountOf ty]
enumFromThen :: CountOf ty -> CountOf ty -> [CountOf ty]
$cenumFromThen :: forall ty. CountOf ty -> CountOf ty -> [CountOf ty]
enumFrom :: CountOf ty -> [CountOf ty]
$cenumFrom :: forall ty. CountOf ty -> [CountOf ty]
fromEnum :: CountOf ty -> Int
$cfromEnum :: forall ty. CountOf ty -> Int
toEnum :: Int -> CountOf ty
$ctoEnum :: forall ty. Int -> CountOf ty
pred :: CountOf ty -> CountOf ty
$cpred :: forall ty. CountOf ty -> CountOf ty
succ :: CountOf ty -> CountOf ty
$csucc :: forall ty. CountOf ty -> CountOf ty
Enum,Typeable,Integer -> CountOf ty
(Integer -> CountOf ty) -> Integral (CountOf ty)
forall ty. Integer -> CountOf ty
forall a. (Integer -> a) -> Integral a
fromInteger :: Integer -> CountOf ty
$cfromInteger :: forall ty. Integer -> CountOf ty
Integral)
instance Prelude.Num (CountOf ty) where
fromInteger :: Integer -> CountOf ty
fromInteger Integer
a = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Integer -> Int
forall a. Integral a => Integer -> a
fromInteger Integer
a)
+ :: CountOf ty -> CountOf ty -> CountOf ty
(+) (CountOf Int
a) (CountOf Int
b) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int
aInt -> Int -> Int
forall a. Additive a => a -> a -> a
+Int
b)
(-) (CountOf Int
a) (CountOf Int
b)
| Int
b Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
a = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf Int
0
| Bool
otherwise = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int
a Int -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
- Int
b)
* :: CountOf ty -> CountOf ty -> CountOf ty
(*) (CountOf Int
a) (CountOf Int
b) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int
aInt -> Int -> Int
forall a. Multiplicative a => a -> a -> a
*Int
b)
abs :: CountOf ty -> CountOf ty
abs CountOf ty
a = CountOf ty
a
negate :: CountOf ty -> CountOf ty
negate CountOf ty
_ = String -> CountOf ty
forall a. HasCallStack => String -> a
error String
"cannot negate CountOf: use Foundation Numerical hierarchy for this function to not be exposed to CountOf"
signum :: CountOf ty -> CountOf ty
signum (CountOf Int
a) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int -> Int
forall a. Num a => a -> a
Prelude.signum Int
a)
instance IsIntegral (CountOf ty) where
toInteger :: CountOf ty -> Integer
toInteger (CountOf Int
i) = Int -> Integer
forall a. IsIntegral a => a -> Integer
toInteger Int
i
instance IsNatural (CountOf ty) where
toNatural :: CountOf ty -> Natural
toNatural (CountOf Int
i) = Word -> Natural
forall a. IsNatural a => a -> Natural
toNatural (Int -> Word
intToWord Int
i)
instance Additive (CountOf ty) where
azero :: CountOf ty
azero = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf Int
0
+ :: CountOf ty -> CountOf ty -> CountOf ty
(+) (CountOf Int
a) (CountOf Int
b) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int
aInt -> Int -> Int
forall a. Additive a => a -> a -> a
+Int
b)
scale :: n -> CountOf ty -> CountOf ty
scale n
n (CountOf Int
a) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (n -> Int -> Int
forall a n. (Additive a, IsNatural n) => n -> a -> a
scale n
n Int
a)
instance Subtractive (CountOf ty) where
type Difference (CountOf ty) = Maybe (CountOf ty)
(CountOf Int
a) - :: CountOf ty -> CountOf ty -> Difference (CountOf ty)
- (CountOf Int
b) | Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
b = CountOf ty -> Maybe (CountOf ty)
forall a. a -> Maybe a
Just (CountOf ty -> Maybe (CountOf ty))
-> (Int -> CountOf ty) -> Int -> Maybe (CountOf ty)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int -> Maybe (CountOf ty)) -> Int -> Maybe (CountOf ty)
forall a b. (a -> b) -> a -> b
$ Int
a Int -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
- Int
b
| Bool
otherwise = Difference (CountOf ty)
forall a. Maybe a
Nothing
instance Semigroup (CountOf ty) where
<> :: CountOf ty -> CountOf ty -> CountOf ty
(<>) = CountOf ty -> CountOf ty -> CountOf ty
forall a. Additive a => a -> a -> a
(+)
instance Monoid (CountOf ty) where
mempty :: CountOf ty
mempty = CountOf ty
forall a. Additive a => a
azero
mappend :: CountOf ty -> CountOf ty -> CountOf ty
mappend = CountOf ty -> CountOf ty -> CountOf ty
forall a. Additive a => a -> a -> a
(+)
mconcat :: [CountOf ty] -> CountOf ty
mconcat = (CountOf ty -> CountOf ty -> CountOf ty)
-> CountOf ty -> [CountOf ty] -> CountOf ty
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' CountOf ty -> CountOf ty -> CountOf ty
forall a. Additive a => a -> a -> a
(+) CountOf ty
0
sizeOfE :: CountOf Word8 -> CountOf ty -> CountOf Word8
sizeOfE :: CountOf Word8 -> CountOf ty -> CountOf Word8
sizeOfE (CountOf Int
sz) (CountOf Int
ty) = Int -> CountOf Word8
forall ty. Int -> CountOf ty
CountOf (Int
ty Int -> Int -> Int
forall a. Multiplicative a => a -> a -> a
* Int
sz)
countOfRoundUp :: Int -> CountOf ty -> CountOf ty
countOfRoundUp :: Int -> CountOf ty -> CountOf ty
countOfRoundUp Int
alignment (CountOf Int
n) = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf ((Int
n Int -> Int -> Int
forall a. Additive a => a -> a -> a
+ (Int
alignmentInt -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
-Int
1)) Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int -> Int
forall a. Bits a => a -> a
complement (Int
alignmentInt -> Int -> Difference Int
forall a. Subtractive a => a -> a -> Difference a
-Int
1))
csizeOfSize :: CountOf Word8 -> CSize
#if WORD_SIZE_IN_BITS < 64
csizeOfSize (CountOf (I# sz)) = CSize (W32# (int2Word# sz))
#else
csizeOfSize :: CountOf Word8 -> CSize
csizeOfSize (CountOf (I# Int#
sz)) = Word64 -> CSize
CSize (Word# -> Word64
W64# (Int# -> Word#
int2Word# Int#
sz))
#endif
csizeOfOffset :: Offset8 -> CSize
#if WORD_SIZE_IN_BITS < 64
csizeOfOffset (Offset (I# sz)) = CSize (W32# (int2Word# sz))
#else
csizeOfOffset :: Offset8 -> CSize
csizeOfOffset (Offset (I# Int#
sz)) = Word64 -> CSize
CSize (Word# -> Word64
W64# (Int# -> Word#
int2Word# Int#
sz))
#endif
sizeOfCSSize :: CSsize -> CountOf Word8
sizeOfCSSize :: CSsize -> CountOf Word8
sizeOfCSSize (CSsize (-1)) = String -> CountOf Word8
forall a. HasCallStack => String -> a
error String
"invalid size: CSSize is -1"
#if WORD_SIZE_IN_BITS < 64
sizeOfCSSize (CSsize (I32# sz)) = CountOf (I# sz)
#else
sizeOfCSSize (CSsize (I64# Int#
sz)) = Int -> CountOf Word8
forall ty. Int -> CountOf ty
CountOf (Int# -> Int
I# Int#
sz)
#endif
sizeOfCSize :: CSize -> CountOf Word8
#if WORD_SIZE_IN_BITS < 64
sizeOfCSize (CSize (W32# sz)) = CountOf (I# (word2Int# sz))
#else
sizeOfCSize :: CSize -> CountOf Word8
sizeOfCSize (CSize (W64# Word#
sz)) = Int -> CountOf Word8
forall ty. Int -> CountOf ty
CountOf (Int# -> Int
I# (Word# -> Int#
word2Int# Word#
sz))
#endif
natValCountOf :: forall n ty proxy . (KnownNat n, NatWithinBound (CountOf ty) n) => proxy n -> CountOf ty
natValCountOf :: proxy n -> CountOf ty
natValCountOf proxy n
n = Int -> CountOf ty
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf ty) -> Int -> CountOf ty
forall a b. (a -> b) -> a -> b
$ Integer -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal proxy n
n)
natValOffset :: forall n ty proxy . (KnownNat n, NatWithinBound (Offset ty) n) => proxy n -> Offset ty
natValOffset :: proxy n -> Offset ty
natValOffset proxy n
n = Int -> Offset ty
forall ty. Int -> Offset ty
Offset (Int -> Offset ty) -> Int -> Offset ty
forall a b. (a -> b) -> a -> b
$ Integer -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal proxy n
n)
type instance NatNumMaxBound (CountOf x) = NatNumMaxBound Int
type instance NatNumMaxBound (Offset x) = NatNumMaxBound Int
type Countable ty n = NatWithinBound (CountOf ty) n
type Offsetable ty n = NatWithinBound (Offset ty) n