HaLeX-1.2.6: HaLeX enables modelling, manipulation and visualization of regular languages

Copyright(c) João Saraiva 20012002200320042005 2016
LicenseLGPL
Maintainersaraiva@di.uminho.pt
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.HaLex.Ndfa

Contents

Description

Non-Deterministic Finite Automata in Haskell.

Code Included in the Lecture Notes on Language Processing (with a functional flavour).

Synopsis

Data type

data Ndfa st sy Source #

Type of Non-Deterministic Finite Automata. Parameterized with the type st of states and sy of symbols.

Constructors

Ndfa [sy] [st] [st] [st] (st -> Maybe sy -> [st]) 

Instances

(Show st, Show sy, Ord st, Ord sy) => Fa Ndfa st sy Source #

Instance of class Fa for a Ndfa

Methods

accept :: Ndfa st sy -> [sy] -> Bool Source #

sizeFa :: Ndfa st sy -> Int Source #

equiv :: Ndfa st sy -> Ndfa st sy -> Bool Source #

minimize :: Ndfa st sy -> Dfa [[st]] sy Source #

reverseFa :: Ndfa st sy -> Ndfa st sy Source #

deadstates :: Ndfa st sy -> [st] Source #

sentences :: Ndfa st sy -> [[sy]] Source #

toHaskell' :: Ndfa st sy -> String -> IO () Source #

toGraph :: Ndfa st sy -> String -> String Source #

toGraphIO :: Ndfa st sy -> String -> IO () Source #

unionFa :: Ndfa st sy -> Ndfa st sy -> Ndfa st sy Source #

concatFa :: Ndfa st sy -> Ndfa st sy -> Ndfa st sy Source #

starFa :: Ndfa st sy -> Ndfa st sy Source #

plusFa :: Ndfa st sy -> Ndfa st sy Source #

(Eq st, Show st, Show sy) => Show (Ndfa st sy) Source #

Print a Ndfa as a Haskell function.

Methods

showsPrec :: Int -> Ndfa st sy -> ShowS #

show :: Ndfa st sy -> String #

showList :: [Ndfa st sy] -> ShowS #

Acceptance

ndfaaccept Source #

Arguments

:: Ord st 
=> Ndfa st sy

Automaton

-> [sy]

Input symbols

-> Bool 

Test whether the given automaton accepts the given list of input symbols.

ndfawalk Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition function

-> [st]

Initial states

-> [sy]

Input symbols

-> [st]

Reached states

Execute the transition function of a Ndfa on an initial state and list of input symbol. Return the final state when all input symbols have been consumed.

epsilon_closure Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition function

-> [st]

Current states

-> [st]

Reached states

Compute the eplison closure of a Ndfa.

Transformation

ttNdfa2Ndfa Source #

Arguments

:: (Eq st, Eq sy) 
=> ([sy], [st], [st], [st], [(st, Maybe sy, st)])

Tuple-based Ndfa

-> Ndfa st sy

Automaton

Reconstruct a Ndfa from a transition table. Given a Ndfa expressed by a transition table (ie a list of triples of the form (Origin,Maybe Symbol,Destination) it constructs a Ndfa. The other elements of the input tuple are the vocabulary, a set of states, and the sets of initial and final states

Transitions

ndfaTransitionsFromTo :: Eq st => (st -> Maybe sy -> [st]) -> [sy] -> st -> st -> [Maybe sy] Source #

Compute the labels with the same (giving) origin and destination

ndfadestinationsFrom Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> st

Origin

-> [st]

Destination States

Compute the destination states giving the origin state

transitionTableNdfa Source #

Arguments

:: Ndfa st sy

Automaton

-> [(st, Maybe sy, st)]

Transition table

Produce the transition table of a given Ndfa.

Given a Ndfa it returns a list of triples of the form (Origin,Symbol,Destination) defining all the transitions of the Ndfa.

ndfareachedStatesFrom Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> st

Origin

-> [st]

Reached States

Compute the states that can be reached from a given state according to a given transition function and vocabulary

Printing

toHaskell Source #

Arguments

:: Show fa 
=> fa

Automaton

-> [Char]

Haskell module or file name

-> IO () 

Produce the transition table of a given finite automaton.

renameNdfa Source #

Arguments

:: Eq st 
=> Ndfa st sy

Automaton

-> Int

Initial integer number

-> Ndfa Int sy

Renamed Automaton

Renames a Ndfa.

showNdfaDelta :: (Show t1, Show a, Show t, Eq t) => [t1] -> [a] -> (t1 -> Maybe a -> [t]) -> String -> String Source #

Helper function to show the transition function of a Ndfa.

Properties of Ndfa

sizeNdfa Source #

Arguments

:: Ndfa st sy

Automaton

-> Int

Size

The size of an automaton is the number of its states.

ndfadeadstates Source #

Arguments

:: Ord st 
=> Ndfa st sy

Automaton

-> [st]

Dead States

Compute the dead states of a Ndfa

Properties of States

ndfaIsStDead Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> [st]

Set of Final States

-> st

State

-> Bool 

Checks whether a Ndfa state is dead or not.

ndfaIsSyncState Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> [st]

Set of Final States

-> st

State

-> Bool 

Checks whether a Ndfa state is a sync state or not

ndfanumberIncomingArrows Source #

Arguments

:: Eq st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> [st]

Set of States

-> st

Destination

-> Int

Number of Arrows

Compute the number of incoming arrows for a given state

ndfanumberOutgoingArrows Source #

Arguments

:: Ord st 
=> (st -> Maybe sy -> [st])

Transition Function

-> [sy]

Vocabulary

-> st

Origin

-> Int

Number of Arrows

Compute the number of outgoing arrows for a given state