| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.ByteString.IsoBaseFileFormat.Boxes.BoxFields
Contents
Description
Mini EDSL for labelled box fields. The boxfields can be Scalar or
ScalarArrays.
- type U64 label = Scalar Word64 label
- type I64 label = Scalar Int64 label
- u64 :: Word64 -> U64 label
- i64 :: Int64 -> I64 label
- type U32 label = Scalar Word32 label
- type I32 label = Scalar Int32 label
- u32 :: Word32 -> U32 label
- i32 :: Int32 -> I32 label
- type U16 label = Scalar Word16 label
- type I16 label = Scalar Int16 label
- u16 :: Word16 -> U16 label
- i16 :: Int16 -> I16 label
- type U8 label = Scalar Word8 label
- type I8 label = Scalar Int8 label
- u8 :: Word8 -> U8 label
- i8 :: Int8 -> I8 label
- newtype Scalar scalartype label = Scalar {
- fromScalar :: scalartype
- relabelScalar :: Scalar t l -> Scalar t l'
- type U64Arr label size = ScalarArray label size Word64
- u64Arr :: (KnownNat size, KnownSymbol label) => [Word64] -> U64Arr label size
- type I64Arr label size = ScalarArray label size Int64
- i64Arr :: (KnownNat size, KnownSymbol label) => [Int64] -> I64Arr label size
- type U32Arr label size = ScalarArray label size Word32
- u32Arr :: (KnownNat size, KnownSymbol label) => [Word32] -> U32Arr label size
- type I32Arr label size = ScalarArray label size Int32
- i32Arr :: (KnownNat size, KnownSymbol label) => [Int32] -> I32Arr label size
- type U16Arr label size = ScalarArray label size Word16
- u16Arr :: (KnownNat size, KnownSymbol label) => [Word16] -> U16Arr label size
- type I16Arr label size = ScalarArray label size Int16
- i16Arr :: (KnownNat size, KnownSymbol label) => [Int16] -> I16Arr label size
- type U8Arr label size = ScalarArray label size Word8
- u8Arr :: (KnownNat size, KnownSymbol label) => [Word8] -> U8Arr label size
- type I8Arr label size = ScalarArray label size Int8
- i8Arr :: (KnownNat size, KnownSymbol label) => [Int8] -> I8Arr label size
- newtype ScalarArray label len o where
- ScalarArray :: Vector n o -> ScalarArray label n o
- fromList :: forall label n o. (KnownSymbol label, KnownNat n) => [o] -> ScalarArray label n o
- data Constant o v where
- data Template o v where
- templateValue :: FromTypeLit o v => Template o v -> o
- class FromTypeLit o v where
- data a :+ b = a :+ b
Scalar box fields
newtype Scalar scalartype label Source #
A numeric box field with a type level label. Note that it has a Num
instance. Use the type aliases above, e.g.
U8,I8,U16,I16,U32,I32,U64,I64 from above. Use either the
smart constructors, e.g. u8,i8,u16,i16,u32,i32,u64,i64 or the
Num instance, whereas the constructors might give a bit more safety.
Constructors
| Scalar | |
Fields
| |
Instances
| (KnownNat scalar, Num o) => FromTypeLit Nat (Scalar k o label) scalar Source # | |
| Eq scalartype => Eq (Scalar k scalartype label) Source # | |
| Num scalartype => Num (Scalar k scalartype label) Source # | |
| Ord scalartype => Ord (Scalar k scalartype label) Source # | |
| Read scalartype => Read (Scalar k scalartype label) Source # | |
| Show scalartype => Show (Scalar k scalartype label) Source # | |
| Default scalartype => Default (Scalar k scalartype label) Source # | |
| IsBoxContent (Scalar k Int64 label) Source # | |
| IsBoxContent (Scalar k Int32 label) Source # | |
| IsBoxContent (Scalar k Int16 label) Source # | |
| IsBoxContent (Scalar k Int8 label) Source # | |
| IsBoxContent (Scalar k Word64 label) Source # | |
| IsBoxContent (Scalar k Word32 label) Source # | |
| IsBoxContent (Scalar k Word16 label) Source # | |
| IsBoxContent (Scalar k Word8 label) Source # | |
relabelScalar :: Scalar t l -> Scalar t l' Source #
Relabel a scalar value, e.g. convert a Scalar U32 "foo" to a Scalar U32
"bar".
Array fields
type U64Arr label size = ScalarArray label size Word64 Source #
type I64Arr label size = ScalarArray label size Int64 Source #
type U32Arr label size = ScalarArray label size Word32 Source #
type I32Arr label size = ScalarArray label size Int32 Source #
type U16Arr label size = ScalarArray label size Word16 Source #
type I16Arr label size = ScalarArray label size Int16 Source #
type U8Arr label size = ScalarArray label size Word8 Source #
type I8Arr label size = ScalarArray label size Int8 Source #
newtype ScalarArray label len o where Source #
A box field that is an array of Scalars with a type level label. Use the
type aliases, e.g.
U8Arr,I8Arr,U16Arr,I16Arr,U32Arr,I32Arr,U64Arr,I64Arr from
above. Use the smart constructors, e.g.
u8Arr,i8Arr,u16Arr,i16Arr,u32Arr,i32Arr,u64Arr,i64Arr .
Constructors
| ScalarArray :: Vector n o -> ScalarArray label n o |
Instances
| (SingI [Nat] arr, Num o, SingKind [Nat], KnownNat len, (~) Nat len (Length Nat arr)) => FromTypeLit [Nat] (ScalarArray k label len o) arr Source # | |
| Eq o => Eq (ScalarArray k label len o) Source # | |
| Show o => Show (ScalarArray k label len o) Source # | |
| (Default o, KnownNat len) => Default (ScalarArray k label len o) Source # | |
| (Num o, IsBoxContent (Scalar k o label), KnownNat len) => IsBoxContent (ScalarArray k label len o) Source # | |
fromList :: forall label n o. (KnownSymbol label, KnownNat n) => [o] -> ScalarArray label n o Source #
Internal function
Constant fields
data Constant o v where Source #
Wrapper around a field, e.g. a Scalar or ScalarArray, with a type level
value. The wrapped content must implement FromTypeLit. To get the value of
a Constant use fromTypeLit.
Instances
| Default (Constant k k1 o v) Source # | |
| (IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Constant * k o v) Source # | |
Template Fields
data Template o v where Source #
Fields with default values that can be overriden with custom value. Like
Constant this is a wrapper around a field, e.g. a Scalar or
ScalarArray, with a type level default value. The wrapped content must
implement FromTypeLit.
Instances
| Default (Template k o v) Source # | |
| (IsBoxContent o, FromTypeLit k o v) => IsBoxContent (Template k o v) Source # | |
templateValue :: FromTypeLit o v => Template o v -> o Source #
Get a value from a Template.
Conversion from type-level numbers and lists to values
class FromTypeLit o v where Source #
Types that can be constructed from type level value representations.
Minimal complete definition
Methods
fromTypeLit :: proxy o v -> o Source #