
Hi, I am writing a Text Adventure game in Haskell (like Zork) I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself) Everything that I have works (so far...) except for the following problem: I want to define a grammar using a series of Verbs like this: data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read) and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command" Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword My parser is defined like this: newtype Parser a = Parser (String -> [(a, String)]) So I CAN give it a Verb type but this is where I run into a problem.... I've written a Parser called keyword keyword :: Parser Verb keyword = do x <- many1 letter return (read x) (read this as "take-at-least-one-alphabetic-letter-and-convert-to-a-Verb-type") which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt. Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar". Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing. I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context. Thanks Mark Spezzano

On Sun, Jan 17, 2010 at 6:30 AM, Mark Spezzano wrote: I've written a Parser called keyword keyword :: Parser Verb
keyword = do x <- many1 letter
return (read x) (read this as
"take-at-least-one-alphabetic-letter-and-convert-to-a-Verb-type") which DOES work provided that the user types in one of my Verbs. If they
don't, well, the whole thing fails with an Exception and halts processing,
returning to GHCi prompt. Question: Am I going about this the right way? I want to put together lots
of "data" types like Verb and Noun etc so that I can build a kind of "BNF
grammar". Sounds good to me. Question: If I am going about this the right way then what do I about the
"read x" bit failing when the user stops typing in a recognised keyword. I
could catch the exception, but typing an incorrect sentence is just a typo,
not really appropriate for an exception, I shouldn't think. If it IS
appropriate to do this in Haskell, then how do I catch this exception and
continue processing. In my opinion, traditional exceptions have no place in Haskell. In some
others' opinions, they have their place, but are infrequently used. In any
case, you're right, this is not the time to catch an exception.
This is a usability failure on the part of the Haskell prelude. read should
have the type Read a => String -> Maybe a, because failure is possible. You
can write a proper version:
import Data.Maybe (listToMaybe)
maybeRead :: Read a => String -> Maybe a
maybeRead = fmap fst . listToMaybe . reads
Luke

Hello Mark [ Literate haskell follows... ]
module Verb where
import qualified Data.Map as Map import Data.Char
data Verb = Go | Get | Jump | Climb | Give deriving (Show, Read)
I wouldn't use read instead something either a simple function:
verb :: String -> Maybe Verb verb "Go" = Just Go verb "Get" = Just Get verb _ = Nothing
Or possible a Map:
verb2 :: String -> Maybe Verb verb2 s = Map.lookup s verb_map
verb_map :: Map.Map String Verb verb_map = Map.fromAscList [ ("Go", Go), ("Get", Get) {- .. -} ]
You could then do more about say case sensitivity - e.g. add ("get",Get) etc or always convert to upper before querying the map.
verb3 :: String -> Maybe Verb verb3 s = Map.lookup (map toUpper s) verb_map2
verb_map2 :: Map.Map String Verb verb_map2 = Map.fromAscList [ ("GO", Go), ("GET", Get) {- .. -} ]
Best wishes Stephen

