Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Dfsa t
- evaluate :: (Foldable f, Ord t) => Dfsa t -> f t -> Bool
- 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
- data Builder t s a
- data State s
- build :: forall t a. (Bounded t, Ord t, Enum t) => (forall s. State s -> Builder t s a) -> Dfsa t
- state :: Builder t s (State s)
- transition :: t -> t -> State s -> State s -> Builder t s ()
- accept :: State s -> Builder t s ()
Static
Types
Deterministic Finite State Automaton.
The start state is always zero.
Evaluation
evaluate :: (Foldable f, Ord t) => Dfsa t -> f t -> Bool Source #
Evaluate a foldable collection of tokens against the DFA. This returns true if the string is accepted by the language.
Composition
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.
Special DFA
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
.
Builder
Types
Functions
build :: forall t a. (Bounded t, Ord t, Enum t) => (forall s. State s -> Builder t s a) -> Dfsa t Source #
The argument function takes a start state and builds an NFA. This function will execute the builder.
state :: Builder t s (State s) Source #
Generate a new state in the NFA. On any input, the state transitions to the start state.