Earley-0.11.0.0: Parsing all context-free grammars using Earley's algorithm.

Safe HaskellNone
LanguageHaskell2010

Text.Earley.Internal

Contents

Description

This module exposes the internals of the package: its API may change independently of the PVP-compliant version number.

Synopsis

Concrete rules and productions

data Rule s r e t a Source

The concrete rule type that the parser uses

Constructors

Rule 

Fields

ruleProd :: ProdR s r e t a
 
ruleConts :: !(STRef s (STRef s [Cont s r e t a r]))
 
ruleNulls :: !(Results s a)
 

mkRule :: ProdR s r e t a -> ST s (Rule s r e t a) Source

prodNulls :: ProdR s r e t a -> Results s a Source

removeNulls :: ProdR s r e t a -> ProdR s r e t a Source

Remove (some) nulls from a production

type ProdR s r e t a = Prod (Rule s r) e t a Source

resetConts :: Rule s r e t a -> ST s () Source

Delayed results

newtype Results s a Source

Constructors

Results 

Fields

unResults :: ST s [a]
 

lazyResults :: ST s [a] -> ST s (Results s a) Source

States and continuations

data BirthPos Source

Constructors

Previous 
Current 

Instances

data State s r e t a where Source

An Earley state with result type a.

Constructors

State :: !(ProdR s r e t a) -> !(a -> Results s b) -> !BirthPos -> !(Conts s r e t b c) -> State s r e t c 
Final :: !(Results s a) -> State s r e t a 

data Cont s r e t a b where Source

A continuation accepting an a and producing a b.

Constructors

Cont :: !(a -> Results s b) -> !(ProdR s r e t (b -> c)) -> !(c -> Results s d) -> !(Conts s r e t d e') -> Cont s r e t a e' 
FinalCont :: (a -> Results s c) -> Cont s r e t a c 

data Conts s r e t a c Source

Constructors

Conts 

Fields

conts :: !(STRef s [Cont s r e t a c])
 
contsArgs :: !(STRef s (Maybe (STRef s (Results s a))))
 

newConts :: STRef s [Cont s r e t a c] -> ST s (Conts s r e t a c) Source

contraMapCont :: (b -> Results s a) -> Cont s r e t a c -> Cont s r e t b c Source

contToState :: BirthPos -> Results s a -> Cont s r e t a c -> State s r e t c Source

simplifyCont :: Conts s r e t b a -> ST s [Cont s r e t b a] Source

Strings of non-ambiguous continuations can be optimised by removing indirections.

Grammars

initialState :: ProdR s a e t a -> ST s (State s a e t a) Source

Given a grammar, construct an initial state.

Parsing

data Report e i Source

A parsing report, which contains fields that are useful for presenting errors to the user if a parse is deemed a failure. Note however that we get a report even when we successfully parse something.

Constructors

Report 

Fields

position :: Int

The final position in the input (0-based) that the parser reached.

expected :: [e]

The named productions processed at the final position.

unconsumed :: i

The part of the input string that was not consumed, which may be empty.

Instances

(Eq e, Eq i) => Eq (Report e i) Source 
(Ord e, Ord i) => Ord (Report e i) Source 
(Read e, Read i) => Read (Report e i) Source 
(Show e, Show i) => Show (Report e i) Source 

data Result s e i a Source

The result of a parse.

Constructors

Ended (Report e i)

The parser ended.

Parsed (ST s [a]) Int i (ST s (Result s e i a))

The parser parsed a number of as. These are given as a computation, ST s [a] that constructs the as when run. We can thus save some work by ignoring this computation if we do not care about the results. The Int is the position in the input where these results were obtained, the i the rest of the input, and the last component is the continuation.

Instances

safeHead :: ListLike i t => i -> Maybe t Source

data ParseEnv s e i t a Source

Constructors

ParseEnv 

Fields

results :: ![ST s [a]]

Results ready to be reported (when this position has been processed)

next :: ![State s a e t a]

States to process at the next position

reset :: !(ST s ())

Computation that resets the continuation refs of productions

names :: ![e]

Named productions encountered at this position

curPos :: !Int

The current position in the input string

input :: !i

The input string

emptyParseEnv :: i -> ParseEnv s e i t a Source

parse Source

Arguments

:: ListLike i t 
=> [State s a e t a]

States to process at this position

-> ParseEnv s e i t a 
-> ST s (Result s e i a) 

The internal parsing routine

parser :: ListLike i t => (forall r. Grammar r (Prod r e t a)) -> ST s (i -> ST s (Result s e i a)) Source

Create a parser from the given grammar.

allParses :: (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([(a, Int)], Report e i) Source

Return all parses from the result of a given parser. The result may contain partial parses. The Ints are the position at which a result was produced.

fullParses :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([a], Report e i) Source

Return all parses that reached the end of the input from the result of a given parser.

report :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> Report e i Source

See e.g. how far the parser is able to parse the input string before it fails. This can be much faster than getting the parse results for highly ambiguous grammars.