| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Binary.Combinators
Description
This module defines a bunch of types to be used as fields of records with Generic-based deriving of Binary instances.
For example:
data MyFileFormat = MyFileFormat
{ header :: MatchBytes "my format header" '[ 0xd3, 0x4d, 0xf0, 0x0d ]
, slack :: SkipByte 0xff
, reserved :: SkipCount Word8 4
, subElements :: Some MyElement
} deriving (Generic, Binary)
Synopsis
- newtype Many a = Many {
- getMany :: [a]
- newtype Some a = Some {
- getSome :: [a]
- newtype CountedBy ty a = CountedBy {
- getCounted :: [a]
- data SkipCount ty (n :: Nat) = SkipCount
- data SkipByte (n :: Nat) = SkipByte
- data MatchBytes (ctx :: Symbol) (bytes :: [Nat]) :: Type
- matchBytes :: MatchBytesSing ctx ns => MatchBytes ctx ns
- type MatchByte ctx byte = MatchBytes ctx '[byte]
Documentation
Zero or more elements of a, parsing as long as the parser for a succeeds.
Many Word8 will consume all your input!
Instances
| Functor Many Source # | |
| Foldable Many Source # | |
Defined in Data.Binary.Combinators Methods fold :: Monoid m => Many m -> m # foldMap :: Monoid m => (a -> m) -> Many a -> m # foldMap' :: Monoid m => (a -> m) -> Many a -> m # foldr :: (a -> b -> b) -> b -> Many a -> b # foldr' :: (a -> b -> b) -> b -> Many a -> b # foldl :: (b -> a -> b) -> b -> Many a -> b # foldl' :: (b -> a -> b) -> b -> Many a -> b # foldr1 :: (a -> a -> a) -> Many a -> a # foldl1 :: (a -> a -> a) -> Many a -> a # elem :: Eq a => a -> Many a -> Bool # maximum :: Ord a => Many a -> a # | |
| Traversable Many Source # | |
| Eq a => Eq (Many a) Source # | |
| Ord a => Ord (Many a) Source # | |
| Show a => Show (Many a) Source # | |
| Arbitrary a => Arbitrary (Many a) Source # | |
| Binary a => Binary (Many a) Source # | |
One or more elements of a, parsing as long as the parser for a succeeds.
Some Word8 will consume all your non-empty input!
Instances
| Functor Some Source # | |
| Foldable Some Source # | |
Defined in Data.Binary.Combinators Methods fold :: Monoid m => Some m -> m # foldMap :: Monoid m => (a -> m) -> Some a -> m # foldMap' :: Monoid m => (a -> m) -> Some a -> m # foldr :: (a -> b -> b) -> b -> Some a -> b # foldr' :: (a -> b -> b) -> b -> Some a -> b # foldl :: (b -> a -> b) -> b -> Some a -> b # foldl' :: (b -> a -> b) -> b -> Some a -> b # foldr1 :: (a -> a -> a) -> Some a -> a # foldl1 :: (a -> a -> a) -> Some a -> a # elem :: Eq a => a -> Some a -> Bool # maximum :: Ord a => Some a -> a # | |
| Traversable Some Source # | |
| Eq a => Eq (Some a) Source # | |
| Ord a => Ord (Some a) Source # | |
| Show a => Show (Some a) Source # | |
| Arbitrary a => Arbitrary (Some a) Source # | |
| Binary a => Binary (Some a) Source # | |
newtype CountedBy ty a Source #
First, parse the elements count as type ty. Then, parse exactly as many elements of type a.
Constructors
| CountedBy | |
Fields
| |
Instances
| Functor (CountedBy ty) Source # | |
| Foldable (CountedBy ty) Source # | |
Defined in Data.Binary.Combinators Methods fold :: Monoid m => CountedBy ty m -> m # foldMap :: Monoid m => (a -> m) -> CountedBy ty a -> m # foldMap' :: Monoid m => (a -> m) -> CountedBy ty a -> m # foldr :: (a -> b -> b) -> b -> CountedBy ty a -> b # foldr' :: (a -> b -> b) -> b -> CountedBy ty a -> b # foldl :: (b -> a -> b) -> b -> CountedBy ty a -> b # foldl' :: (b -> a -> b) -> b -> CountedBy ty a -> b # foldr1 :: (a -> a -> a) -> CountedBy ty a -> a # foldl1 :: (a -> a -> a) -> CountedBy ty a -> a # toList :: CountedBy ty a -> [a] # null :: CountedBy ty a -> Bool # length :: CountedBy ty a -> Int # elem :: Eq a => a -> CountedBy ty a -> Bool # maximum :: Ord a => CountedBy ty a -> a # minimum :: Ord a => CountedBy ty a -> a # | |
| Traversable (CountedBy ty) Source # | |
Defined in Data.Binary.Combinators | |
| Eq a => Eq (CountedBy ty a) Source # | |
| Ord a => Ord (CountedBy ty a) Source # | |
Defined in Data.Binary.Combinators Methods compare :: CountedBy ty a -> CountedBy ty a -> Ordering # (<) :: CountedBy ty a -> CountedBy ty a -> Bool # (<=) :: CountedBy ty a -> CountedBy ty a -> Bool # (>) :: CountedBy ty a -> CountedBy ty a -> Bool # (>=) :: CountedBy ty a -> CountedBy ty a -> Bool # | |
| Show a => Show (CountedBy ty a) Source # | |
| Arbitrary a => Arbitrary (CountedBy ty a) Source # | |
| (Integral ty, Binary ty, Binary a) => Binary (CountedBy ty a) Source # | |
data SkipCount ty (n :: Nat) Source #
Parse out and skip n elements of type ty.
Serializing this type produces no bytes.
Constructors
| SkipCount |
Instances
| Eq (SkipCount ty n) Source # | |
| Ord (SkipCount ty n) Source # | |
Defined in Data.Binary.Combinators Methods compare :: SkipCount ty n -> SkipCount ty n -> Ordering # (<) :: SkipCount ty n -> SkipCount ty n -> Bool # (<=) :: SkipCount ty n -> SkipCount ty n -> Bool # (>) :: SkipCount ty n -> SkipCount ty n -> Bool # (>=) :: SkipCount ty n -> SkipCount ty n -> Bool # | |
| Show (SkipCount ty n) Source # | |
| Arbitrary (SkipCount ty n) Source # | |
| (Num ty, Binary ty, KnownNat n) => Binary (SkipCount ty n) Source # | |
data SkipByte (n :: Nat) Source #
Skip any number of bytes with value n.
Serializing this type produces no bytes.
Constructors
| SkipByte |
Instances
| Eq (SkipByte n) Source # | |
| Ord (SkipByte n) Source # | |
Defined in Data.Binary.Combinators | |
| Show (SkipByte n) Source # | |
| Arbitrary (SkipByte n) Source # | |
| KnownNat n => Binary (SkipByte n) Source # | |
data MatchBytes (ctx :: Symbol) (bytes :: [Nat]) :: Type Source #
MatchBytes str bytes ensures that the subsequent bytes in the input stream are the same as bytes.
str can be used to denote the context in which MatchBytes is used for better parse failure messages.
For example, MatchBytes "my format header" '[ 0xd3, 0x4d, 0xf0, 0x0d ] consumes four bytes from the input stream
if they are equal to [ 0xd3, 0x4d, 0xf0, 0x0d ] respectively, or fails otherwise.
Serializing this type produces the bytes.
Instances
matchBytes :: MatchBytesSing ctx ns => MatchBytes ctx ns Source #
Produce the (singleton) value of type MatchBytes ctx ns.
type MatchByte ctx byte = MatchBytes ctx '[byte] Source #
An alias for MatchBytes when you only need to match a single byte.