On Sun, Jan 17, 2010 at 7:02 AM, Stephen Tetley
I wouldn't use read instead something either a simple function:
verb :: String -> Maybe Verb verb "Go" = Just Go verb "Get" = Just Get verb _ = Nothing
Or possible a Map:
verb2 :: String -> Maybe Verb verb2 s = Map.lookup s verb_map
verb_map :: Map.Map String Verb verb_map = Map.fromAscList [ ("Go", Go), ("Get", Get) {- .. -} ]
Oh, yeah, I like these better than relying on the Read instance. Relying on Read and Show for program logic has been kind of an implicit smell to me, and I can put my finger on why now: you lose alpha conversion on the program scale. I like the ability to rename with confidence. Plus, this way it is natural to encode synonyms; eg. "take" and "get". Though depending on the vernacular of the game you might not want that. I'm not sure what it means to take out of bed. Luke
You could then do more about say case sensitivity - e.g. add ("get",Get) etc or always convert to upper before querying the map.
verb3 :: String -> Maybe Verb verb3 s = Map.lookup (map toUpper s) verb_map2
verb_map2 :: Map.Map String Verb verb_map2 = Map.fromAscList [ ("GO", Go), ("GET", Get) {- .. -} ]
Best wishes
Stephen _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Sonntag 17 Januar 2010 14:30:36 schrieb Mark Spezzano:
Hi,
I am writing a Text Adventure game in Haskell (like Zork)
I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself)
Everything that I have works (so far...) except for the following problem:
I want to define a grammar using a series of Verbs like this:
data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read)
and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command"
Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs
So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword
But the Read instance can only read "Get", not "get". You'd have to capitalise the input to work with derived Read instances.
My parser is defined like this:
newtype Parser a = Parser (String -> [(a, String)])
So I CAN give it a Verb type
but this is where I run into a problem....
I've written a Parser called keyword
keyword :: Parser Verb keyword = do x <- many1 letter
case reads x of [(verb,"")] -> return verb _ -> fail "No verb" fails gracefully (assuming your Monad instance for Parser has fail _ = Parser (\_ -> []) ).
return (read x)
(read this as "take-at-least-one-alphabetic-letter-and-convert-to-a-Verb-type")
which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt.
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.
You could try guessing what the user meant (cf. Levenshtein distance) for added comfort. Or you could ask for corrected input immediately when parsing an input fails. With the graceful failing of the parse as above, that doesn't need exceptions. If you think catching exceptions might be preferable after all, take a look at Control.Exception.
I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context.
Thanks
Mark Spezzano

Hi Mark,
On Sun, Jan 17, 2010 at 5:30 AM, Mark Spezzano
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Your basic idea to use a datatype is a good one. You just need to implement it in a slightly different way. For example, you could write a function: string :: String -> Parser () Given a string, this function returns a parser that will try to recognize the string in the input. If successful, the parser returns a single trivial result, otherwise it fails (i.e. returns an empty list of result). You will also need a function, say (<+>): (<+>) :: Parser a -> Parser a -> Parser a This function will apply two parser two the same input and combine their results. Now you can write your verb parser: verb :: Parser Verb verb = (string "jump" >> return Jump) <+> ((string "get" <+> string "take") >> return Get) -- supports synonyms <+> ... etc .. Hope that this helps. -Iavor PS: By the way, there are a number of libraries that already implement such basic "parser combinators" so you can use one of them if you are not interested in the actual low level details of how the parser works. One such library is "parsimony", another is "parsec".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.

Hi Mark,
I recently ported Conrad Barski's 'Casting SPELs in Lisp' to Haskell (a text
adventure game).
I had some of these problems as well, and you can find my code on Hackage
(the package is called Advgame).
Some things in there might be of some help.
Cheers,
- Tim
On Sun, Jan 17, 2010 at 7:30 AM, Mark Spezzano wrote: Hi, I am writing a Text Adventure game in Haskell (like Zork) I have all of the basic parser stuff written as described in Hutton's
Programming in Haskell and his associated papers. (I'm trying to avoid using
3rd party libraries, so that I can learn this myself) Everything that I have works (so far...) except for the following problem: I want to define a grammar using a series of Verbs like this: data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read) and then have my parser "get" one of these Verb tokens if possible;
otherwise it should do something (?) else like give an error message stating
"I don't know that command" Now, Hutton gives examples of parsing strings into string whereas I want to
parse Strings into my Verbs So, if the user types "get sword" then it will tokenise "get" as type
Verb's data constructor Get and perhaps "sword" into a Noun called Sword My parser is defined like this: newtype Parser a = Parser (String -> [(a, String)]) So I CAN give it a Verb type but this is where I run into a problem.... I've written a Parser called keyword keyword :: Parser Verb
keyword = do x <- many1 letter
return (read x) (read this as
"take-at-least-one-alphabetic-letter-and-convert-to-a-Verb-type") which DOES work provided that the user types in one of my Verbs. If they
don't, well, the whole thing fails with an Exception and halts processing,
returning to GHCi prompt. Question: Am I going about this the right way? I want to put together lots
of "data" types like Verb and Noun etc so that I can build a kind of "BNF
grammar". Question: If I am going about this the right way then what do I about the
"read x" bit failing when the user stops typing in a recognised keyword. I
could catch the exception, but typing an incorrect sentence is just a typo,
not really appropriate for an exception, I shouldn't think. If it IS
appropriate to do this in Haskell, then how do I catch this exception and
continue processing. I thought that exceptions should be for exceptional circumstances, and it
would seem that I might be misusing them in this context. Thanks Mark Spezzano _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

