
data Command = Play Int [Int] | Jump Int -- I want to parse a string that will have any of the following forms -- and turn it into Command -- "p" - Produces "Play 0 []" -- "p v55" - Produces "Play 55 []" -- "p c123" - Produces "Play 0 [1,2,3]" -- "p v13 c12" - Produces "Play 13 [1,2]" -- In other words the p command can have two kinds of arguments, "v" -- and "c", and there are defaults for the case that no argument is -- supplied. -- So it's going to look something like play :: Parser Command play = do char 'p' vResult <- .. maybe a v, otherwise supply default value 0 cResult <- .. maybe a c .. (could the v and c be put in either order?) return $ Play vResult cResult

On 19/07/10 04:36, Michael Mossey wrote:
data Command = Play Int [Int] | Jump Int
-- I want to parse a string that will have any of the following forms -- and turn it into Command -- "p" - Produces "Play 0 []" -- "p v55" - Produces "Play 55 []" -- "p c123" - Produces "Play 0 [1,2,3]" -- "p v13 c12" - Produces "Play 13 [1,2]"
-- In other words the p command can have two kinds of arguments, "v" -- and "c", and there are defaults for the case that no argument is -- supplied. -- So it's going to look something like
play :: Parser Command play = do char 'p' vResult <- .. maybe a v, otherwise supply default value 0 cResult <- .. maybe a c .. (could the v and c be put in either order?) return $ Play vResult cResult
This isn't really an answer, but more of a suggestion on how to approach parsing problems. I tend to split things until I get down to easily handled stuff. In this case I'd probably write the following functions: 1. Parser for strings like "v55" and "v13": result type Parser Int 2. Parser for strings like "c123" and "c12": result type Parser [Int] 3. Parser combining 1 and 2: result type Parser (Int, [Int]) 4. Parser requiring a string starting with 'p ', combined with 3: result type Parser Command /M

Magnus Therning wrote:
This isn't really an answer, but more of a suggestion on how to approach parsing problems.
I tend to split things until I get down to easily handled stuff. In this case I'd probably write the following functions:
1. Parser for strings like "v55" and "v13": result type Parser Int 2. Parser for strings like "c123" and "c12": result type Parser [Int] 3. Parser combining 1 and 2: result type Parser (Int, [Int]) 4. Parser requiring a string starting with 'p ', combined with 3: result type Parser Command
That makes sense. Mike

Here's what I eventually came up with. I decided to make a function parseArg that can parse either "v" args or "c" args, and use sepBy parseArg space to parse all the args on the command line. I created the algebraic type Arg to express both kinds of args, which I call Verts and Chans, so that parseArg can have the signature parseArg :: Parser Arg and parsing the whole command line: parseArgs :: Parser [Arg] Then I grab the first Verts and first Chans from the resulting list, and ignore the other ones (if any others are present). I use fromMaybe to supply a default value. data Command = Forward Int | Backward Int | Jump Int | Play Int [Int] | Quit deriving (Show) data Arg = Verts Int | Chans [Int] deriving (Show) integer :: Parser Int integer = do ds <- many1 digit return (read ds) digitList :: Parser [Int] digitList = do d <- digit remainder <- digitList return $ read [d] : remainder <|> return [] -- Parse an argument for the p command. -- Note that so-called "v" args are now just bare integers. -- "c" args are still prefaced with a "c" parseArg :: Parser Arg parseArg = do fmap Verts integer <|> do char 'c' fmap Chans digitList parseArgs :: Parser [Arg] parseArgs = sepBy parseArg space parseP :: Parser Command parseP = (do many space -- Zero or more arguments may be present. -- We will consider at most one "v" argument -- and at most one "c" argument. There are -- default values for the "V" and "C" arguments -- when none are present. args <- parseArgs let vArgs = [i | Verts i <- args] cArgs = [c | Chans c <- args] singleV = fromMaybe 1 (listToMaybe vArgs) singleC = fromMaybe [] (listToMaybe cArgs) return $ Play singleV singleC) <|> (return $ Play 1 []) parseCommand :: Parser Command parseCommand = do char 'j' fmap Jump integer <|> do char 'f' fmap Forward (option 1 integer) <|> do char 'b' fmap Backward (option 1 integer) <|> do char 'p' parseP <|> do char 'q' return Quit runParse :: String -> Either String Command runParse s = case parse parseCommand "" s of Left err -> Left $ show err Right x -> Right x

