parsing commandline arguments using parsec

Hello. I've rewritten the source position handing of parsec so that you can now use different position markers such as commandline arguments. You can find it with a demo application here: (Still very untested) http://www.mawercer.de/marcweber/haskell/fparsec/ Do you think this would be useful merging back (after fixing some small bugs like missing spaces in error message and adding some more documentation) ? Example application: ---------------------------------------------------- module Main where import Data.List import Text.ParserCombinators.Parsec.Prim import Text.ParserCombinators.Parsec.Combinator import Text.ParserCombinators.Parsec.Token import Text.ParserCombinators.Parsec.Char import Text.ParserCombinators.Parsec.Argument usage = unlines [ "cat <file> <file> (- means stdin/out)" , "tac <file> <file> (- means stdin/out)" , "calc 3 + 7 \\* 8 ... <- shell escape" ] cat :: ( String -> String ) -> String -> ArgParser () (IO ()) cat f s = do expectToken s input <- inputFile output <- outputFile return $ input >>= output . f calc :: ArgParser () (IO ()) calc = expectToken "calc" >> sum >>= return . print where sum = fmap (foldr1 (+)) (sepBy product (expectToken "+") ) product =fmap (foldr1 (*)) (sepBy value (expectToken "*")) value = intArg parser = choice [ cat id "cat" -- cat , cat (unlines . map reverse . lines) "tac" -- cat but reverse lines , calc -- simple calculator, only knows how to do + and * operations ] main = do action <- handleArgs parser () usage action ---------------------------------------------------- Marc Weber
participants (1)
-
Marc Weber