[Haskell-cafe] Parsec operator with letter problem
Reto Kramer
kramer at acm.org
Fri Mar 31 18:44:02 EST 2006
Great! Thanks for the revision Daniel. If you're ever in San
Francisco, please do ping me - I sure owe you lunch!
- Reto
On Mar 31, 2006, at 3:14 PM, Daniel Fischer wrote:
> Am Freitag, 31. März 2006 15:24 schrieb Daniel Fischer:
>> Hi,
>>
>> probably somebody else has already come up with something better, but
>> still...
>>
>> I surmise that you have two kinds of infix-operators,
>> 1. dot-like operators, made up entirely of symbols (^!$%&/\,.:;#+-
>> ~* ...)
>> 2. LaTeX-command-like operators, starting with a backslash and then
>> followed by a nonempty sequence of letters (or possibly alphanumeric
>> characters).
>>
>> Then the following helps:
>>
>> import Data.Char (isAlpha)
>>
>> lexer = lexer0{P.reservedOp = rOp}
>> where
>> lexer0 = P.makeTokenParser testdef
>> resOp0 = P.reservedOp lexer0
>> resOp1 name =
>> case name of
>> ('\\':cs@(_:_))
>>
>> | all isAlpha cs -> do string name
>>
>> notFollowedBy letter <?>
>> ("end of " ++ show
>> name)
>> _ -> fail (show name ++ " no good reservedOp")
>> rOp name = lexeme $ try $ resOp0 name <|> resOp1 name
>> lexeme p = do { x <- p; P.whiteSpace lexer0; return x }
>
> Noho, that's not right, that parses "a\inn" as
> InfixExpr OP_In (Ident "a") (Ident "n"),
> because resOp1 is never used, which we don't want, so:
>
> lexer = lexer0{P.reservedOp = rOp}
> where
> lexer0 = P.makeTokenParser testdef
> resOp0 = P.reservedOp lexer0
> resOp1 name = do string name
> notFollowedBy letter <?> ("end of " ++
> show name)
> rOp name = lexeme $ try $
> case name of
> ('\\':cs@(_:_)) | all isAlpha cs ->
> resOp1 name
> _ -> resOp0 name
> lexeme p = do { x <- p; P.whiteSpace lexer0; return x }
>
> Now:
> dafis at linux:~/Documents/haskell/Reto> cat input
> a.n
> dafis at linux:~/Documents/haskell/Reto> reto input
> InfixExpr OP_Dot (Ident "a") (Ident "n")
> dafis at linux:~/Documents/haskell/Reto> cat input
> a\inn
> dafis at linux:~/Documents/haskell/Reto> reto input
> Ident "a"
> dafis at linux:~/Documents/haskell/Reto> cat input
> a\in n
> dafis at linux:~/Documents/haskell/Reto> reto input
> InfixExpr OP_In (Ident "a") (Ident "n")
>
> That's better.
>>
>> testdef = emptyDef
>> { P.identStart = letter <|> char '_'
>> , P.identLetter = alphaNum <|> char '_'
>> , P.opStart = oneOf $ nub $
>> map (\s -> head s) $ P.reservedOpNames
>> testdef
>> -- , P.opLetter = oneOf (concat (P.reservedOpNames testdef))
>> , P.opLetter = oneOf symbs
>> , P.reservedOpNames = [ ".", "\\in" ] }
>> where
>> symbs = filter (not . isAlpha) . concat $ P.reservedOpNames
>> testdef
>> ---------------------------------------------------------------------
>> dafis at linux:~/Documents/haskell/Reto> cat input
>> a.n
>> dafis at linux:~/Documents/haskell/Reto> reto input
>> InfixExpr OP_Dot (Ident "a") (Ident "n")
>>
>> If you have more complicated infix operators (e.g.
>> \foo#bar:, :ouch:),
>> it won't be so easy, anyway, you have to change the definition of
>> reservedOp.
>>
>> Cheers,
>> Daniel
>
> --
>
> "In My Egotistical Opinion, most people's C programs should be
> indented six feet downward and covered with dirt."
> -- Blair P. Houghton
>
More information about the Haskell-Cafe
mailing list