[Haskell-cafe] Parsers for Text Adventures; in one line

S. Doaitse Swierstra doaitse at swierstra.net
Tue Jan 19 17:12:48 EST 2010


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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list