How about using one of the existing libraries, in this case uu- parsinglib: module Parse where import Text.ParserCombinators.UU.Parsing import Text.ParserCombinators.UU.Examples data Verb = Go | Get | Jump | Climb | Give deriving (Show) pCommand :: Pars String pCommand = foldr (<|>) pFail (map str2com [(Go, "G0"), (Get, "Get"), (Jump, "Jump"), (Give, "Climb"), (Climb, "Give")]) str2com (comm, str) = show comm <$ pToken str and then (the show is for demonstration purposes only; not the swap in the last two elements in the list) *Parse> :load "../Test.hs" [1 of 1] Compiling Parse ( ../Test.hs, interpreted ) Ok, modules loaded: Parse. *Parse> test pCommand "Go" ("Go",[]) *Parse> test pCommand "G0" ("Go",[ Deleted '0' at position 1 expecting 'o', Inserted 'o' at position 2 expecting 'o']) *Parse> test pCommand "o" ("Go",[ Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']]) *Parse> test pCommand "Clim" ("Give",[ Inserted 'b' at position 4 expecting 'b']) *Parse> On 17 jan 2010, at 14:30, Mark Spezzano wrote:
Hi,
I am writing a Text Adventure game in Haskell (like Zork)
I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself)
Everything that I have works (so far...) except for the following problem:
I want to define a grammar using a series of Verbs like this:
data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read)
and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command"
Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs
So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword
My parser is defined like this:
newtype Parser a = Parser (String -> [(a, String)])
So I CAN give it a Verb type
but this is where I run into a problem....
I've written a Parser called keyword
keyword :: Parser Verb keyword = do x <- many1 letter return (read x)
(read this as "take-at-least-one-alphabetic-letter-and-convert-to-a- Verb-type")
which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt.
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.
I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context.
Thanks
Mark Spezzano
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

