[Haskell-cafe] Re: Backpatching

ChrisK haskell at list.mightyreason.com
Wed Aug 1 05:32:01 EDT 2007


Thomas Conway wrote:
> One of the things that gets messy is that in lots of places you can
> put either a thing or a reference to a thing (i.e. the name of a thing
> defined elsewhere). For example, consider the production:
> 
>     NamedNumber ::= identifier "(" SignedNumber ")"
>                   | identifier "(" DefinedValue ")"
> 

I like solving this with either a (WriterT Parser) or using the Parsec state to
lazily access the final mapping.  Here is a working Toy example where 'finalMap'
is used during the parsing.  Parsec was a bit too strict with the return of
'parseVal' so I had to use a (data Box) to make it lazy:


> import Text.ParserCombinators.Parsec
> 
> import Data.Maybe
> import qualified Data.Map as M
> 
> data Box a = Box {unBox :: a}
> 
> input = unlines $
>   [ "name(ref)"
>   , "ref=7"
>   ]
> 
> data Toy = Toy String Int deriving (Show)
> 
> myParse s = toys where
>   result = runParser parser M.empty "Title" s
>   toys = either Left (Right . fst) result
> 
>   lookupRef r = Box (finalMap M.! r)
>     where finalMap = either undefined snd result
> 
>   parser = do
>     maybeToyList <- many parseLine
>     defMap <- getState
>     return (catMaybes maybeToyList,defMap)
> 
>   parseLine = try parseToy <|> parseDef <|> (char '\n' >> return Nothing)
> 
>   parseToy = do
>     name <- many1 letter
>     val <- between (char '(') (char ')') (try parseVal <|> parseRef)
>     return (Just (Toy name (unBox val)))
> 
>   parseVal = do 
>     s <- many1 digit
>     return (Box (read s))
> 
>   parseRef = do
>     s <- many1 letter
>     return (lookupRef s)
> 
>   parseDef = do
>     s <- many1 letter
>     char '='
>     v <- parseVal
>     defMap <- getState
>     let defMap' = M.insert s (unBox v) defMap
>     setState $! defMap'
>     return Nothing


When I run it in ghci I get:

> *Main> myParse input
> Right [Toy "name" 7]

Cheers,
  Chris



More information about the Haskell-Cafe mailing list