automata-0.1.0.0: automata

Safe HaskellNone
LanguageHaskell2010

Automata.Nfst

Contents

Synopsis

Static

Types

data Nfst t m Source #

A nondeterministic finite state transducer. The t represents the input token on which a transition occurs. The m represents the output token that is generated when a transition is taken. On an epsilon transation, no output is generated.

Instances
(Eq t, Eq m) => Eq (Nfst t m) Source # 
Instance details

Defined in Automata.Internal.Transducer

Methods

(==) :: Nfst t m -> Nfst t m -> Bool #

(/=) :: Nfst t m -> Nfst t m -> Bool #

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

Defined in Automata.Internal.Transducer

Methods

showsPrec :: Int -> Nfst t m -> ShowS #

show :: Nfst t m -> String #

showList :: [Nfst t m] -> ShowS #

Functions

evaluate :: forall f t m. (Foldable f, Ord t, Ord m) => Nfst t m -> f t -> Set [m] Source #

Evaluate an NFST. If the output is the empty set, the input string did not belong to the language. Otherwise, all possible outputs given. The output token lists are in reverse order, and they are all the exact same length as the input string. The reversed order is done to maximize opportunities for sharing common output prefixes. To get the output tokens in the right order, reverse the NFST before evaluating an input string against it. Then, the output tokens will be in the right order, and they will share common suffixes in memory.

evaluateAscii :: forall m. Ord m => Nfst Char m -> ByteString -> Set [m] Source #

union :: (Bounded t, Ord m) => Nfst t m -> Nfst t m -> Nfst t m Source #

Accepts input that is accepts by either of the transducers, producing the output of both of them.

toDfst :: forall t m. (Ord t, Bounded t, Enum t, Monoid m) => Nfst t m -> Dfst t m Source #

Convert an NFST to a DFST that accepts the same input and produces output. Since NFST are more powerful than DFST, it is not possible to preserve output of the NFST during this conversion. However, this function makes the guarantee that if the NFST would accepts an input string and produces the output

[[a1,a2,a3,...],[b1,b2,b3,...],...]

Then DFST will accept the same input and produce an output of

∃ ω1 ω2. [ω1 <> a1 <> b1 <> ..., ω2 <> a1 <> b1 <> ...]

This must be a commutative semigroup, and the existentially quantified values appended to the output cannot be easily predicted.

toNfsa :: Nfst t m -> Nfsa t Source #

Discard information about output tokens.

Special Transducers

rejection :: (Ord t, Bounded t, Monoid m, Ord m) => Nfst t m Source #

Transducer that rejects all input, generating the monoid identity as output. This is the identity for union.

Builder

Types

data Builder t m s a Source #

Instances
Monad (Builder t m s) Source # 
Instance details

Defined in Automata.Nfst

Methods

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

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

return :: a -> Builder t m s a #

fail :: String -> Builder t m s a #

Functor (Builder t m s) Source # 
Instance details

Defined in Automata.Nfst

Methods

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

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

Applicative (Builder t m s) Source # 
Instance details

Defined in Automata.Nfst

Methods

pure :: a -> Builder t m s a #

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

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

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

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

data State s Source #

Functions

build :: forall t m a. (Bounded t, Ord t, Enum t, Monoid m, Ord m) => (forall s. State s -> Builder t m s a) -> Nfst t m Source #

The argument function turns a start state into an NFST builder. This function converts the builder to a usable transducer.

state :: Builder t m s (State s) Source #

Generate a new state in the NFA. On any input, the state transitions to zero states.

transition Source #

Arguments

:: t

inclusive lower bound

-> t

inclusive upper bound

-> m

output token

-> State s

from state

-> State s

to state

-> Builder t m s () 

Add a transition from one state to another when the input token is inside the inclusive range.

epsilon Source #

Arguments

:: State s

from state

-> State s

to state

-> Builder t m s () 

Add a transition from one state to another that consumes no input. No output is generated on such a transition.

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

Mark a state as being an accepting state.