On Mon, Jul 19, 2010 at 9:41 AM, Michael Mossey
digitList :: Parser [Int] digitList = do d <- digit remainder <- digitList return $ read [d] : remainder <|> return []
I would write digitList :: Parser [Int] digitList = do l <- many digit let l' = map ( read -- read the string . (: []) -- convert the digit from a char to a string so I can "read" it ) l return l' That can be shortened to : digitList :: Parser [Int] digitList = map ( read.(:[])) `fmap` many digit David.

Parsec has the CharParser - /integer/ - to avoid "many1 digit" and the like.
You have to instantiate a TokenParser to use it - but for all but
simplest parser the effort pays for itself.
On 19 July 2010 09:14, David Virebayre
That can be shortened to :
digitList :: Parser [Int] digitList = map ( read.(:[])) `fmap` many digit

On 19 July 2010 12:05, David Virebayre
Note that he doesn't want "123456" to parse as the integer 123456, but rather as the list of digits [ 1,2,3,4,5,6 ].
Fair enough, I'd swap /digitToInt/ for read though... digit1 :: Parser Int digit1 = liftM digitToInt digit digitList :: Parser [Int] digitList = many digit1 digitToInt should do less work than read - running read is effectively re-parsing the digits you have already parsed. Best wishes Stephen

On Mon, Jul 19, 2010 at 2:10 PM, Stephen Tetley
On 19 July 2010 12:05, David Virebayre
wrote: Note that he doesn't want "123456" to parse as the integer 123456, but rather as the list of digits [ 1,2,3,4,5,6 ].
Fair enough, I'd swap /digitToInt/ for read though...
Of course ! I just didn't know that function existed :) Now that I think of it, that's not a good excuse. Converting a single char to an int is not difficult, I just had made a quick reply without thinking too much. David.

In any case, thanks to David and Stephen for helping with my problem. Either solution is a neat improvement and an illustration for how the language can be used. Mike David Virebayre wrote:
On Mon, Jul 19, 2010 at 2:10 PM, Stephen Tetley
wrote: On 19 July 2010 12:05, David Virebayre
wrote: Note that he doesn't want "123456" to parse as the integer 123456, but rather as the list of digits [ 1,2,3,4,5,6 ]. Fair enough, I'd swap /digitToInt/ for read though...
Of course ! I just didn't know that function existed :) Now that I think of it, that's not a good excuse. Converting a single char to an int is not difficult, I just had made a quick reply without thinking too much.
David. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Michael Mossey schrieb:
Here's what I eventually came up with. I decided to make a function parseArg that can parse either "v" args or "c" args, and use
sepBy parseArg space
You may want to reject duplicate v or c args rather than to discard them silently. You can do so by checking the list before returning "Play singleV singleC" and use the "fail" or "unexpected" parser for non-proper lists. C.
to parse all the args on the command line. I created the algebraic type Arg to express both kinds of args, which I call Verts and Chans, so that parseArg can have the signature
parseArg :: Parser Arg
and parsing the whole command line:
parseArgs :: Parser [Arg]
Then I grab the first Verts and first Chans from the resulting list, and ignore the other ones (if any others are present). I use fromMaybe to supply a default value.
data Command = Forward Int | Backward Int | Jump Int | Play Int [Int] | Quit deriving (Show)
data Arg = Verts Int | Chans [Int] deriving (Show)
integer :: Parser Int integer = do ds <- many1 digit return (read ds)
digitList :: Parser [Int] digitList = do d <- digit remainder <- digitList return $ read [d] : remainder <|> return []
-- Parse an argument for the p command. -- Note that so-called "v" args are now just bare integers. -- "c" args are still prefaced with a "c" parseArg :: Parser Arg parseArg = do fmap Verts integer <|> do char 'c' fmap Chans digitList
parseArgs :: Parser [Arg] parseArgs = sepBy parseArg space
parseP :: Parser Command parseP = (do many space -- Zero or more arguments may be present. -- We will consider at most one "v" argument -- and at most one "c" argument. There are -- default values for the "V" and "C" arguments -- when none are present. args <- parseArgs let vArgs = [i | Verts i <- args] cArgs = [c | Chans c <- args] singleV = fromMaybe 1 (listToMaybe vArgs) singleC = fromMaybe [] (listToMaybe cArgs) return $ Play singleV singleC) <|> (return $ Play 1 [])
parseCommand :: Parser Command parseCommand = do char 'j' fmap Jump integer <|> do char 'f' fmap Forward (option 1 integer) <|> do char 'b' fmap Backward (option 1 integer) <|> do char 'p' parseP <|> do char 'q' return Quit
runParse :: String -> Either String Command runParse s = case parse parseCommand "" s of Left err -> Left $ show err Right x -> Right x
participants (5)
-
Christian Maeder
-
David Virebayre
-
Magnus Therning
-
Michael Mossey
-
Stephen Tetley