License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype FileSize = FileSize Word64
- newtype Offset ty = Offset Int
- type Offset8 = Offset Word8
- sentinel :: Offset ty
- offsetOfE :: CountOf Word8 -> Offset ty -> Offset8
- offsetPlusE :: Offset ty -> CountOf ty -> Offset ty
- offsetMinusE :: Offset ty -> CountOf ty -> Offset ty
- offsetRecast :: CountOf Word8 -> CountOf Word8 -> Offset ty -> Offset ty2
- offsetCast :: Proxy (a -> b) -> Offset a -> Offset b
- offsetSub :: Offset a -> Offset a -> Offset a
- offsetShiftL :: Int -> Offset ty -> Offset ty2
- offsetShiftR :: Int -> Offset ty -> Offset ty2
- sizeCast :: Proxy (a -> b) -> CountOf a -> CountOf b
- sizeLastOffset :: CountOf a -> Offset a
- sizeAsOffset :: CountOf a -> Offset a
- sizeSub :: CountOf a -> CountOf a -> CountOf a
- countOfRoundUp :: Int -> CountOf ty -> CountOf ty
- offsetAsSize :: Offset a -> CountOf a
- (+.) :: Offset ty -> Int -> Offset ty
- (.==#) :: Offset ty -> CountOf ty -> Bool
- newtype CountOf ty = CountOf Int
- sizeOfE :: CountOf Word8 -> CountOf ty -> CountOf Word8
- csizeOfOffset :: Offset8 -> CSize
- csizeOfSize :: CountOf Word8 -> CSize
- sizeOfCSSize :: CSsize -> CountOf Word8
- sizeOfCSize :: CSize -> CountOf Word8
- type Countable ty n = NatWithinBound (CountOf ty) n
- type Offsetable ty n = NatWithinBound (Offset ty) n
- natValCountOf :: forall n ty proxy. (KnownNat n, NatWithinBound (CountOf ty) n) => proxy n -> CountOf ty
- natValOffset :: forall n ty proxy. (KnownNat n, NatWithinBound (Offset ty) n) => proxy n -> Offset ty
Documentation
File size in bytes
Offset in a data structure consisting of elements of type ty
.
Int is a terrible backing type which is hard to get away from, considering that GHC/Haskell are mostly using this for offset. Trying to bring some sanity by a lightweight wrapping.
Instances
type Offset8 = Offset Word8 Source #
Offset in bytes used for memory addressing (e.g. in a vector, string, ..)
offsetSub :: Offset a -> Offset a -> Offset a Source #
subtract 2 CountOf values of the same type.
m need to be greater than n, otherwise negative count error ensue use the safer (-) version if unsure.
sizeLastOffset :: CountOf a -> Offset a Source #
sizeAsOffset :: CountOf a -> Offset a Source #
sizeSub :: CountOf a -> CountOf a -> CountOf a Source #
subtract 2 CountOf values of the same type.
m need to be greater than n, otherwise negative count error ensue use the safer (-) version if unsure.
offsetAsSize :: Offset a -> CountOf a Source #
CountOf of a data structure.
More specifically, it represents the number of elements of type ty
that fit
into the data structure.
>>>
length (fromList ['a', 'b', 'c', '🌟']) :: CountOf Char
CountOf 4
Same caveats as Offset
apply here.
Instances
csizeOfOffset :: Offset8 -> CSize Source #
type Countable ty n = NatWithinBound (CountOf ty) n Source #
type Offsetable ty n = NatWithinBound (Offset ty) n Source #
natValCountOf :: forall n ty proxy. (KnownNat n, NatWithinBound (CountOf ty) n) => proxy n -> CountOf ty Source #
natValOffset :: forall n ty proxy. (KnownNat n, NatWithinBound (Offset ty) n) => proxy n -> Offset ty Source #