antlr-haskell-0.1.0.0: A Haskell implementation of the ANTLR top-down parser generator

Copyright(c) Karl Cronburg 2018
LicenseBSD3
Maintainerkarl@cs.tufts.edu
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.ANTLR.Lex.NFA

Description

 
Synopsis

Documentation

data Edge s Source #

NFA edges can be labeled with either a symbol in symbol alphabet s, or an epsilon.

Constructors

Edge s 
NFAEpsilon 
Instances
Eq s => Eq (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

Methods

(==) :: Edge s -> Edge s -> Bool #

(/=) :: Edge s -> Edge s -> Bool #

Ord s => Ord (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

Methods

compare :: Edge s -> Edge s -> Ordering #

(<) :: Edge s -> Edge s -> Bool #

(<=) :: Edge s -> Edge s -> Bool #

(>) :: Edge s -> Edge s -> Bool #

(>=) :: Edge s -> Edge s -> Bool #

max :: Edge s -> Edge s -> Edge s #

min :: Edge s -> Edge s -> Edge s #

Show s => Show (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

Methods

showsPrec :: Int -> Edge s -> ShowS #

show :: Edge s -> String #

showList :: [Edge s] -> ShowS #

Generic (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

Associated Types

type Rep (Edge s) :: Type -> Type #

Methods

from :: Edge s -> Rep (Edge s) x #

to :: Rep (Edge s) x -> Edge s #

Hashable s => Hashable (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

Methods

hashWithSalt :: Int -> Edge s -> Int #

hash :: Edge s -> Int #

type Rep (Edge s) Source # 
Instance details

Defined in Text.ANTLR.Lex.NFA

type Rep (Edge s) = D1 (MetaData "Edge" "Text.ANTLR.Lex.NFA" "antlr-haskell-0.1.0.0-I1YLZdM1Y3a3syLrgVdT7Y" False) (C1 (MetaCons "Edge" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: C1 (MetaCons "NFAEpsilon" PrefixI False) (U1 :: Type -> Type))

isEdge :: Edge s -> Bool Source #

Is this an edge (not an epsilon)?

type NFA s i = Automata (Edge s) s i Source #

An NFA is an automata with edges Edge s and nodes i.

type State i = i Source #

NFA states

type DFAState i = Config (State i) Source #

DFA states as constructed from an NFA is a set (config) of NFA states.

epsClosure :: (Ord i, Hashable i, Hashable s, Eq s) => Automata (Edge s) s i -> Config i -> Config i Source #

Epsilon closure of an NFA is a closure where we can traverse epsilons.

nfa2dfa_slow :: forall s i. (Hashable s, Eq s, Hashable i, Eq i, Ord i) => NFA s i -> DFA s (Set (State i)) Source #

Subset construction algorithm for constructing a DFA from an NFA.

nfa2dfa :: forall s i. (Hashable s, Eq s, Hashable i, Eq i, Ord i) => NFA s i -> DFA s (Set (State i)) Source #

Subset construction but where we compress our sets of transitions along the way.

allStates :: forall s i. (Hashable i, Eq i) => Set (Transition (Edge s) i) -> Set (State i) Source #

Compute all the states statically used in a particular set of transitions.

list2nfa :: forall s i. (Hashable i, Eq i, Hashable s, Eq s) => [Transition (Edge s) i] -> NFA s i Source #

Converts the given list of transitions into a complete NFA / Automata structure, assuming two things:

The first node of the first edge is the start state
The last  node of the last  edge is the (only) final state

shiftAllStates :: forall s i. (Hashable i, Eq i, Ord i, Hashable s, Eq s) => (i -> Int) -> (Int -> i) -> NFA s i -> NFA s i -> NFA s i Source #

Rename the states in the second NFA such that they start at the index one greater than the maximum index of the first NFA.

nfaUnion :: forall s i. (Ord i, Hashable i, Eq i, Hashable s, Eq s) => (i -> Int) -> (Int -> i) -> NFA s i -> NFA s i -> NFA s i Source #

Take the union of two NFAs, renaming states according to shiftAllStates.

nfaConcat :: forall s i. (Hashable i, Eq i, Ord i, Hashable s, Eq s) => (i -> Int) -> (Int -> i) -> NFA s i -> NFA s i -> NFA s i Source #

Concatenate two NFAs, renaming states in the second NFA according to shiftAllStates.

nfaKleene :: forall s i. (Ord i, Hashable i, Eq i, Hashable s, Eq s) => (i -> Int) -> (Int -> i) -> NFA s i -> NFA s i Source #

Take the Kleene-star of an NFA, adding epsilons as needed.