[Ticket #2393] Text.PrettyPrint.HughesPJ: Bug fixes,
performance improvement
Thorkil Naur
naur at post11.tele.dk
Fri Jul 4 09:13:54 EDT 2008
Hello Benedikt,
On Thursday 26 June 2008 20:40, Benedikt Huber wrote:
> Thorkil Naur schrieb:
> > Hello Benedikt,
> >
> > Thanks for all this. From memory, notes, and (last resort) trac search,
the
> > HughesPJ-related trac tickets on the GHC trac are:
> >
> > #669 negative indentation in Text.PrettyPrint.HughesPJ
> > #1176 Infinite loop when printing error message
> > #1217 Add zeroText to Text.PrettyPrint.HughesPJ
> > #1337 Fix wrong indentation from Text.PrettyPrint.HughesPJ fill (fcat and
> > fsep)
> >
> Hello,
> I've added a comment to #2393 commenting those bugs: #669 wontfix,
I suggest to add documentation as suggested by Simon PJ and then close it.
> ...
> #1176 propably fixed.
I don't think so: The infinite loop is gone, but the GHC version of the
pretty-printing library still has the error reported as #1337 against the
external library (see the comments that I added to #1176.).
>
> So, there is one open issue: the specification of fill. Note that the
> old specification is flawed and needs to be fixed anyway.
>
> Here's the cleaned up, documented version. It looks implementation
> oriented, but is far simpler than the actual implementation.
>
> -- Revised Specification:
>
> -- {- start paragraph fill at column 0 -}
> -- fill g docs = fill' 0 docs
> --
> -- {- base cases -}
> -- fill' col [] = []
> -- fill' col [p] = [p]
> --
> -- {- either put p2 beside p1, or below p1 -}
> -- fill' col (p1:p2:ps) =
> -- {- precondition for p1 beside p2: p1,p2 span only one line -}
> -- {- As we build (p1 <> p2), remove the nesting of p2 -}
> -- oneLiner p1
> -- <g>
> -- fill' (col + length p1 + gap g)
> -- (elideNests (oneLiner p2) : ps)
> -- `union`
> -- {- put p2 below p1; p2 should be aligned with the first
> -- argument of fill, which is col columns to the left of p1 -}
> -- p1
> -- $*$
> -- nest (-col) (fill' 0 (p2:ps))
> --
> -- {- width of space -}
> -- gap g = if g then 1 else 0
> --
> --
> -- $*$ is defined for layouts (One-Layout Documents) as
> --
> -- layout1 $*$ layout2 | isOneLiner layout1 = layout1 $+$ layout2
> -- | otherwise = layout1 $$ layout2
> --
> -- without the the first case, we would violate the one-line lookahead
> -- invariant
>
> The specification of fill' - left alone elideNests and $*$ - does not
> add any complexity, it is exactly what a paragraph fill should do.
>
> elideNests is an improvement - it makes it possible to have nesting in
> the arguments (otherwise, fill fails with nested arguments).
>
> $*$ is a "feature" in the current implementation:
> It allows overlapping in certain situations.
>
> Consider
> fill |a| , |...c|
> |b| |...d|
> Without $*$ ($+$) we would get
> |a|
> |b|
> |...c|
> |...d|
> Using $*$ we get
> |a|
> |b..c|
> |...d|
>
> I do not know wheter this might be useful - it is an extra feature
> rarely used I suppose ??
>
> Note that the specification of fill has to be changed anyway, either
> with $+$ or with $*$.
> ...
> > On Wednesday 25 June 2008 14:41, Benedikt Huber wrote:
> >> ...
> >> thorkil: Can you help me with a simplified test case (pretty printer
> >> only) of Bug #1176 ?
> >
> > #1176 is a case of #1337 for the internal GHC version of the HughesPJ
library
> > and I expect a fix of #1337 to be applicable to the internal GHC library,
> > hence fixing #1176. So I expect the failing cases for #1337 to fail for
#1176
> > as well, but being, unfortunately, somewhat less easily exercised.
> Could you have a look at Bug1176a.hs attached to #1337 ? Is this what
> happened ?
This looks like the same thing, yes, so a correstion to the GHC version of the
pretty-printing library like the one you supplied for #1337 seems called for.
> ...
> As you seem to know the pretty printer library well, it would be great
> if you could comment on the revised specification of fill.
The new specification certainly explained things for me that I had not
understood earlier, so it is definitely an improvement.
> ...
Best regards
Thorkil
More information about the Libraries
mailing list