automata-0.1.0.0: automata

Safe HaskellNone
LanguageHaskell2010

Automata.Dfsa

Contents

Synopsis

Static

Types

data Dfsa t Source #

Deterministic Finite State Automaton.

The start state is always zero.

Instances
Eq t => Eq (Dfsa t) Source # 
Instance details

Defined in Automata.Internal

Methods

(==) :: Dfsa t -> Dfsa t -> Bool #

(/=) :: Dfsa t -> Dfsa t -> Bool #

(Bounded t, Enum t, Show t) => Show (Dfsa t) Source # 
Instance details

Defined in Automata.Internal

Methods

showsPrec :: Int -> Dfsa t -> ShowS #

show :: Dfsa t -> String #

showList :: [Dfsa t] -> ShowS #

(Ord t, Enum t, Bounded t) => Semiring (Dfsa t) Source #

This uses union for plus and intersection for times.

Instance details

Defined in Automata.Internal

Methods

plus :: Dfsa t -> Dfsa t -> Dfsa t #

zero :: Dfsa t #

times :: Dfsa t -> Dfsa t -> Dfsa t #

one :: Dfsa t #

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

data Builder t s a Source #

Instances
Monad (Builder t s) Source # 
Instance details

Defined in Automata.Dfsa

Methods

(>>=) :: Builder t s a -> (a -> Builder t s b) -> Builder t s b #

(>>) :: Builder t s a -> Builder t s b -> Builder t s b #

return :: a -> Builder t s a #

fail :: String -> Builder t s a #

Functor (Builder t s) Source # 
Instance details

Defined in Automata.Dfsa

Methods

fmap :: (a -> b) -> Builder t s a -> Builder t s b #

(<$) :: a -> Builder t s b -> Builder t s a #

Applicative (Builder t s) Source # 
Instance details

Defined in Automata.Dfsa

Methods

pure :: a -> Builder t s a #

(<*>) :: Builder t s (a -> b) -> Builder t s a -> Builder t s b #

liftA2 :: (a -> b -> c) -> Builder t s a -> Builder t s b -> Builder t s c #

(*>) :: Builder t s a -> Builder t s b -> Builder t s b #

(<*) :: Builder t s a -> Builder t s b -> Builder t s a #

data State s Source #

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.

transition Source #

Arguments

:: t

inclusive lower bound

-> t

inclusive upper bound

-> State s

from state

-> State s

to state

-> Builder t s () 

Add a transition from one state to another when the input token is inside the inclusive range. If multiple transitions from a state are given, the last one given wins.

accept :: State s -> Builder t s () Source #

Mark a state as being an accepting state.