Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Nfst t m = Nfst {
- nfstTransition :: !(Array (TransitionNfst t m))
- nfstFinal :: !(Set Int)
- data TransitionNfst t m = TransitionNfst {
- transitionNfstEpsilon :: !(Set Int)
- transitionNfstConsume :: !(Map t (Map m (Set Int)))
- data Dfst t m = Dfst {
- dfstTransition :: !(Array (Map t (MotionDfst m)))
- dfstFinal :: !(Set Int)
- data MotionDfst m = MotionDfst {
- motionDfstState :: !Int
- motionDfstOutput :: !m
- data Edge t m = Edge !Int !Int !t !t !m
- data EdgeDest t m = EdgeDest !Int !t !t !m
- epsilonClosure :: Array (TransitionNfst m t) -> Set Int -> Set Int
- rejection :: (Ord t, Bounded t, Monoid m, Ord m) => Nfst t m
- union :: (Bounded t, Ord m) => Nfst t m -> Nfst t m -> Nfst t m
Documentation
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.
Nfst | |
|
data TransitionNfst t m Source #
TransitionNfst | |
|
Instances
(Eq t, Eq m) => Eq (TransitionNfst t m) Source # | |
Defined in Automata.Internal.Transducer (==) :: TransitionNfst t m -> TransitionNfst t m -> Bool # (/=) :: TransitionNfst t m -> TransitionNfst t m -> Bool # | |
(Bounded t, Enum t, Show t, Show m) => Show (TransitionNfst t m) Source # | |
Defined in Automata.Internal.Transducer showsPrec :: Int -> TransitionNfst t m -> ShowS # show :: TransitionNfst t m -> String # showList :: [TransitionNfst t m] -> ShowS # |
A deterministic finite state transducer.
Dfst | |
|
data MotionDfst m Source #
MotionDfst | |
|
Instances
Eq m => Eq (MotionDfst m) Source # | |
Defined in Automata.Internal.Transducer (==) :: MotionDfst m -> MotionDfst m -> Bool # (/=) :: MotionDfst m -> MotionDfst m -> Bool # | |
Show m => Show (MotionDfst m) Source # | |
Defined in Automata.Internal.Transducer showsPrec :: Int -> MotionDfst m -> ShowS # show :: MotionDfst m -> String # showList :: [MotionDfst m] -> ShowS # |
epsilonClosure :: Array (TransitionNfst m t) -> Set Int -> Set Int Source #