fsmActions-0.3.0: Finite state machines and FSM actionsSource codeContentsIndex
Data.FsmActions
Contents
Data types
Simple FSM operations
Normalisation
Operations on actions
Destination sets
Identity
Determinism
Description

Finite state machines.

Here an FSM is a map from symbols to actions. Symbols are parametric (will usually be Strings or Chars). Actions specify the action of a symbol on each state, and are represented as lists of transitions: one per state. States are just numbers, from 0 to n, corresponding to indices on transition lists in Actions. Then deterministic actions are just Ints, identifying the state to transition to under that action; nondeterministic actions are lists of Ints: all the states to possibly transition to under that action.

Synopsis
type State = Int
newtype DestinationSet = DestinationSet {
destinations :: [State]
}
newtype Action = Action {
destinationSets :: [DestinationSet]
}
data FSM sy
newtype Word sy = Word [sy]
fromList :: Ord sy => [(sy, Action)] -> FSM sy
toList :: FSM sy -> [(sy, Action)]
delete :: Ord sy => sy -> FSM sy -> FSM sy
lookup :: Ord sy => sy -> FSM sy -> Maybe Action
fsmMap :: (sy -> Action -> a) -> FSM sy -> [a]
states :: FSM sy -> [State]
alphabet :: FSM sy -> [sy]
normalise :: FSM sy -> FSM sy
normaliseAction :: Action -> Action
mkAction :: [[State]] -> Action
mkDAction :: [State] -> Action
append :: Action -> Action -> Action
actionLookup :: Action -> State -> DestinationSet
action :: Ord sy => FSM sy -> Word sy -> Maybe Action
actionEquiv :: Ord sy => FSM sy -> Word sy -> Word sy -> Bool
destinationSet :: Ord sy => FSM sy -> State -> Word sy -> Maybe DestinationSet
destinationEquiv :: Ord sy => FSM sy -> State -> Word sy -> Word sy -> Bool
fsmIdentity :: FSM sy -> Action
identity :: Int -> Action
isDAction :: Action -> Bool
isDFSM :: FSM sy -> Bool
Data types
type State = IntSource
States are integers, counting from zero.
newtype DestinationSet Source
Destination sets are just lists of States.
Constructors
DestinationSet
destinations :: [State]
show/hide Instances
newtype Action Source
Actions are lists of DestinationSets, indexed by source State.
Constructors
Action
destinationSets :: [DestinationSet]
show/hide Instances
data FSM sy Source
Finite state machine whose nodes are labelled with type sy.
show/hide Instances
Eq sy => Eq (FSM sy)
Ord sy => Ord (FSM sy)
Show sy => Show (FSM sy)
newtype Word sy Source
Words are lists of symbols.
Constructors
Word [sy]
Simple FSM operations
fromList :: Ord sy => [(sy, Action)] -> FSM sySource
Create an FSM from a list of symbol, Action pairs.
toList :: FSM sy -> [(sy, Action)]Source
Turn an FSM into a list of symbol, Action pairs.
delete :: Ord sy => sy -> FSM sy -> FSM sySource
Delete a symbol and its action from an FSM.
lookup :: Ord sy => sy -> FSM sy -> Maybe ActionSource
Look up a symbol's Action in an FSM
fsmMap :: (sy -> Action -> a) -> FSM sy -> [a]Source
Map a function over the FSM.
states :: FSM sy -> [State]Source
Compute the list of states of the FSM. Only really meaningful if the FSM's well-formedness is not BadLengths. With current implementation, is just [0..n] for some n (or empty).
alphabet :: FSM sy -> [sy]Source
Compute the alphabet of an FSM.
Normalisation
normalise :: FSM sy -> FSM sySource
Normalise an FSM, i.e. normalise all its Actions.
normaliseAction :: Action -> ActionSource
Operations on actions
mkAction :: [[State]] -> ActionSource
Build an action given a nested list of destination states.
mkDAction :: [State] -> ActionSource
Build a deterministic action given a list of destination states.
append :: Action -> Action -> ActionSource
Append two Actions, ie compute the Action corresponding to the application of the first followed by the second.
actionLookup :: Action -> State -> DestinationSetSource
Compute the DestinationSet reached by following some Action from some State.
action :: Ord sy => FSM sy -> Word sy -> Maybe ActionSource
Compute the Action for some Word over some FSM. The word might contain symbols outside the FSM's alphabet, so the result could be Nothing.
actionEquiv :: Ord sy => FSM sy -> Word sy -> Word sy -> BoolSource
Test if two Words are action-equivalent over some FSM.
Destination sets
destinationSet :: Ord sy => FSM sy -> State -> Word sy -> Maybe DestinationSetSource
Compute the DestinationSet for some Word at some State of an FSM. The word might contain symbols outside the FSM's alphabet, or the state might be out of range, so the result could be Nothing.
destinationEquiv :: Ord sy => FSM sy -> State -> Word sy -> Word sy -> BoolSource
Test if two Words are destination-equivalent at some State of an FSM.
Identity
fsmIdentity :: FSM sy -> ActionSource
Compute the identity action for a given FSM.
identity :: Int -> ActionSource
Compute the identity action for a given number of states
Determinism
isDAction :: Action -> BoolSource
Test if an Action is deterministic or not.
isDFSM :: FSM sy -> BoolSource
Compute whether an FSM is deterministic or not.
Produced by Haddock version 2.4.2