[Haskell-cafe] Parsec monad transformer with IO?
Stefan Klinger
all-lists at stefan-klinger.de
Thu Mar 18 12:37:22 EDT 2010
Hello!
Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could
use IO as inner monad, and perform IO operations during parsing.
But I failed. Monad transformers still bend my mind. My problem: I
don't see a function to actually lift the IO operation into the
ParsecT. It should be something like
lift :: IO a -> ParsecT s u IO a
The following is a toy example, I just could not make something
smaller: Let's parse command line arguments (tokens are Strings), and
execute them while parsing.
> import Text.Parsec.Prim
> import Text.Parsec.Pos
> import Text.Parsec
> import System.Environment ( getArgs )
Command line interface parser (Clip) type: Inner monad IO, user state
u, tokens are Strings, returns something typed a.
> type Clip u a = ParsecT [String] u IO a
Source code position for command line arguments: The line is always 1,
column n represents the n-th command line argument.
> nextPos p _ _ = incSourceColumn p 1
Two primitive parsers, one for flags (with a dash) and one for other
arguments:
clipFlag "x" accepts the command line flag "-x", and returns "x".
> clipFlag :: String -> Clip u String
> clipFlag x
> = tokenPrim
> id
> nextPos
> (\y -> if '-':x == y then Just x else Nothing)
clipValue accepts any command line argument that does not tart with a
dash '-'.
> clipValue :: Clip u String
> clipValue
> = tokenPrim id nextPos test
> where
> test ('-':_) = Nothing
> test other = Just other
Now the test program:
Load files given on the command line, and sum up their word count,
until -p is given. -p prints the current word count and sets the
counter to zero. Further files may be processed then. At the end, show
the sum of all word counts.
Example: foo has 12 words, bar has 34 words:
main foo -p bar -p foo bar -p
Counted 12 words, reset counter.
Counted 34 words, reset counter.
Counted 46 words, reset counter.
Grand total: 92
> type CurrentCount = Int -- the user state used with Clip/ParsecT.
root implements the command line grammar (<filename>+ "-p")* and
returns the sum of all word counts.
> root :: Clip CurrentCount Int
> root
> = do ns <- many (many1 loadFile >> printSize)
> eof
> return $ sum ns
Interprets each non-flag on the command line as filename, loads it,
counts its words, and adds the count to the state.
> loadFile :: Clip CurrentCount ()
> loadFile
> = do -- expect a filename
> filename <- clipValue
> -- load the file: IO
> content <- lift $ readFile filename
> -- add wordcount to state
> modifyState ((+) (length $ words content))
If -p shows up on the command line, print accumulated count, reset
counter to cero and return count for grand-total calculation.
> printSize :: Clip CurrentCount Int
> printSize
> = do -- expect flag -p
> clipFlag "p"
> -- print current word count: IO
> n <- getState
> lift . putStrLn $ "Counted "++show n++" words, reset counter."
> -- reset user state to zero, return word count for grand total
> putState 0
> return n
main just runs the root parser on the command line arguments and
checks the result.
> main
> = do result <- getArgs >>= runParserT root 0 "command line"
> case result of
> Left err -> error $ show err
> Right n -> putStrLn $ "Grand total: "++show n
So where is the lift function? Does it exist? Here, I need your help.
> lift :: IO a -> ParsecT s u IO a
> lift = undefined
Any comments are appreciated.
Thank you!
Stefan
____________________
[1] http://hackage.haskell.org/packages/archive/parsec/3.0.0/doc/html/Text-Parsec-Prim.html#t:ParsecT
--
Stefan Klinger o/klettern
/\/ bis zum
send plaintext only - max size 32kB - no spam \ Abfallen
http://stefan-klinger.de
More information about the Haskell-Cafe
mailing list