How about using one of the existing libraries, in this case uu- parsinglib: module Parse where import Text.ParserCombinators.UU.Parsing import Text.ParserCombinators.UU.Examples data Verb = Go | Get | Jump | Climb | Give deriving (Show) pCommand :: Pars String pCommand = foldr (<|>) pFail (map str2com [(Go, "Go"), (Get, "Get"), (Jump, "Jump"), (Give, "Climb"), (Climb, "Give")]) str2com (comm, str) = show comm <$ pToken str and then (the show is for demonstration purposes only; not the swap in the last two elements in the list) *Parse> :load "../Test.hs" [1 of 1] Compiling Parse ( ../Test.hs, interpreted ) Ok, modules loaded: Parse. *Parse> test pCommand "Go" ("Go",[]) *Parse> test pCommand "G0" ("Go",[ Deleted '0' at position 1 expecting 'o', Inserted 'o' at position 2 expecting 'o']) *Parse> test pCommand "o" ("Go",[ Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']]) *Parse> test pCommand "Clim" ("Give",[ Inserted 'b' at position 4 expecting 'b']) *Parse> On 17 jan 2010, at 14:30, Mark Spezzano wrote:
Hi,
I am writing a Text Adventure game in Haskell (like Zork)
I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself)
Everything that I have works (so far...) except for the following problem:
I want to define a grammar using a series of Verbs like this:
data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read)
and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command"
Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs
So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword
My parser is defined like this:
newtype Parser a = Parser (String -> [(a, String)])
So I CAN give it a Verb type
but this is where I run into a problem....
I've written a Parser called keyword
keyword :: Parser Verb keyword = do x <- many1 letter return (read x)
(read this as "take-at-least-one-alphabetic-letter-and-convert-to-a- Verb-type")
which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt.
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.
I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context.
Thanks
Mark Spezzano
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The original author said he did not want to use existing parser
libraries, but write it himself for learning. After I read
"introduction to functional programming" from Bird, I closed the book,
and re-wrote the parser from scratch again, and seeing how all these
pieces come together was such a wonderful experience that I would
recommend everyone to this once instead of immediately using an
existing library :-)
It seems Marks parser definition lacks error information. It's been a
while since I played with Haskell, but if I recall correctly, you
could define a parser with backtracking that carries errors as:
type Error = String
newtype Parser a = Parser (String -> Either Error [(a, String)])
or was it
newtype Parser a = Parser (String -> [(Either Error a, String)])
in any case, when combining parsers using >>=, the errors must be propagated.
As you can see, I forgot the correct solution myself, so now I would
indeed use a library, since I know I could do it once ;)
On Tue, Jan 19, 2010 at 5:31 PM, S.Doaitse Swierstra
How about using one of the existing libraries, in this case uu-parsinglib:
module Parse where
import Text.ParserCombinators.UU.Parsing import Text.ParserCombinators.UU.Examples
data Verb = Go | Get | Jump | Climb | Give deriving (Show)
pCommand :: Pars String pCommand = foldr (<|>) pFail (map str2com [(Go, "Go"), (Get, "Get"), (Jump, "Jump"), (Give, "Climb"), (Climb, "Give")])
str2com (comm, str) = show comm <$ pToken str
and then (the show is for demonstration purposes only; not the swap in the last two elements in the list)
*Parse> :load "../Test.hs" [1 of 1] Compiling Parse ( ../Test.hs, interpreted ) Ok, modules loaded: Parse. *Parse> test pCommand "Go" ("Go",[]) *Parse> test pCommand "G0" ("Go",[ Deleted '0' at position 1 expecting 'o', Inserted 'o' at position 2 expecting 'o']) *Parse> test pCommand "o" ("Go",[ Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']]) *Parse> test pCommand "Clim" ("Give",[ Inserted 'b' at position 4 expecting 'b']) *Parse>
On 17 jan 2010, at 14:30, Mark Spezzano wrote:
Hi,
I am writing a Text Adventure game in Haskell (like Zork)
I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself)
Everything that I have works (so far...) except for the following problem:
I want to define a grammar using a series of Verbs like this:
data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read)
and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command"
Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs
So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword
My parser is defined like this:
newtype Parser a = Parser (String -> [(a, String)])
So I CAN give it a Verb type
but this is where I run into a problem....
I've written a Parser called keyword
keyword :: Parser Verb keyword = do x <- many1 letter return (read x)
(read this as "take-at-least-one-alphabetic-letter-and-convert-to-a-Verb-type")
which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt.
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.
I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context.
Thanks
Mark Spezzano
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

