Ticket #3058: Add 'hex' to the pretty package (and other thoughts)

All, http://hackage.haskell.org/trac/ghc/ticket/3058 Attached is a patch for Text.PrettyPrint.HughesPJ that adds a 'hex' function to print hexidecimal numbers. The only point that I exepect to be contended is it varies slightly from the surrounding functions in that it allows one to control the number of characters printed:
hex 5 31 0001f hex 2 8 08 hex 3 7495 d47
While we can argue about the consistancy issues, I almost always want to control the number of digits when dealing with hex. Hence I feel this is a reasonable special case. Secondary Issues: 1) Is there a repo for pretty? I didn't see one on code.haskell.org 2) If I submit a ticket+patch to move Text.PrettyPrint.HughesPJClass (from prettyclass, Augustsson) into Text.PrettyPrint (of the 'pretty' package) would anyone object? It feels mis-placed / I feel things need consolidated. Thomas

On Mon, 2009-03-02 at 01:53 -0800, Thomas DuBuisson wrote:
All,
http://hackage.haskell.org/trac/ghc/ticket/3058
Attached is a patch for Text.PrettyPrint.HughesPJ that adds a 'hex' function to print hexidecimal numbers.
The only point that I exepect to be contended is it varies slightly from the surrounding functions in that it allows one to control the number of characters printed:
There are a number of other functions from the Numeric module we should also consider. These are all the ones that return ShowS, the equivalent of the Doc type. showEFloat :: (RealFloat a) => Maybe Int -> a -> ShowS showFFloat :: (RealFloat a) => Maybe Int -> a -> ShowS showGFloat :: (RealFloat a) => Maybe Int -> a -> ShowS showHex :: (Integral a) => a -> ShowS showInt :: (Integral a) => a -> ShowS showIntAtBase :: (Integral a) => a -> (Int -> Char) -> a -> ShowS showOct :: (Integral a) => a -> ShowS showFloat :: (RealFloat a) => a -> ShowS showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
While we can argue about the consistancy issues, I almost always want to control the number of digits when dealing with hex. Hence I feel this is a reasonable special case.
For some reason I thought I remembered that the Numeric show functions also allowed fixed width 0-padded display but it appears they do not, except by manually rendering and adding leading 0's. Note the show float functions take an optional precision. Perhaps that's a sensible approach for optional fixed width octal and hexadecimal display.
Secondary Issues: 1) Is there a repo for pretty? I didn't see one on code.haskell.org
It's on darcs.haskell.org along with ghc and the other core libs.
2) If I submit a ticket+patch to move Text.PrettyPrint.HughesPJClass (from prettyclass, Augustsson) into Text.PrettyPrint (of the 'pretty' package) would anyone object? It feels mis-placed / I feel things need consolidated.
That's a much bigger change. I suggest a separate ticket and discussion for that. There's a rather large design space and range of use cases. Duncan

On Mon, 2009-03-02 at 12:55 +0000, Duncan Coutts wrote:
On Mon, 2009-03-02 at 01:53 -0800, Thomas DuBuisson wrote:
All,
http://hackage.haskell.org/trac/ghc/ticket/3058 There are a number of other functions from the Numeric module we should also consider. These are all the ones that return ShowS, the equivalent of the Doc type.
I've added another patch to that ticket for consideration. It has hex, oct, intAtBase (plus padded variants). Also included are {e,f,g}float without any padding options. Padding floats could be touchy - perhaps it should be a separate patch by someone who would use such a feature and know what they want. Thoughts? Thomas

On Mon, 2009-03-02 at 17:16 -0800, Thomas DuBuisson wrote:
On Mon, 2009-03-02 at 12:55 +0000, Duncan Coutts wrote:
On Mon, 2009-03-02 at 01:53 -0800, Thomas DuBuisson wrote:
All,
http://hackage.haskell.org/trac/ghc/ticket/3058 There are a number of other functions from the Numeric module we should also consider. These are all the ones that return ShowS, the equivalent of the Doc type.
I've added another patch to that ticket for consideration. It has hex, oct, intAtBase (plus padded variants). Also included are {e,f,g}float without any padding options.
Padding floats could be touchy - perhaps it should be a separate patch by someone who would use such a feature and know what they want.
Thoughts?
Presumably it would be uncontroversial for the float ones to behave the same as the ones from the existing Numeric module. Duncan

