automata-0.1.0.0: automata

Safe HaskellNone
LanguageHaskell2010

Automata.Internal

Contents

Synopsis

Types

data Dfsa t Source #

Deterministic Finite State Automaton.

The start state is always zero.

Constructors

Dfsa 

Fields

  • dfaTransition :: !(Array (Map t Int))

    Given a state and transition, this field tells you what state to go to next. The length of this array must match the total number of states.

  • dfaFinal :: !(Set Int)

    A string that ends in any of these set of states is considered to have been accepted by the grammar.

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 #

data Nfsa t Source #

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.

Constructors

Nfsa 

Fields

  • nfaTransition :: !(Array (TransitionNfsa t))

    Given a state and transition, this field tells you what state to go to next. The length of this array must match the total number of states. The data structure inside is a diet map. This is capable of collapsing adjacent key-value pairs into ranges.

  • nfaFinal :: !(Set Int)

    A string that ends in any of these set of states is considered to have been accepted by the grammar.

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

Defined in Automata.Internal

Methods

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

show :: Nfsa t -> String #

showList :: [Nfsa t] -> ShowS #

Bounded t => Semiring (Nfsa t) Source #

This uses union for plus and append for times.

Instance details

Defined in Automata.Internal

Methods

plus :: Nfsa t -> Nfsa t -> Nfsa t #

zero :: Nfsa t #

times :: Nfsa t -> Nfsa t -> Nfsa t #

one :: Nfsa t #

data TransitionNfsa t Source #

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

Defined in Automata.Internal

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

Defined in Automata.Internal

Builder Types

newtype State s Source #

Constructors

State Int 

data Epsilon Source #

Constructors

Epsilon !Int !Int 

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 #

append :: Nfsa t -> Nfsa t -> Nfsa 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.

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.

minimizeMapping :: forall t. (Ord t, Bounded t, Enum t) => Array (Map t Int) -> Set Int -> (Map Int Int, Dfsa t) Source #

This uses Hopcroft's Algorithm. It also provides the mapping from old state number to new state number. We need this mapping for a special NFST to DFST minimizer.

composeMapping :: (Ord t, Bounded t, Enum t) => (Bool -> Bool -> Bool) -> Dfsa t -> Dfsa t -> (Map (Int, Int) Int, Dfsa t) Source #