crypton-asn1-parse-0.10.0: A monadic parser combinator for a ASN.1 stream.
Copyright(c) 2010-2013 Vincent Hanquez <vincent@snarc.org>
LicenseBSD-style
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell98

Data.ASN1.Parse

Description

A monadic parser combinator for a stream of ASN.1 items.

Synopsis

Documentation

data ParseASN1 a Source #

Type representing a parser combinator for a stream of ASN.1 items.

Instances

Instances details
MonadFail ParseASN1 Source # 
Instance details

Defined in Data.ASN1.Parse

Methods

fail :: String -> ParseASN1 a #

Alternative ParseASN1 Source # 
Instance details

Defined in Data.ASN1.Parse

Methods

empty :: ParseASN1 a #

(<|>) :: ParseASN1 a -> ParseASN1 a -> ParseASN1 a #

some :: ParseASN1 a -> ParseASN1 [a] #

many :: ParseASN1 a -> ParseASN1 [a] #

Applicative ParseASN1 Source # 
Instance details

Defined in Data.ASN1.Parse

Methods

pure :: a -> ParseASN1 a #

(<*>) :: ParseASN1 (a -> b) -> ParseASN1 a -> ParseASN1 b #

liftA2 :: (a -> b -> c) -> ParseASN1 a -> ParseASN1 b -> ParseASN1 c #

(*>) :: ParseASN1 a -> ParseASN1 b -> ParseASN1 b #

(<*) :: ParseASN1 a -> ParseASN1 b -> ParseASN1 a #

Functor ParseASN1 Source # 
Instance details

Defined in Data.ASN1.Parse

Methods

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

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

Monad ParseASN1 Source # 
Instance details

Defined in Data.ASN1.Parse

Methods

(>>=) :: ParseASN1 a -> (a -> ParseASN1 b) -> ParseASN1 b #

(>>) :: ParseASN1 a -> ParseASN1 b -> ParseASN1 b #

return :: a -> ParseASN1 a #

Run ParseASN1

runParseASN1State :: ParseASN1 a -> [ASN1] -> Either String (a, [ASN1]) Source #

Run the given parse monad over the given list of ASN.1 items. Returns the result and a list of the ASN.1 items remaining in the stream (if successful).

runParseASN1 :: ParseASN1 a -> [ASN1] -> Either String a Source #

Run the given parse monad over the given list of ASN.1 items and returns the result (if successful).

If ASN.1 items remain in the stream after doing so, returns an error.

throwParseError Source #

Arguments

:: String

Error message.

-> ParseASN1 a 

Throw a parse error.

Combinators

onNextContainer :: ASN1ConstructionType -> ParseASN1 a -> ParseASN1 a Source #

Run the parse monad over the elements of the next container of specified type. Throws an error if there is no next container of the specified type.

onNextContainerMaybe :: ASN1ConstructionType -> ParseASN1 a -> ParseASN1 (Maybe a) Source #

As for onNextContainer, except that it does not throw an error if there is no next container of the specified type.

getNextContainer :: ASN1ConstructionType -> ParseASN1 [ASN1] Source #

Get the next container of the specified type and return a list of all its ASN.1 elements. Throws a parse error if there is no next container of the specified type.

getNextContainerMaybe :: ASN1ConstructionType -> ParseASN1 (Maybe [ASN1]) Source #

As for getNextContainer, except that it does not throw an error if there is no next container of the specified type.

getNext :: ParseASN1 ASN1 Source #

Get the next ASN.1 item in a stream of ASN.1 items.

getNextMaybe :: (ASN1 -> Maybe a) -> ParseASN1 (Maybe a) Source #

Applies the given function to the next ASN.1 item in a stream of ASN.1 items, if there is one.

hasNext :: ParseASN1 Bool Source #

Are there any more ASN.1 items in the stream?

getObject :: ASN1Object a => ParseASN1 a Source #

Get the object from the next ASN.1 item in a stream of ASN.1 items. Throws a parse error if the object cannot be obtained from the item.

getMany :: ParseASN1 a -> ParseASN1 [a] Source #

Get many items from the stream until there are none left.