Padding floats could be touchy - perhaps it should be a separate patch by someone who would use such a feature and know what they want.
Thoughts?
Presumably it would be uncontroversial for the float ones to behave the same as the ones from the existing Numeric module.
Done, the new prettyNumeric.patch is with the ticket including hex, oct, ffloat, efloat, gfloat, signed, intByBase. Also, padded versions of hex, oct, intByBase. Thomas

In a couple days it will be the two week mark and I'll be posting a
summary of this conversation on the ticket. At this point I don't see
any disagreement, just questions regarding the completeness of the
patch (so I included many more functions from Numeric). The final
type signatures are:
efloat :: (RealFloat a) => Maybe Int -> a -> Doc
ffloat :: (RealFloat a) => Maybe Int -> a -> Doc
gfloat :: (RealFloat a) => Maybe Int -> a -> Doc
hex :: (Integral a) => a -> Doc
hexPad :: (Integral a) => a -> Int -> Doc
intAtBase :: (Integral a) => a -> (Int -> Char) -> a -> Doc
intAtBasePad :: (Integral a) => a -> (Int -> Char) -> a -> Int -> Doc
oct :: (Integral a) => a -> Doc
octPad :: (Integral a) => Maybe Int -> a -> Int -> Doc
Which follows the Numeric module pretty close (except the *Pad
functions, which are obvious devivations).
Thomas
On Mon, Mar 2, 2009 at 7:01 PM, Thomas DuBuisson
Padding floats could be touchy - perhaps it should be a separate patch by someone who would use such a feature and know what they want.
Thoughts?
Presumably it would be uncontroversial for the float ones to behave the same as the ones from the existing Numeric module.
Done, the new prettyNumeric.patch is with the ticket including hex, oct, ffloat, efloat, gfloat, signed, intByBase. Also, padded versions of hex, oct, intByBase.
Thomas

Thomas DuBuisson wrote:
In a couple days it will be the two week mark and I'll be posting a summary of this conversation on the ticket. At this point I don't see any disagreement, just questions regarding the completeness of the patch (so I included many more functions from Numeric). The final type signatures are:
efloat :: (RealFloat a) => Maybe Int -> a -> Doc ffloat :: (RealFloat a) => Maybe Int -> a -> Doc gfloat :: (RealFloat a) => Maybe Int -> a -> Doc hex :: (Integral a) => a -> Doc hexPad :: (Integral a) => a -> Int -> Doc intAtBase :: (Integral a) => a -> (Int -> Char) -> a -> Doc intAtBasePad :: (Integral a) => a -> (Int -> Char) -> a -> Int -> Doc oct :: (Integral a) => a -> Doc octPad :: (Integral a) => Maybe Int -> a -> Int -> Doc
Which follows the Numeric module pretty close (except the *Pad functions, which are obvious devivations).
are the "Pad" functions ones that (as mentioned above) are willing not just to add padding but to chop off higher-order digits? I find the name misleading. Also hexPad and intAtBasePad each add (compared to the non-Pad versions) an Int argument, but octPad adds an Int and a Maybe Int argument? why is this? -Isaac

are the "Pad" functions ones that (as mentioned above) are willing not just to add padding but to chop off higher-order digits? I find the name misleading.
Yes, and I agree the name is misleading. Does anyone have a suggestion of a better name?
Also hexPad and intAtBasePad each add (compared to the non-Pad versions) an Int argument, but octPad adds an Int and a Maybe Int argument? why is this? That's not right - don't know how that error happened, perhaps a toy-version of the library was loaded. Here is a copy paste of the type signature and some uses:
Prelude Text.PrettyPrint> :i octPad octPad :: (Integral a) => a -> Int -> Doc Prelude Text.PrettyPrint> octPad 10 2 12 Prelude Text.PrettyPrint> hexPad 133 3 085 Prelude Text.PrettyPrint> hexPad 133 2 85 Prelude Text.PrettyPrint> hexPad 133 1 5

Thomas DuBuisson wrote:
The only point that I exepect to be contended is it varies slightly from the surrounding functions in that it allows one to control the number of characters printed:
hex 5 31
0001f
hex 2 8
08
hex 3 7495
d47
what about when it doesn't fit in the given number of characters? Show us the answer to: hex 1 31 -Isaac

what about when it doesn't fit in the given number of characters? Show us the answer to: hex 1 31
That was my third example. As you can see from the source it will show the least significant bits in this case.
hex 1 31 f
Thomas
participants (3)
-
Duncan Coutts
-
Isaac Dupree
-
Thomas DuBuisson