HaLeX-1.1: HaLeX enables modelling, manipulation and animation of regular languagesSource codeContentsIndex
Language.HaLex.DfaMonad
Documentation
data Dfa m st sy Source
Constructors
Dfa [sy] [st] st [st] (st -> sy -> m st)
dfawalk :: Monad m => (st -> sy -> m st) -> st -> [sy] -> m stSource
dfaaccept' :: (Monad m, Eq st) => Dfa m st sy -> [sy] -> m BoolSource
dfaaccept :: (Monad m, Eq st) => Dfa m st sy -> [sy] -> m BoolSource
runDfa :: Eq st => Dfa (State s) st sy -> [sy] -> s -> (Bool, s)Source
showDfa :: (Monad m, Show st, Show sy) => Dfa m st sy -> m StringSource
showDfaDelta :: (Monad m, Show st, Show sy) => [st] -> [sy] -> (st -> sy -> m st) -> m ([Char] -> [Char])Source
showInDot :: (Monad m, Eq st, Show st, Show sy) => Dfa m st sy -> Bool -> m [Char]Source
showElemsListPerLine :: [String] -> StringSource
showArrows :: (Monad m, Eq st, Show st, Show sy) => Dfa m st sy -> [st] -> Bool -> m [[Char]]Source
buildLine :: (Monad m, Eq st, Show st, Show sy) => st -> (st -> sy -> m st) -> [st] -> Bool -> sy -> m [Char]Source
(<->) :: Eq a => [a] -> [a] -> [a]Source
xpto :: Monad m => [m [a]] -> m [a]Source
deadstates :: (Monad m, Eq st) => Dfa m st sy -> m [st]Source
deadstates' :: (Monad m, Eq st) => [st] -> [sy] -> (st -> sy -> m st) -> m [st]Source
isStDead :: (Monad m, Eq st) => st -> m [st] -> m BoolSource
isSyncState :: (Monad m, Eq st) => st -> m [st] -> m BoolSource
robot :: Dfa Maybe [Char] [Char]Source
ex2 :: Dfa IO Char CharSource
ex3 :: Dfa (State Integer) Char CharSource
ex4 :: Dfa (State [Char]) Char CharSource
ex5 :: Dfa (State [Char]) Char CharSource
ex_int :: Dfa (State [Char]) Integer CharSource
ex6 :: Dfa (State ([Char], Int)) Integer CharSource
type Instr = [Code]Source
data Code Source
Constructors
Open String
Locate Int
Insert String
Delete [Int]
Save
End
show/hide Instances
te :: Dfa (State ([Char], [Code])) Integer CharSource
pr :: Dfa (State ([Char], [Int])) Integer CharSource
converte :: [Char] -> IntSource
runAccept_pr :: [Char] -> (Bool, ([Char], [Int]))Source
Produced by Haddock version 2.3.0