When cycling home I realised it could even be shorter: module Parse where import Text.ParserCombinators.UU.Parsing import Text.ParserCombinators.UU.Examples data Verb = Go | Get | Jump | Climb | Give deriving (Show) pCommand :: Pars Verb pCommand = foldr (\ c r -> c <$ pToken (show c) <|> r) pFail [Go , Get , Jump , Climb , Give] *Parse> test pCommand "Go" Loading package syb ... linking ... done. Loading package base-3.0.3.1 ... linking ... done. Loading package array-0.2.0.0 ... linking ... done. Loading package filepath-1.1.0.2 ... linking ... done. Loading package old-locale-1.0.0.1 ... linking ... done. Loading package old-time-1.0.0.2 ... linking ... done. Loading package unix-2.3.2.0 ... linking ... done. Loading package directory-1.0.0.3 ... linking ... done. Loading package process-1.0.1.1 ... linking ... done. Loading package random-1.0.0.1 ... linking ... done. Loading package haskell98 ... linking ... done. Loading package uu-parsinglib-2.3.1 ... linking ... done. (Go,[]) se> *Parse> test pCommand "Clim" (Climb,[ Inserted 'b' at position 4 expecting 'b']) *Parse> On 19 jan 2010, at 17:31, S.Doaitse Swierstra wrote:
How about using one of the existing libraries, in this case uu- parsinglib:
module Parse where
import Text.ParserCombinators.UU.Parsing import Text.ParserCombinators.UU.Examples
data Verb = Go | Get | Jump | Climb | Give deriving (Show)
pCommand :: Pars String pCommand = foldr (<|>) pFail (map str2com [(Go, "Go"), (Get, "Get"), (Jump, "Jump"), (Give, "Climb"), (Climb, "Give")])
str2com (comm, str) = show comm <$ pToken str
and then (the show is for demonstration purposes only; not the swap in the last two elements in the list)
*Parse> :load "../Test.hs" [1 of 1] Compiling Parse ( ../Test.hs, interpreted ) Ok, modules loaded: Parse. *Parse> test pCommand "Go" ("Go",[]) *Parse> test pCommand "G0" ("Go",[ Deleted '0' at position 1 expecting 'o', Inserted 'o' at position 2 expecting 'o']) *Parse> test pCommand "o" ("Go",[ Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']]) *Parse> test pCommand "Clim" ("Give",[ Inserted 'b' at position 4 expecting 'b']) *Parse>
On 17 jan 2010, at 14:30, Mark Spezzano wrote:
Hi,
I am writing a Text Adventure game in Haskell (like Zork)
I have all of the basic parser stuff written as described in Hutton's Programming in Haskell and his associated papers. (I'm trying to avoid using 3rd party libraries, so that I can learn this myself)
Everything that I have works (so far...) except for the following problem:
I want to define a grammar using a series of Verbs like this:
data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show, Read)
and then have my parser "get" one of these Verb tokens if possible; otherwise it should do something (?) else like give an error message stating "I don't know that command"
Now, Hutton gives examples of parsing strings into string whereas I want to parse Strings into my Verbs
So, if the user types "get sword" then it will tokenise "get" as type Verb's data constructor Get and perhaps "sword" into a Noun called Sword
My parser is defined like this:
newtype Parser a = Parser (String -> [(a, String)])
So I CAN give it a Verb type
but this is where I run into a problem....
I've written a Parser called keyword
keyword :: Parser Verb keyword = do x <- many1 letter return (read x)
(read this as "take-at-least-one-alphabetic-letter-and-convert-to-a- Verb-type")
which DOES work provided that the user types in one of my Verbs. If they don't, well, the whole thing fails with an Exception and halts processing, returning to GHCi prompt.
Question: Am I going about this the right way? I want to put together lots of "data" types like Verb and Noun etc so that I can build a kind of "BNF grammar".
Question: If I am going about this the right way then what do I about the "read x" bit failing when the user stops typing in a recognised keyword. I could catch the exception, but typing an incorrect sentence is just a typo, not really appropriate for an exception, I shouldn't think. If it IS appropriate to do this in Haskell, then how do I catch this exception and continue processing.
I thought that exceptions should be for exceptional circumstances, and it would seem that I might be misusing them in this context.
Thanks
Mark Spezzano
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (9)
-
Daniel Fischer
-
Iavor Diatchki
-
Luke Palmer
-
Mark Spezzano
-
Peter Verswyvelen
-
S. Doaitse Swierstra
-
S.Doaitse Swierstra
-
Stephen Tetley
-
Tim Wawrzynczak