Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Dfsa t = Dfsa {}
- data Nfsa t = Nfsa {
- nfaTransition :: !(Array (TransitionNfsa t))
- nfaFinal :: !(Set Int)
- data TransitionNfsa t = TransitionNfsa {
- transitionNfsaEpsilon :: !(Set Int)
- transitionNfsaConsume :: !(Map t (Set Int))
- newtype State s = State Int
- data Epsilon = Epsilon !Int !Int
- toDfsa :: (Ord t, Bounded t, Enum t) => Nfsa t -> Dfsa t
- toDfsaMapping :: forall t. (Ord t, Bounded t, Enum t) => Nfsa t -> (Map (Set Int) Int, Dfsa t)
- append :: Nfsa t -> Nfsa t -> Nfsa t
- empty :: Bounded t => Nfsa t
- rejectionNfsa :: Bounded t => Nfsa t
- unionNfsa :: Bounded t => Nfsa t -> Nfsa t -> Nfsa t
- epsilonClosure :: Array (TransitionNfsa t) -> Set Int -> Set Int
- union :: (Ord t, Bounded t, Enum t) => Dfsa t -> Dfsa t -> Dfsa t
- intersection :: (Ord t, Bounded t, Enum t) => Dfsa t -> Dfsa t -> Dfsa t
- acceptance :: Bounded t => Dfsa t
- rejection :: Bounded t => Dfsa t
- minimize :: (Ord t, Bounded t, Enum t) => Array (Map t Int) -> Set Int -> Dfsa t
- minimizeMapping :: forall t. (Ord t, Bounded t, Enum t) => Array (Map t Int) -> Set Int -> (Map Int Int, Dfsa t)
- composeMapping :: (Ord t, Bounded t, Enum t) => (Bool -> Bool -> Bool) -> Dfsa t -> Dfsa t -> (Map (Int, Int) Int, Dfsa t)
Types
Deterministic Finite State Automaton.
The start state is always zero.
Non-Deterministic Finite State Automaton.
Some notes on the implementation and design:
- You can transition to any non-negative number of states (including 0).
- There is only one start state.
- We use the Thompson encoding. This means that there is an epsilon transition that consumes no input.
- We store the full epsilon closure for every state. This means that, when evaluating the NFA, we do not ever need to compute the closure.
- There is no Eq instance for NFA. In general, this can take exponential time. If you really need to do this, convert the NFA to a DFA.
Invariants:
- The start state is always the state at position 0.
- The length of nfaTransition is given by nfaStates.
Nfsa | |
|
data TransitionNfsa t Source #
TransitionNfsa | |
|
Instances
Eq t => Eq (TransitionNfsa t) Source # | |
Defined in Automata.Internal (==) :: TransitionNfsa t -> TransitionNfsa t -> Bool # (/=) :: TransitionNfsa t -> TransitionNfsa t -> Bool # | |
(Bounded t, Enum t, Show t) => Show (TransitionNfsa t) Source # | |
Defined in Automata.Internal showsPrec :: Int -> TransitionNfsa t -> ShowS # show :: TransitionNfsa t -> String # showList :: [TransitionNfsa t] -> ShowS # |
Builder Types
NFA Functions
toDfsa :: (Ord t, Bounded t, Enum t) => Nfsa t -> Dfsa t Source #
Convert an NFSA to a DFSA. For certain inputs, this causes the number of states to blow up expontentially, so do not call this on untrusted input.
toDfsaMapping :: forall t. (Ord t, Bounded t, Enum t) => Nfsa t -> (Map (Set Int) Int, Dfsa t) Source #
empty :: Bounded t => Nfsa t Source #
Automaton that accepts the empty string and rejects all
other strings. This is the identity for append
.
rejectionNfsa :: Bounded t => Nfsa t Source #
Docs for this are at Automata.Nfsa.rejection
.
unionNfsa :: Bounded t => Nfsa t -> Nfsa t -> Nfsa t Source #
Docs for this are at Automata.Nfsa.union
.
epsilonClosure :: Array (TransitionNfsa t) -> Set Int -> Set Int Source #
DFA Functions
union :: (Ord t, Bounded t, Enum t) => Dfsa t -> Dfsa t -> Dfsa t Source #
Accepts input that is accepted by either of the two argument DFAs. This is also known as synchronous composition in the literature.
intersection :: (Ord t, Bounded t, Enum t) => Dfsa t -> Dfsa t -> Dfsa t Source #
Accepts input that is accepted by both of the two argument DFAs. This is also known as completely synchronous composition in the literature.
acceptance :: Bounded t => Dfsa t Source #
Automaton that accepts all input. This is the identity
for intersection
.
rejection :: Bounded t => Dfsa t Source #
Automaton that rejects all input. This is the identity
for union
.
minimize :: (Ord t, Bounded t, Enum t) => Array (Map t Int) -> Set Int -> Dfsa t Source #
This uses Hopcroft's Algorithm. It is like a smart constructor for Dfsa.