| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Dahdit.Sizes
Synopsis
- newtype ByteCount = ByteCount {
- unByteCount :: Int
- newtype ElemCount = ElemCount {
- unElemCount :: Int
- class KnownNat (StaticSize a) => StaticByteSized a where
- type StaticSize a :: Nat
- staticByteSize :: Proxy a -> ByteCount
- staticByteSizeFoldable :: (Foldable f, StaticByteSized a) => f a -> ByteCount
- byteSizeViaStatic :: StaticByteSized a => a -> ByteCount
- primByteSize :: Prim a => a -> ByteCount
- primByteSizeOf :: forall a. Prim a => Proxy a -> ByteCount
Documentation
Constructors
| ByteCount | |
Fields
| |
Instances
| Bounded ByteCount Source # | |
| Enum ByteCount Source # | |
Defined in Dahdit.Sizes Methods succ :: ByteCount -> ByteCount # pred :: ByteCount -> ByteCount # fromEnum :: ByteCount -> Int # enumFrom :: ByteCount -> [ByteCount] # enumFromThen :: ByteCount -> ByteCount -> [ByteCount] # enumFromTo :: ByteCount -> ByteCount -> [ByteCount] # enumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount] # | |
| Num ByteCount Source # | |
| Integral ByteCount Source # | |
Defined in Dahdit.Sizes Methods quot :: ByteCount -> ByteCount -> ByteCount # rem :: ByteCount -> ByteCount -> ByteCount # div :: ByteCount -> ByteCount -> ByteCount # mod :: ByteCount -> ByteCount -> ByteCount # quotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount) # divMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount) # | |
| Real ByteCount Source # | |
Defined in Dahdit.Sizes Methods toRational :: ByteCount -> Rational # | |
| Show ByteCount Source # | |
| Default ByteCount Source # | |
Defined in Dahdit.Sizes | |
| Eq ByteCount Source # | |
| Ord ByteCount Source # | |
Constructors
| ElemCount | |
Fields
| |
Instances
| Bounded ElemCount Source # | |
| Enum ElemCount Source # | |
Defined in Dahdit.Sizes Methods succ :: ElemCount -> ElemCount # pred :: ElemCount -> ElemCount # fromEnum :: ElemCount -> Int # enumFrom :: ElemCount -> [ElemCount] # enumFromThen :: ElemCount -> ElemCount -> [ElemCount] # enumFromTo :: ElemCount -> ElemCount -> [ElemCount] # enumFromThenTo :: ElemCount -> ElemCount -> ElemCount -> [ElemCount] # | |
| Num ElemCount Source # | |
| Integral ElemCount Source # | |
Defined in Dahdit.Sizes Methods quot :: ElemCount -> ElemCount -> ElemCount # rem :: ElemCount -> ElemCount -> ElemCount # div :: ElemCount -> ElemCount -> ElemCount # mod :: ElemCount -> ElemCount -> ElemCount # quotRem :: ElemCount -> ElemCount -> (ElemCount, ElemCount) # divMod :: ElemCount -> ElemCount -> (ElemCount, ElemCount) # | |
| Real ElemCount Source # | |
Defined in Dahdit.Sizes Methods toRational :: ElemCount -> Rational # | |
| Show ElemCount Source # | |
| Default ElemCount Source # | |
Defined in Dahdit.Sizes | |
| Eq ElemCount Source # | |
| Ord ElemCount Source # | |
class KnownNat (StaticSize a) => StaticByteSized a where Source #
For types with Prim instances, this will match sizeOfType.
Minimal complete definition
Nothing
Associated Types
type StaticSize a :: Nat Source #
Methods
staticByteSize :: Proxy a -> ByteCount Source #
Instances
staticByteSizeFoldable :: (Foldable f, StaticByteSized a) => f a -> ByteCount Source #
byteSizeViaStatic :: StaticByteSized a => a -> ByteCount Source #
primByteSize :: Prim a => a -> ByteCount Source #