[Haskell-cafe] Prettyprinting infix expressions with HughesPJ

Alfonso Acosta alfonso.acosta at gmail.com
Tue Apr 10 19:53:49 EDT 2007


On 4/11/07, Stefan O'Rear <stefanor at cox.net> wrote:
> Your use of 'have' is slightly suspicious here.  That said, the rest
> of your problem looks very un-homework-y, so I'll look at it.

It's for my masters thesis (big piece of badly-specified homework  if
you want to think about it like that :)). I used "have" cause I'm
coding an embedded VHDL compiler and I really "have" to pretty print
VHDL in the backend :) (the more readable the code I get the better).

>
> "Associativity" is ambiguous here.  Do you mean:
> 1 + 2 + 3   =>  (1 + 2) + 3      (Associativity of parsing)

This is what I mean. Say "-" is right associative in the target
language, that allows to remove the parenthesis of the following
expression "1 - (1 - 2)" and just write "1 - 1 - 2", but probably the
code would be less readable since a human doesn't normally take that
in account (I tend to forget those things and keep writing parenthesis
all the time anyway).

> (1 + 2) + 3 == 6 == 1 + (2 + 3)  (Associativity of functions)

I don't see how taking this in account would make the output more readable.



> > data Expr = Val String |
> >                  -- Binary operators (using infix constructors)
> >                  Expr :+: Expr  | Expr  :-: Expr  |
> >                  Expr :*: Expr  | Expr  :/: Expr  |
> >                  Expr :^: Expr |
> >                  -- Unary operators
> >                  Negate Expr
> >
> >
> > I'm using HughesPJ for the rest of my AST (not just expressions) but
> > the library doesn't provide any mechanism to help coding this kind of
> > prettyprinter so I decided to simply use the standard showsPrec and
> > then feed HughesPJ with the obtained text.
>
> That seems very counter-productive.  By using showsPrec, you lose all
> the information that could be used to guide line breaks.

Yes, you're totally right. Thanks a lot for your code :)

> It would be
> far better to do it yourself.  Note that the method I am about to show
> is exactly the same as that used by the standard showsPrec:
>
> -- let +, - have infixl 1
> -- let *, / have infixl 2
> -- let ^ have infixr 3
> -- let uminus have (nofix) 4
>
> pprExpr :: Int  -- ^ Precedence context - if you're like me no
>                 --   explanation of this will make more sense than the
>                 --   code
>         -> Expr -> Doc
> pprExpr cx (Val str) = text str
> pprExpr cx (a :+: b) = cparen (cx >= 1) $ pprExpr 1 a <+> char '+' <+> pprExpr 1 b
> pprExpr cx (a :-: b) = cparen (cx >= 1) $ pprExpr 1 a <+> char '+' <+> pprExpr 1 b
> pprExpr cx (a :*: b) = cparen (cx >= 2) $ pprExpr 2 a <+> char '+' <+> pprExpr 2 b
> pprExpr cx (a :/: b) = cparen (cx >= 2) $ pprExpr 2 a <+> char '+' <+> pprExpr 2 b
> pprExpr cx (a :^: b) = cparen (cx >= 3) $ pprExpr 3 a <+> char '+' <+> pprExpr 3 b
> pprExpr cx (Negate a) = cparen (cx >= 4) $ char '-' <+> pprExpr 4 a
>
> -- this is provided for ShowS under the name showsParen, but
> -- unfortunately does not exist for Doc standardly
> cparen :: Bool -> Doc -> Doc
> cparen False = id
> cparen True = parens
>
> > showsPrec helps to take advantage of the precedence information.
> > However, I don't find a way to remove parenthesis according to
> > associativity.
>
> A simple modification of the above code will do it:
>
> pprExpr cx (Val str) = text str
> pprExpr cx (a :+: b) = cparen (cx >= 1) $ pprExpr 0 a <+> char '+' <+> pprExpr 1 b
> pprExpr cx (a :-: b) = cparen (cx >= 1) $ pprExpr 0 a <+> char '-' <+> pprExpr 1 b
> pprExpr cx (a :*: b) = cparen (cx >= 2) $ pprExpr 1 a <+> char '*' <+> pprExpr 2 b
> pprExpr cx (a :/: b) = cparen (cx >= 2) $ pprExpr 1 a <+> char '/' <+> pprExpr 2 b
> pprExpr cx (a :^: b) = cparen (cx >= 3) $ pprExpr 3 a <+> char '^' <+> pprExpr 2 b
> pprExpr cx (Negate a) = cparen (cx >= 4) $ char '+' <+> pprExpr 4 a
>
> Handling line breaks is left as an excercise for the reader.
>
> > I'm sure this kind of prettyprinting has been already done zillions of
> > times in Haskell. Any suggestions?
>
> Stefan
>


More information about the Haskell-Cafe mailing list