Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Edge s
- = Edge s
- | NFAEpsilon
- isEdge :: Edge s -> Bool
- type NFA s i = Automata (Edge s) s i
- type State i = i
- type DFAState i = Config (State i)
- epsClosure :: (Ord i, Hashable i, Hashable s, Eq s) => Automata (Edge s) s i -> Config i -> Config i
- nfa2dfa_slow :: forall s i. (Hashable s, Eq s, Hashable i, Eq i, Ord i) => NFA s i -> DFA s (Set (State i))
- nfa2dfa :: forall s i. (Hashable s, Eq s, Hashable i, Eq i, Ord i) => NFA s i -> DFA s (Set (State i))
- allStates :: forall s i. (Hashable i, Eq i) => Set (Transition (Edge s) i) -> Set (State i)
- list2nfa :: forall s i. (Hashable i, Eq i, Hashable s, Eq s) => [Transition (Edge s) i] -> NFA s i
- 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
- 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
- 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
- nfaKleene :: forall s i. (Ord i, Hashable i, Eq i, Hashable s, Eq s) => (i -> Int) -> (Int -> i) -> NFA s i -> NFA s i
Documentation
NFA edges can be labeled with either a symbol in symbol alphabet s
,
or an epsilon.
Instances
Eq s => Eq (Edge s) Source # | |
Ord s => Ord (Edge s) Source # | |
Show s => Show (Edge s) Source # | |
Generic (Edge s) Source # | |
Hashable s => Hashable (Edge s) Source # | |
Defined in Text.ANTLR.Lex.NFA | |
type Rep (Edge s) Source # | |
Defined in Text.ANTLR.Lex.NFA type Rep (Edge s) = D1 (MetaData "Edge" "Text.ANTLR.Lex.NFA" "antlr-haskell-0.1.0.1-47wJxWjYxn91lXcjBVmKNu" False) (C1 (MetaCons "Edge" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: C1 (MetaCons "NFAEpsilon" PrefixI False) (U1 :: Type -> Type)) |
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
.