[Haskell-cafe] Interpreter with Cont
Tim Baumgartner
baumgartner.tim at googlemail.com
Sat Nov 19 21:08:38 CET 2011
Hi all,
I wrote a simple interpreter that can be run in the console:
data Interaction a b = Exit b
| Output b (Interaction a b)
| Input (a -> Interaction a b)
runConsole :: Interaction String String -> IO ()
runConsole (Exit b) =
putStrLn $ "Finished. Result: " ++ b
runConsole (Output s cont) =
putStrLn s >> runConsole cont
runConsole (Input f) =
putStr "> " >> getLine >>= runConsole . f
interpreter :: Int -> Interaction String String
interpreter i = interaction
where
interaction = Input input
input "exit" = Exit (show i)
input "inc" = Output "ok" $ interpreter (i+1)
input "show" = Output (show i) interaction
input "hello"= Output "Hello World!" interaction
input s = Output ("Whas's '" ++ s ++ "' ?") interaction
main = runConsole .
Output "Known commands: show, inc, hello, exit" $ interpreter 5
I have not yet gained a good understanding of the continuation monad, but I
wonder if it could be used here. What would a clean solution look like?
Perhaps there are other things that need to be changed as well?
Regards,
Tim
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111119/cf134e8c/attachment.htm>
More information about the Haskell-Cafe
mailing list