Meaning of "ribbonsPerLine" at Text.PrettyPrint.HughesPJ ?

Hi, Can anyone give a good explanation of what ribbonsPerLine means? Maybe it would be better to simply ask for the meaning of ribbon in this context. The documentation is totally meaningless to me: "reibbonsPerLine: Ratio of ribbon length to line length". I asked at #haskell and frankly, I was surprised by the answer: fons: can anyone tell me what the heck does ribbonsPerLine mean in Text.PrettyPrint.HughesPJ? fons: > renderStyle style{lineLength=10, ribbonsPerLine=1} $ sep [text "foo" ,text "bar"] lambdabot: "foo bar" fons: > renderStyle style{lineLength=10, ribbonsPerLine=2} $ sep [text "foo" ,text "bar"] lambdabot: "foo\nbar" fons: ok, somehow it affects the line width ... byorgey: fons: I can't explain it, all I know is that you must set it to 1 or else it does bizarre things fons: hahah, ok fons: byorgey: that's funny considering its default value is 1.5 byorgey: if you set it to 1 then lineLength means what you think it should byorgey: fons: EXACTLY Cheers, Fons

byorgey: fons: I can't explain it, all I know is that you must set it to 1 or else it does bizarre things fons: hahah, ok fons: byorgey: that's funny considering its default value is 1.5 byorgey: if you set it to 1 then lineLength means what you think it should byorgey: fons: EXACTLY
Excellent, thanks for solving a nagging problem I couldn't be bothered to track down. I was wondering why my pretty printing was a little messed up and slightly too wide. And isn't 100 columns a bit non-standard for a default? I thought 80 columns had more traction? I know that's what my terminals are at...

On Wed, 2008-06-18 at 13:55 -0700, Evan Laforge wrote:
byorgey: fons: I can't explain it, all I know is that you must set it to 1 or else it does bizarre things fons: hahah, ok fons: byorgey: that's funny considering its default value is 1.5 byorgey: if you set it to 1 then lineLength means what you think it should byorgey: fons: EXACTLY
Excellent, thanks for solving a nagging problem I couldn't be bothered to track down. I was wondering why my pretty printing was a little messed up and slightly too wide.
And isn't 100 columns a bit non-standard for a default? I thought 80 columns had more traction? I know that's what my terminals are at...
Yeah. I'd vote for 80. That's what we use in pretty printing messages in Cabal. Duncan

On Wed, Jun 18, 2008 at 5:41 PM, Duncan Coutts
And isn't 100 columns a bit non-standard for a default? I thought 80 columns had more traction? I know that's what my terminals are at...
Yeah. I'd vote for 80. That's what we use in pretty printing messages in Cabal.
Yep, me too, I'm also using 80. I'd also vote for a default ribbonsPerLine of 1 (whatever that is).

To answer the original question (in the subject line), "The ribbon ratio is the number of times the ribbon fits into a line. The ribbon is the number of characters on a line excluding leading and trailing white spaces. " See also the original paper on which the Text.PrettyPrint.HughesPJ code is based: http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps section 7.4. The idea is that the pretty-printer should not cram lots of text into a single line, if it would look nicer split across two (shorter) lines. The ribbonsPerLine ratio is the factor that determines this level of "prettiness". A ratio of 1.0 means to cram everything into the line if you can. A larger ratio means to go for more lines, but less text on each. Somewhere between 1.2 and 1.8 is likely to be more or less pleasing: 1.0 will be ugly, 2.0 or above will look decidedly fragmented. Regards, Malcolm

