| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Binary.Machine
Synopsis
- processGet :: Get a -> Plan (Stack ByteString) (Either DecodingError a) ()
- processGetL :: Get a -> Plan (Stack ByteString) (Either DecodingError (ByteOffset, a)) ()
- streamGet :: Get a -> Process ByteString (Either DecodingError a)
- streamGetL :: Get a -> Process ByteString (Either DecodingError (ByteOffset, a))
- processPut :: Monad m => (a -> Put) -> ProcessT m a ByteString
- data DecodingError = DecodingError {
- deConsumed :: !ByteOffset
- deMessage :: !String
Get
processGet :: Get a -> Plan (Stack ByteString) (Either DecodingError a) () Source #
Construct a Plan that run a Get until it fails or it return a parsed result.
This plan automatically manages the pushback of unused input.
You can use this function to construct a machine and run a Get on the
provided input.
With stack you can convert the created machine to a normal machine
-- construct the machine myMachine ::Machine(StackByteString) (Either DecodingError Word8) myMachine =construct$processGetgetWord8-- run the machine run $stack(source["abc", "d", "efgh"]) myMachine
You can combine machines created in this way with the facilities provided by the machines package.
--run m2 after m1
myMachine = m1 <> m2
where
m1 = construct $ processGet (getByteString 5)
m2 = construct $ processGet (getByteString 1)
run $ stack (source ["abc", "d", "efgh"]) myMachine
> [Right "abcde",Right "f"]
processGetL :: Get a -> Plan (Stack ByteString) (Either DecodingError (ByteOffset, a)) () Source #
Same as processGet with additional information about the number
of bytes consumed by the Get
streamGet :: Get a -> Process ByteString (Either DecodingError a) Source #
Run a Get multiple times and stream its results
run $ source ["abc", "d", "efgh"] ~> streamGet (getByteString 2) > [Right "ab",Right "cd",Right "ef",Right "gh"]
streamGetL :: Get a -> Process ByteString (Either DecodingError (ByteOffset, a)) Source #
Put
processPut :: Monad m => (a -> Put) -> ProcessT m a ByteString Source #
Encode evrery input object with a Put
Types
data DecodingError Source #
A Get decoding error.
Constructors
| DecodingError | |
Fields
| |
Instances
| Eq DecodingError Source # | |
Defined in Data.Binary.Machine Methods (==) :: DecodingError -> DecodingError -> Bool # (/=) :: DecodingError -> DecodingError -> Bool # | |
| Read DecodingError Source # | |
Defined in Data.Binary.Machine Methods readsPrec :: Int -> ReadS DecodingError # readList :: ReadS [DecodingError] # | |
| Show DecodingError Source # | |
Defined in Data.Binary.Machine Methods showsPrec :: Int -> DecodingError -> ShowS # show :: DecodingError -> String # showList :: [DecodingError] -> ShowS # | |