| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Dahdit.Fancy
Synopsis
- newtype TermBytes = TermBytes {}
- 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 (s :: Symbol) = ExactBytes {
- unExactBytes :: ()
Documentation
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
| TermBytes | |
Fields | |
Instances
| IsString TermBytes Source # | |
Defined in Dahdit.Fancy Methods fromString :: String -> TermBytes # | |
| Show TermBytes Source # | |
| Binary TermBytes Source # | |
| HasCodec TermBytes Source # | |
| ByteSized TermBytes Source # | |
| Default TermBytes Source # | |
Defined in Dahdit.Fancy | |
| Eq TermBytes Source # | |
| Ord TermBytes Source # | |
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
newtype StaticArray (n :: Nat) a Source #
Constructors
| StaticArray | |
Fields | |
Instances
Constructors
| BoolByte | |
Fields
| |
newtype ExactBytes (s :: Symbol) Source #
Constructors
| ExactBytes | |
Fields
| |
Instances
| Show (ExactBytes s) Source # | |
Defined in Dahdit.Fancy Methods showsPrec :: Int -> ExactBytes s -> ShowS # show :: ExactBytes s -> String # showList :: [ExactBytes s] -> ShowS # | |
| KnownSymbol s => Binary (ExactBytes s) Source # | |
Defined in Dahdit.Fancy | |
| KnownSymbol s => HasCodec (ExactBytes s) Source # | |
Defined in Dahdit.Codec Methods codec :: Codec (ExactBytes s) Source # | |
| KnownSymbol s => ByteSized (ExactBytes s) Source # | |
Defined in Dahdit.Fancy Methods byteSize :: ExactBytes s -> ByteCount Source # | |
| KnownSymbol s => StaticByteSized (ExactBytes s) Source # | |
Defined in Dahdit.Fancy Methods staticByteSize :: Proxy (ExactBytes s) -> ByteCount Source # | |
| Default (ExactBytes s) Source # | |
Defined in Dahdit.Fancy Methods def :: ExactBytes s # | |
| Eq (ExactBytes s) Source # | |
Defined in Dahdit.Fancy | |