[Haskell] Haskell implementation of infixr and infixl/priorities
Mark P Jones
mpj at cse.ogi.edu
Mon Oct 25 03:46:32 EDT 2004
Hi Peter,
| I´m progarmming a parser for functional programs. Now
| I want to implement the infixL and infixR feature to increase
| the readability of the code. I would be very glad if anyone
| can send me some information about the implementation of
| this feature of the Haskell parser or where I can find
| something about it.
The comment shown below is taken from the Hugs sources (the
file static.c) and might help to answer your questions.
Hope this helps,
Mark
/*
--------------------------------------------------------------------------
* Dealing with infix operators:
*
* Expressions involving infix operators or unary minus are parsed as
* elements of the following type:
*
* data InfixExp = Only Exp | Neg InfixExp | Infix InfixExp Op Exp
*
* (The algorithms here do not assume that negation can be applied only
once,
* i.e., that - - x is a syntax error, as required by the Haskell report.
* Instead, that restriction is captured by the grammar itself, given
above.)
*
* There are rules of precedence and grouping, expressed by two functions:
*
* prec :: Op -> Int; assoc :: Op -> Assoc (Assoc = {L, N, R})
*
* InfixExp values are rearranged accordingly when a complete expression
* has been read using a simple shift-reduce parser whose result may be
taken
* to be a value of the following type:
*
* data Exp = Atom Int | Negate Exp | Apply Op Exp Exp | Error String
*
* The machine on which this parser is based can be defined as follows:
*
* tidy :: InfixExp -> [(Op,Exp)] -> Exp
* tidy (Only a) [] = a
* tidy (Only a) ((o,b):ss) = tidy (Only (Apply o a b)) ss
* tidy (Infix a o b) [] = tidy a [(o,b)]
* tidy (Infix a o b) ((p,c):ss)
* | shift o p = tidy a ((o,b):(p,c):ss)
* | red o p = tidy (Infix a o (Apply p b c)) ss
* | ambig o p = Error "ambiguous use of operators"
* tidy (Neg e) [] = tidy (tidyNeg e) []
* tidy (Neg e) ((o,b):ss)
* | nshift o = tidy (Neg (underNeg o b e)) ss
* | nred o = tidy (tidyNeg e) ((o,b):ss)
* | nambig o = Error "illegal use of negation"
*
* At each stage, the parser can either shift, reduce, accept, or error.
* The transitions when dealing with juxtaposed operators o and p are
* determined by the following rules:
*
* shift o p = (prec o > prec p)
* || (prec o == prec p && assoc o == L && assoc p == L)
*
* red o p = (prec o < prec p)
* || (prec o == prec p && assoc o == R && assoc p == R)
*
* ambig o p = (prec o == prec p)
* && (assoc o == N || assoc p == N || assoc o /= assoc p)
*
* The transitions when dealing with juxtaposed unary minus and infix
* operators are as follows. The precedence of unary minus (infixl 6) is
* hardwired in to these definitions, as it is to the definitions of the
* Haskell grammar in the official report.
*
* nshift o = (prec o > 6)
* nred o = (prec o < 6) || (prec o == 6 && assoc o == L)
* nambig o = prec o == 6 && (assoc o == R || assoc o == N)
*
* An InfixExp of the form (Neg e) means negate the last thing in
* the InfixExp e; we can force this negation using:
*
* tidyNeg :: OpExp -> OpExp
* tidyNeg (Only e) = Only (Negate e)
* tidyNeg (Infix a o b) = Infix a o (Negate b)
* tidyNeg (Neg e) = tidyNeg (tidyNeg e)
*
* On the other hand, if we want to sneak application of an infix operator
* under a negation, then we use:
*
* underNeg :: Op -> Exp -> OpExp -> OpExp
* underNeg o b (Only e) = Only (Apply o e b)
* underNeg o b (Neg e) = Neg (underNeg o b e)
* underNeg o b (Infix e p f) = Infix e p (Apply o f b)
*
* As a concession to efficiency, we lower the number of calls to syntaxOf
* by keeping track of the values of sye, sys throughout the process. The
* value APPLIC is used to indicate that the syntax value is unknown.
*
------------------------------------------------------------------------*/
More information about the Haskell
mailing list