| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Dahdit.Fancy
Synopsis
- newtype TermBytes8 = TermBytes8 {}
- newtype TermBytes16 = TermBytes16 {}
- newtype StaticBytes (n :: Nat) = StaticBytes {}
- mkStaticBytes :: KnownNat n => Proxy n -> ShortByteString -> StaticBytes n
- normStaticBytes :: KnownNat n => StaticBytes n -> StaticBytes n
- newtype StaticSeq (n :: Nat) a = StaticSeq {
- unStaticSeq :: Seq a
- newtype StaticArray (n :: Nat) a = StaticArray {}
- newtype BoolByte = BoolByte {
- unBoolByte :: Bool
- newtype ExactBytes (n :: Nat) (s :: Symbol) = ExactBytes {
- unExactBytes :: ()
Documentation
newtype TermBytes8 Source #
Bytes terminated with null byte.
Constructors
| TermBytes8 | |
Fields | |
Instances
| IsString TermBytes8 Source # | |
Defined in Dahdit.Fancy Methods fromString :: String -> TermBytes8 # | |
| Show TermBytes8 Source # | |
Defined in Dahdit.Fancy Methods showsPrec :: Int -> TermBytes8 -> ShowS # show :: TermBytes8 -> String # showList :: [TermBytes8] -> ShowS # | |
| Binary TermBytes8 Source # | |
Defined in Dahdit.Fancy Methods byteSize :: TermBytes8 -> ByteCount Source # get :: Get TermBytes8 Source # put :: TermBytes8 -> Put Source # | |
| Default TermBytes8 Source # | |
Defined in Dahdit.Fancy Methods def :: TermBytes8 # | |
| Eq TermBytes8 Source # | |
Defined in Dahdit.Fancy | |
| Ord TermBytes8 Source # | |
Defined in Dahdit.Fancy Methods compare :: TermBytes8 -> TermBytes8 -> Ordering # (<) :: TermBytes8 -> TermBytes8 -> Bool # (<=) :: TermBytes8 -> TermBytes8 -> Bool # (>) :: TermBytes8 -> TermBytes8 -> Bool # (>=) :: TermBytes8 -> TermBytes8 -> Bool # max :: TermBytes8 -> TermBytes8 -> TermBytes8 # min :: TermBytes8 -> TermBytes8 -> TermBytes8 # | |
newtype TermBytes16 Source #
Bytes terminated with null byte. NOTE: Terminated with TWO null bytes if the string is even length to align to Word16 boundaries, as required for RIFF format, for example.
Constructors
| TermBytes16 | |
Fields | |
Instances
| IsString TermBytes16 Source # | |
Defined in Dahdit.Fancy Methods fromString :: String -> TermBytes16 # | |
| Show TermBytes16 Source # | |
Defined in Dahdit.Fancy Methods showsPrec :: Int -> TermBytes16 -> ShowS # show :: TermBytes16 -> String # showList :: [TermBytes16] -> ShowS # | |
| Binary TermBytes16 Source # | |
Defined in Dahdit.Fancy Methods byteSize :: TermBytes16 -> ByteCount Source # get :: Get TermBytes16 Source # put :: TermBytes16 -> Put Source # | |
| Default TermBytes16 Source # | |
Defined in Dahdit.Fancy Methods def :: TermBytes16 # | |
| Eq TermBytes16 Source # | |
Defined in Dahdit.Fancy | |
| Ord TermBytes16 Source # | |
Defined in Dahdit.Fancy Methods compare :: TermBytes16 -> TermBytes16 -> Ordering # (<) :: TermBytes16 -> TermBytes16 -> Bool # (<=) :: TermBytes16 -> TermBytes16 -> Bool # (>) :: TermBytes16 -> TermBytes16 -> Bool # (>=) :: TermBytes16 -> TermBytes16 -> Bool # max :: TermBytes16 -> TermBytes16 -> TermBytes16 # min :: TermBytes16 -> TermBytes16 -> TermBytes16 # | |
newtype StaticBytes (n :: Nat) Source #
A fixed-length bytestring (truncated or zero-padded on put if length does not match).
Constructors
| StaticBytes | |
Fields | |
Instances
mkStaticBytes :: KnownNat n => Proxy n -> ShortByteString -> StaticBytes n Source #
normStaticBytes :: KnownNat n => StaticBytes n -> StaticBytes n Source #
newtype StaticSeq (n :: Nat) a Source #
Constructors
| StaticSeq | |
Fields
| |
Instances
| Foldable (StaticSeq n) Source # | |
Defined in Dahdit.Fancy Methods fold :: Monoid m => StaticSeq n m -> m # foldMap :: Monoid m => (a -> m) -> StaticSeq n a -> m # foldMap' :: Monoid m => (a -> m) -> StaticSeq n a -> m # foldr :: (a -> b -> b) -> b -> StaticSeq n a -> b # foldr' :: (a -> b -> b) -> b -> StaticSeq n a -> b # foldl :: (b -> a -> b) -> b -> StaticSeq n a -> b # foldl' :: (b -> a -> b) -> b -> StaticSeq n a -> b # foldr1 :: (a -> a -> a) -> StaticSeq n a -> a # foldl1 :: (a -> a -> a) -> StaticSeq n a -> a # toList :: StaticSeq n a -> [a] # null :: StaticSeq n a -> Bool # length :: StaticSeq n a -> Int # elem :: Eq a => a -> StaticSeq n a -> Bool # maximum :: Ord a => StaticSeq n a -> a # minimum :: Ord a => StaticSeq n a -> a # | |
| Functor (StaticSeq n) Source # | |
| Show a => Show (StaticSeq n a) Source # | |
| (KnownNat n, Binary a, StaticByteSized a, Default a) => Binary (StaticSeq n a) Source # | |
| (KnownNat n, StaticByteSized a) => StaticByteSized (StaticSeq n a) Source # | |
Defined in Dahdit.Fancy Associated Types type StaticSize (StaticSeq n a) :: Nat Source # | |
| (KnownNat n, Default a) => Default (StaticSeq n a) Source # | |
Defined in Dahdit.Fancy | |
| Eq a => Eq (StaticSeq n a) Source # | |
| type StaticSize (StaticSeq n a) Source # | |
Defined in Dahdit.Fancy | |
newtype StaticArray (n :: Nat) a Source #
Constructors
| StaticArray | |
Fields | |
Instances
Constructors
| BoolByte | |
Fields
| |
Instances
newtype ExactBytes (n :: Nat) (s :: Symbol) Source #
Constructors
| ExactBytes | |
Fields
| |
Instances
| Show (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy Methods showsPrec :: Int -> ExactBytes n s -> ShowS # show :: ExactBytes n s -> String # showList :: [ExactBytes n s] -> ShowS # | |
| (SymLen n s, KnownSymbol s, KnownNat n) => Binary (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy Methods byteSize :: ExactBytes n s -> ByteCount Source # get :: Get (ExactBytes n s) Source # put :: ExactBytes n s -> Put Source # | |
| (SymLen n s, KnownSymbol s, KnownNat n) => StaticByteSized (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy Associated Types type StaticSize (ExactBytes n s) :: Nat Source # Methods staticByteSize :: Proxy (ExactBytes n s) -> ByteCount Source # | |
| Default (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy Methods def :: ExactBytes n s # | |
| Eq (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy Methods (==) :: ExactBytes n s -> ExactBytes n s -> Bool # (/=) :: ExactBytes n s -> ExactBytes n s -> Bool # | |
| type StaticSize (ExactBytes n s) Source # | |
Defined in Dahdit.Fancy | |