[Haskell-cafe] Regular Expression to Determinate Finite Automata translator

S. Doaitse Swierstra doaitse at swierstra.net
Thu Jul 22 16:10:38 EDT 2010


The simplest way to make a recogniser out of a RE is to use one of the available parsing libraries:

module RE where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples

data RE = Epsilon | Leaf Char | Selection RE RE | Sequence RE RE | Kleene RE | Optional RE | End


re_to_fsm :: RE -> Parser String
re_to_fsm re = case re of 
        Leaf c                -> lift <$> pSym c
        Selection re1 re2     -> re_to_fsm re1 <|> re_to_fsm re2
        Sequence re1 re2      -> (++) <$> re_to_fsm re1 <*> re_to_fsm re2
        Kleene re             -> concat <$> pList (re_to_fsm re)
	Optional re           -> re_to_fsm re `opt` ""
        End                   -> pure ""

t = re_to_fsm ((Kleene (Leaf 'a') `Sequence` Kleene (Leaf 'b')) `Selection` (Kleene (Leaf 'a') `Sequence` (Kleene (Leaf 'c') )))

t1 = run t "aaabbb"
t2 = run t "aaaaccccccc"
t3 = run t "aaddcc"
test = run (re_to_fsm (Kleene (Leaf 'a') `Sequence` Kleen (Left 'b')) "aaabbb"

*RE> t1
--
-- > Result: "aaabbb"
-- 
*RE> t2
--
-- > Result: "aaaaccccccc"
-- 
*RE> t3
--
-- > Result: "aacc"
-- > Correcting steps: 
-- >    Deleted  'd' at position 2 expecting one of ['a', 'c', 'a', 'b']
-- >    Deleted  'd' at position 3 expecting 'c'
-- 
*RE> 


On 22 jul 2010, at 20:51, Aaron Gray wrote:

> Hi,
> 
> I am a Haskell newbie. I have coded a Regular Expression to Determinate Finite Automata translator. Algorithm from the Dragon Book.
> 
> Would someone eyeball the code and give me suggestions please. 
> 
> I have not done anything on character classes yet though. And the parsing is a bit of a hack.
> 
> What I am not sure about is having to have multiple versions of similar datatype, each with variations in order to enumerate and generate followPos set.
> 
> Is there a better way of implementing this ?
> 
> Many thanks in advance,
> 
> Aaron
> 
> <RE2DFA.hs>_______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100722/25ef8467/attachment.html


More information about the Haskell-Cafe mailing list