binary-generic-combinators-0.4.2.0: Combinators and utilities to make Generic-based deriving of Binary easier and more expressive
Safe HaskellSafe
LanguageHaskell2010

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

Documentation

newtype Many a Source #

Zero or more elements of a, parsing as long as the parser for a succeeds.

Many Word8 will consume all your input!

Constructors

Many 

Fields

Instances

Instances details
Functor Many Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

fmap :: (a -> b) -> Many a -> Many b #

(<$) :: a -> Many b -> Many a #

Foldable Many Source # 
Instance details

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 #

toList :: Many a -> [a] #

null :: Many a -> Bool #

length :: Many a -> Int #

elem :: Eq a => a -> Many a -> Bool #

maximum :: Ord a => Many a -> a #

minimum :: Ord a => Many a -> a #

sum :: Num a => Many a -> a #

product :: Num a => Many a -> a #

Traversable Many Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

traverse :: Applicative f => (a -> f b) -> Many a -> f (Many b) #

sequenceA :: Applicative f => Many (f a) -> f (Many a) #

mapM :: Monad m => (a -> m b) -> Many a -> m (Many b) #

sequence :: Monad m => Many (m a) -> m (Many a) #

Eq a => Eq (Many a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: Many a -> Many a -> Bool #

(/=) :: Many a -> Many a -> Bool #

Ord a => Ord (Many a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

compare :: Many a -> Many a -> Ordering #

(<) :: Many a -> Many a -> Bool #

(<=) :: Many a -> Many a -> Bool #

(>) :: Many a -> Many a -> Bool #

(>=) :: Many a -> Many a -> Bool #

max :: Many a -> Many a -> Many a #

min :: Many a -> Many a -> Many a #

Show a => Show (Many a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> Many a -> ShowS #

show :: Many a -> String #

showList :: [Many a] -> ShowS #

Arbitrary a => Arbitrary (Many a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (Many a) #

shrink :: Many a -> [Many a] #

Binary a => Binary (Many a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: Many a -> Put #

get :: Get (Many a) #

putList :: [Many a] -> Put #

newtype Some 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!

Constructors

Some 

Fields

Instances

Instances details
Functor Some Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

fmap :: (a -> b) -> Some a -> Some b #

(<$) :: a -> Some b -> Some a #

Foldable Some Source # 
Instance details

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 #

toList :: Some a -> [a] #

null :: Some a -> Bool #

length :: Some a -> Int #

elem :: Eq a => a -> Some a -> Bool #

maximum :: Ord a => Some a -> a #

minimum :: Ord a => Some a -> a #

sum :: Num a => Some a -> a #

product :: Num a => Some a -> a #

Traversable Some Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

traverse :: Applicative f => (a -> f b) -> Some a -> f (Some b) #

sequenceA :: Applicative f => Some (f a) -> f (Some a) #

mapM :: Monad m => (a -> m b) -> Some a -> m (Some b) #

sequence :: Monad m => Some (m a) -> m (Some a) #

Eq a => Eq (Some a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: Some a -> Some a -> Bool #

(/=) :: Some a -> Some a -> Bool #

Ord a => Ord (Some a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

compare :: Some a -> Some a -> Ordering #

(<) :: Some a -> Some a -> Bool #

(<=) :: Some a -> Some a -> Bool #

(>) :: Some a -> Some a -> Bool #

(>=) :: Some a -> Some a -> Bool #

max :: Some a -> Some a -> Some a #

min :: Some a -> Some a -> Some a #

Show a => Show (Some a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> Some a -> ShowS #

show :: Some a -> String #

showList :: [Some a] -> ShowS #

Arbitrary a => Arbitrary (Some a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (Some a) #

shrink :: Some a -> [Some a] #

Binary a => Binary (Some a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: Some a -> Put #

get :: Get (Some a) #

putList :: [Some a] -> Put #

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

Instances details
Functor (CountedBy ty) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

fmap :: (a -> b) -> CountedBy ty a -> CountedBy ty b #

(<$) :: a -> CountedBy ty b -> CountedBy ty a #

Foldable (CountedBy ty) Source # 
Instance details

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 #

sum :: Num a => CountedBy ty a -> a #

product :: Num a => CountedBy ty a -> a #

Traversable (CountedBy ty) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

traverse :: Applicative f => (a -> f b) -> CountedBy ty a -> f (CountedBy ty b) #

sequenceA :: Applicative f => CountedBy ty (f a) -> f (CountedBy ty a) #

mapM :: Monad m => (a -> m b) -> CountedBy ty a -> m (CountedBy ty b) #

sequence :: Monad m => CountedBy ty (m a) -> m (CountedBy ty a) #

Eq a => Eq (CountedBy ty a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: CountedBy ty a -> CountedBy ty a -> Bool #

(/=) :: CountedBy ty a -> CountedBy ty a -> Bool #

Ord a => Ord (CountedBy ty a) Source # 
Instance details

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 #

max :: CountedBy ty a -> CountedBy ty a -> CountedBy ty a #

min :: CountedBy ty a -> CountedBy ty a -> CountedBy ty a #

Show a => Show (CountedBy ty a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> CountedBy ty a -> ShowS #

show :: CountedBy ty a -> String #

showList :: [CountedBy ty a] -> ShowS #

Arbitrary a => Arbitrary (CountedBy ty a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (CountedBy ty a) #

shrink :: CountedBy ty a -> [CountedBy ty a] #

(Integral ty, Binary ty, Binary a) => Binary (CountedBy ty a) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: CountedBy ty a -> Put #

get :: Get (CountedBy ty a) #

putList :: [CountedBy ty a] -> Put #

data SkipCount ty (n :: Nat) Source #

Parse out and skip n elements of type ty.

Serializing this type produces no bytes.

Constructors

SkipCount 

Instances

Instances details
Eq (SkipCount ty n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: SkipCount ty n -> SkipCount ty n -> Bool #

(/=) :: SkipCount ty n -> SkipCount ty n -> Bool #

Ord (SkipCount ty n) Source # 
Instance details

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 #

max :: SkipCount ty n -> SkipCount ty n -> SkipCount ty n #

min :: SkipCount ty n -> SkipCount ty n -> SkipCount ty n #

Show (SkipCount ty n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> SkipCount ty n -> ShowS #

show :: SkipCount ty n -> String #

showList :: [SkipCount ty n] -> ShowS #

Arbitrary (SkipCount ty n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (SkipCount ty n) #

shrink :: SkipCount ty n -> [SkipCount ty n] #

(Num ty, Binary ty, KnownNat n) => Binary (SkipCount ty n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: SkipCount ty n -> Put #

get :: Get (SkipCount ty n) #

putList :: [SkipCount ty n] -> Put #

data SkipByte (n :: Nat) Source #

Skip any number of bytes with value n.

Serializing this type produces no bytes.

Constructors

SkipByte 

Instances

Instances details
Eq (SkipByte n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: SkipByte n -> SkipByte n -> Bool #

(/=) :: SkipByte n -> SkipByte n -> Bool #

Ord (SkipByte n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

compare :: SkipByte n -> SkipByte n -> Ordering #

(<) :: SkipByte n -> SkipByte n -> Bool #

(<=) :: SkipByte n -> SkipByte n -> Bool #

(>) :: SkipByte n -> SkipByte n -> Bool #

(>=) :: SkipByte n -> SkipByte n -> Bool #

max :: SkipByte n -> SkipByte n -> SkipByte n #

min :: SkipByte n -> SkipByte n -> SkipByte n #

Show (SkipByte n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> SkipByte n -> ShowS #

show :: SkipByte n -> String #

showList :: [SkipByte n] -> ShowS #

Arbitrary (SkipByte n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (SkipByte n) #

shrink :: SkipByte n -> [SkipByte n] #

KnownNat n => Binary (SkipByte n) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: SkipByte n -> Put #

get :: Get (SkipByte n) #

putList :: [SkipByte n] -> Put #

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

Instances details
Eq (MatchBytes s ns) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

(==) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

(/=) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

Ord (MatchBytes s ns) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

compare :: MatchBytes s ns -> MatchBytes s ns -> Ordering #

(<) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

(<=) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

(>) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

(>=) :: MatchBytes s ns -> MatchBytes s ns -> Bool #

max :: MatchBytes s ns -> MatchBytes s ns -> MatchBytes s ns #

min :: MatchBytes s ns -> MatchBytes s ns -> MatchBytes s ns #

Show (MatchBytes ctx ns) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

showsPrec :: Int -> MatchBytes ctx ns -> ShowS #

show :: MatchBytes ctx ns -> String #

showList :: [MatchBytes ctx ns] -> ShowS #

MatchBytesSing ctx ns => Arbitrary (MatchBytes ctx ns) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

arbitrary :: Gen (MatchBytes ctx ns) #

shrink :: MatchBytes ctx ns -> [MatchBytes ctx ns] #

(KnownSymbol ctx, KnownNat n, Binary (MatchBytes ctx ns)) => Binary (MatchBytes ctx (n ': ns)) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: MatchBytes ctx (n ': ns) -> Put #

get :: Get (MatchBytes ctx (n ': ns)) #

putList :: [MatchBytes ctx (n ': ns)] -> Put #

Binary (MatchBytes ctx ('[] :: [Nat])) Source # 
Instance details

Defined in Data.Binary.Combinators

Methods

put :: MatchBytes ctx '[] -> Put #

get :: Get (MatchBytes ctx '[]) #

putList :: [MatchBytes ctx '[]] -> Put #

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.