Evan Laforge schrieb:
byorgey: fons: I can't explain it, all I know is that you must set it to 1 or else it does bizarre things fons: hahah, ok fons: byorgey: that's funny considering its default value is 1.5 byorgey: if you set it to 1 then lineLength means what you think it should byorgey: fons: EXACTLY
Excellent, thanks for solving a nagging problem I couldn't be bothered to track down. I was wondering why my pretty printing was a little messed up and slightly too wide.
And isn't 100 columns a bit non-standard for a default? I thought 80 columns had more traction? I know that's what my terminals are at...
Hi, The "ribbon length" is used when choosing the most beautiful layout: I'll just summarize the relevant section from John Hughes paper (http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps), which explains it very nicely: "... Using [the criterion whether the text fits on the page] alone tends to produce layouts such as
for i = 1 to 100; for j=1 to 100; for k=1 to 100; a[i][j][k]:=0;
which fits on a page {==> line-width} but cannot be described as pretty. We therefore impose an additional constraint limiting the number of characters on each line [==> ribbon-width} [...]
for i = 1 to 100 for j = 1 to 100 ... "
So the pretty printer tries to avoid sequences (ribbons) of characters which are longer than ribbon_length, when using auto layout stuff like `sep'. In the source code, we have (paraphrased)
ribbon_length = line_length / ribbonsPerLine
and
choose_nicest_layout indent p q = if p + indent fits into line_length and p fits into ribbon_length then p else q
Working example below. I'm not sure 80 characters is still standard when _pretty_-printing - the longest line in Text.PrettyPrint.HughesPJ is 109 characters wide ;) Setting the ribbon ratio to 1 essentially disables the ribbon feature. Btw: while studying the source code, I also found the cat (and sep) can be implemented in a more space efficient way (currently, cat needs to evaluate every document in a list to yield some output). Does this make sense (see below) ? cheers, benedikt -- * ribbon example
-- lineLength = 26, ribbonsPerLine = 1.5 ==> ribbonLength = 17 -- therefore, we have a line break if width-indent > 17 or width > 26 testStyle = Style { mode = PageMode, lineLength = 26, ribbonsPerLine = 1.5 } ribbonTest = renderStyle testStyle $
-- use hsep as width == 17 <= ribbonLength sep [ txt 5, txt 11 ]
-- linebreak, as width-indent = width = 18 > ribbonLength $+$ sep [ txt 5, txt 12 ]
-- use hsep, as width - indent == 17, and width == 22 < lineLength $+$ sep (map (nest 5) $ [txt 5, txt 11] )
-- linebreak, as width would be 27 > lineLength $+$ sep (map (nest 10) $ [txt 5, txt 11] )
txt :: Int -> Doc txt 0 = text "" txt k = text $ let ks = show k in (replicate (k - (length ks)) '_') ++ ks
-- * lazy variants of vcat and hcat -- you need the constructors from the HughesPJ module
vcat' = foldAbove . foldr vcomp2 empty hcat' = foldBeside . foldr hcomp2 empty
foldAbove :: Doc -> Doc foldAbove (Above Empty _ d2) = d2 foldAbove (Above d1 f d2) = Above d1 f $ foldAbove d2 foldAbove doc = doc
vcomp2 :: Doc -> Doc -> Doc vcomp2 d1 Empty = d1 -- do not match `vcomp2 Empty d1' ! vcomp2 d1 d2 = Above d1 False d2
foldBeside :: Doc -> Doc foldBeside (Beside Empty _ d2) = d2 foldBeside (Beside d1 f d2) = Beside d1 f $ foldBeside d2 foldBeside doc = doc
hcomp2 :: Doc -> Doc -> Doc hcomp2 p Empty = p hcomp2 p q = Beside p False q

