[Haskell-cafe] Prettyprinting infix expressions with HughesPJ

Stefan O'Rear stefanor at cox.net
Tue Apr 10 20:11:38 EDT 2007


On Wed, Apr 11, 2007 at 01:53:49AM +0200, Alfonso Acosta wrote:
> 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).

Hehe.  We're happy to solve subproblems.  It's the
copied-verbatim-from-the-book homework problems we mind. 

> >
> >"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).

It's pretty easy to make this happen - just pretend (-) is
non-associative. 

> >(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.

Suppose we receive Lit 1 :+: (Lit 2 :+: Lit 3).  Would you rather read
1 + 2 + 3 or 1 + (2 + 3)? 

NB: Beware of floating points!

> >> 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 :)

Stefan


More information about the Haskell-Cafe mailing list