
Haskellians, The code pasted in below causes Happy to return parE when invoked with happy rparse.y -i . Is there anyway to get Happy to give me just a wee bit more info as to what might be causing the parE (which i interpret a 'parse error'). Best wishes, --greg { module Main where } %name rparse %tokentype { Token } %error { parseError } %token '{' { TokenLCurly } '}' { TokenRCurly } '[' { TokenLSquare } ']' { TokenRSquare } '(' { TokenLRound } ')' { TokenRRound } '@' { TokenAt } ',' { TokenComma } ';' { TokenSemi } lquote { TokenLQuote } rquote { TokenRQuote } %% Molecule : '{' '}' { Zero } | Name Reagent { Locate $1 $2 } | '@' Name { Decode $2 } ReagentList : Reagent { [ $1 ] } | ReagentList ';' Reagent { $1 ++ [$3] } Reagent : '?' '(' NameList ')' Mixture { Abstraction $3 $5 } | '[' Mixture ']' { Concretion $2 } Mixture : Molecule { Mix [ $1 ] } | '{' ReagentList '}' { Mix $2 } NameList : Name { [ $1 ] } | NameList ',' Name { $1 ++ [$3] } Name : lquote Mixture rquote { Name $2 } { parseError :: [Token] -> a parseError _ = error "Parse error" data Molecule = Zero | Locate Name Reagent | Decode Name deriving (Eq, Show) data Reagent = Abstraction [Name] Mix | Concretion Mix deriving (Eq, Show) data Mix = Mix [Molecule] deriving (Eq, Show) data Name = Name Mix deriving (Eq, Show) data Token = TokenLQuote | TokenRQuote | TokenLCurly | TokenRCurly | TokenLSquare | TokenRSquare | TokenLRound | TokenRRound | TokenComma | TokenSemi | TokenAt deriving Show lexer :: String -> [Token] lexer [] = [] lexer (c:cs) | isSpace c = lexer cs lexer ('{':cs) = TokenLCurly : lexer cs lexer ('}':cs) = TokenRCurly : lexer cs lexer ('[':cs) = TokenLSquare : lexer cs lexer (']':cs) = TokenRSquare : lexer cs lexer ('(':cs) = TokenLRound : lexer cs lexer (')':cs) = TokenRRound : lexer cs lexer (',':cs) = TokenComma : lexer cs lexer (';':cs) = TokenSemi : lexer cs lexer ('@':cs) = TokenAt : lexer cs lexer ('<':'<':cs) = TokenLQuote : lexer cs lexer ('>':'>':cs) = TokenRQuote : lexer cs main = getContents >>= print . rparse . lexer } -- L.G. Meredith Managing Partner Biosimilarity LLC 505 N 72nd St Seattle, WA 98103 +1 206.650.3740 http://biosimilarity.blogspot.com

Greg Meredith wrote:
Haskellians,
The code pasted in below causes Happy to return parE when invoked with happy rparse.y -i . Is there anyway to get Happy to give me just a wee bit more info as to what might be causing the parE (which i interpret a 'parse error').
Please grab a more recent version of Happy from darcs: http://darcs.haskell.org/happy the parE thing was a bug in the error handling introduced in the last release. You'll need Cabal-1.2 in order to build the latest Happy. Cheers, Simon

Simon,
Cheers. i solved the problem before i saw your email. The Happy i got was a
result of invoking
port install happy
What's the drift between macports and happy versions? Is there a way of
using Happy without being on or even near the cutting edge of development?
Best wishes,
--greg
On 9/13/07, Simon Marlow
Greg Meredith wrote:
Haskellians,
The code pasted in below causes Happy to return parE when invoked with happy rparse.y -i . Is there anyway to get Happy to give me just a wee bit more info as to what might be causing the parE (which i interpret a 'parse error').
Please grab a more recent version of Happy from darcs:
http://darcs.haskell.org/happy
the parE thing was a bug in the error handling introduced in the last release. You'll need Cabal-1.2 in order to build the latest Happy.
Cheers, Simon
-- L.G. Meredith Managing Partner Biosimilarity LLC 505 N 72nd St Seattle, WA 98103 +1 206.650.3740 http://biosimilarity.blogspot.com

On 9/13/07, Greg Meredith
Cheers. i solved the problem before i saw your email. The Happy i got was a result of invoking
port install happy
What's the drift between macports and happy versions? Is there a way of using Happy without being on or even near the cutting edge of development?
You can freely intermix bits and pieces installed via port and via traditional (e.g., runghc Setup.hs install or make install) means, provided that you have the paths set up properly. -- paulrbrown@gmail.com http://mult.ifario.us/
participants (3)
-
Greg Meredith
-
Paul Brown
-
Simon Marlow