Benedikt Despite the name, neither I nor John Hughes are actively maintaining this library, so if you have got some better implementations of 'cat' and 'sep', do please submit a patch. That's how it'll improve. Do test carefully! Preferably add some Quickcheck tests too. Thanks Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe- | bounces@haskell.org] On Behalf Of Benedikt Huber | Sent: 19 June 2008 13:31 | To: Evan Laforge | Cc: haskell | Subject: [Haskell-cafe] Re: Meaning of "ribbonsPerLine" at | Text.PrettyPrint.HughesPJ ? | | Evan Laforge schrieb: | >> byorgey: fons: I can't explain it, all I know is that you must set it | >> to 1 or else it does bizarre things | >> fons: hahah, ok | >> fons: byorgey: that's funny considering its default value is 1.5 | >> byorgey: if you set it to 1 then lineLength means what you think it should | >> byorgey: fons: EXACTLY | > | > Excellent, thanks for solving a nagging problem I couldn't be bothered | > to track down. I was wondering why my pretty printing was a little | > messed up and slightly too wide. | > | > And isn't 100 columns a bit non-standard for a default? I thought 80 | > columns had more traction? I know that's what my terminals are at... | | Hi, | | The "ribbon length" is used when choosing the most beautiful layout: | I'll just summarize the relevant section from John Hughes paper | (http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps), which explains it | very nicely: | | "... Using [the criterion whether the text fits on the page] alone tends | to produce layouts such as | | > for i = 1 to 100; for j=1 to 100; for k=1 to 100; a[i][j][k]:=0; | | which fits on a page {==> line-width} but cannot be described as pretty. | We therefore impose an additional constraint limiting the number of | characters on each line [==> ribbon-width} [...] | | > for i = 1 to 100 | > for j = 1 to 100 | > ... | " | | So the pretty printer tries to avoid sequences (ribbons) of characters | which are longer than ribbon_length, when using auto layout stuff like | `sep'. | | In the source code, we have (paraphrased) | | > ribbon_length = line_length / ribbonsPerLine | | and | | > choose_nicest_layout indent p q = | > if p + indent fits into line_length and p fits into ribbon_length | > then p | > else q | | Working example below. | | I'm not sure 80 characters is still standard when _pretty_-printing - | the longest line in Text.PrettyPrint.HughesPJ is 109 characters wide ;) | | Setting the ribbon ratio to 1 essentially disables the ribbon feature. | | Btw: while studying the source code, I also found the cat (and sep) can | be implemented in a more space efficient way (currently, cat needs to | evaluate every document in a list to yield some output). Does this make | sense (see below) ? | | cheers, | | benedikt | | | -- * ribbon example | | > -- lineLength = 26, ribbonsPerLine = 1.5 ==> ribbonLength = 17 | > -- therefore, we have a line break if width-indent > 17 or width > 26 | > testStyle = Style { mode = PageMode, | > lineLength = 26, | > ribbonsPerLine = 1.5 } | > ribbonTest = renderStyle testStyle $ | > | > -- use hsep as width == 17 <= ribbonLength | > sep [ txt 5, txt 11 ] | > | > -- linebreak, as width-indent = width = 18 > ribbonLength | > $+$ sep [ txt 5, txt 12 ] | > | > -- use hsep, as width - indent == 17, and width == 22 < lineLength | > $+$ sep (map (nest 5) $ [txt 5, txt 11] ) | > | > -- linebreak, as width would be 27 > lineLength | > $+$ sep (map (nest 10) $ [txt 5, txt 11] ) | > | > txt :: Int -> Doc | > txt 0 = text "" | > txt k = text $ | > let ks = show k in | > (replicate (k - (length ks)) '_') ++ ks | | | -- * lazy variants of vcat and hcat | -- you need the constructors from the HughesPJ module | | > vcat' = foldAbove . foldr vcomp2 empty | > hcat' = foldBeside . foldr hcomp2 empty | > | > foldAbove :: Doc -> Doc | > foldAbove (Above Empty _ d2) = d2 | > foldAbove (Above d1 f d2) = Above d1 f $ foldAbove d2 | > foldAbove doc = doc | > | > vcomp2 :: Doc -> Doc -> Doc | > vcomp2 d1 Empty = d1 | > -- do not match `vcomp2 Empty d1' ! | > vcomp2 d1 d2 = Above d1 False d2 | > | > foldBeside :: Doc -> Doc | > foldBeside (Beside Empty _ d2) = d2 | > foldBeside (Beside d1 f d2) = Beside d1 f $ foldBeside d2 | > foldBeside doc = doc | > | > hcomp2 :: Doc -> Doc -> Doc | > hcomp2 p Empty = p | > hcomp2 p q = Beside p False q | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello, On Wednesday 18 June 2008 22:13, Alfonso Acosta wrote:
Hi,
Can anyone give a good explanation of what ribbonsPerLine means?
Maybe it would be better to simply ask for the meaning of ribbon in this context. The documentation is totally meaningless to me: "reibbonsPerLine: Ratio of ribbon length to line length".
7.4 Choosing a Pretty Layout
Now that we have designed combinators for constructing documents with many
In the paper "The Design of a Pretty-printing Library" by John Hughes (http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps) that introduced this pretty printing library, the ribbon concept is introduced like this (apologies for the layout, please use the original .ps file for accuracy): possible layouts, it is time to discuss choosing among those alternatives. Many prettyprinters aim simply to avoid exceeding a given page width. However, we found that using this criterion alone tends to produce layouts such as
for i = 1 to 100 do for j = 1 to 100 do for k = 1 to 100 do a[i,j,k] := 0
which fits on a page, but cannot be described as pretty. We therefore impose
an additional constraint limiting the number of characters on each line (excluding indentation) to a smaller number. The idea is to avoid placing too much information on a line -- even a line that begins at the left margin. Under this constraint the example above might instead be laid out as
for i = 1 to 100 do for j = 1 to 100 do for k = 1 to 100 do a[i,j,k] := 0
In general a pretty layout will consist of a ribbon of text snaking across
the page. To see that this is reasonable, ask yourself: `is the prettiest layout on an infinitely wide page really to place everything on one line?' So pretty printing is guided by two lengths: The line length and the (smaller) ribbon length. The ribbons per line ratio that you can specify is simply a way of specifying the ribbon length relative to the line length. So, for example, if the line length is 80 and the ratio is 1.5, the ribbon length would be 80/1.5 which is rounded to 53.
...
Best regards Thorkil
participants (7)
-
Alfonso Acosta
-
Benedikt Huber
-
Duncan Coutts
-
Evan Laforge
-
Malcolm Wallace
-
Simon Peyton-Jones
-
Thorkil Naur