Future of "Text.Show.Functions" module

Hello *,
I noticed the following module (trimmed for brevitiy) hiding in `base`:
-- This module deliberately declares orphan instances:
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions:
--
-- > instance Show (a -> b) where
-- > showsPrec _ _ = showString \"\

On Sun, Oct 19, 2014 at 1:20 PM, Herbert Valerio Riedel
Hello *,
I noticed the following module (trimmed for brevitiy) hiding in `base`:
-- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where -- > showsPrec _ _ = showString \"\
\" -- -----------------------------------------------------------------------------
module Text.Show.Functions () where
instance Show (a -> b) where showsPrec _ _ = showString "<function>"
However, I consider this a questionable module to be in `base` due to its deliberate use of orphan instances. Should this module be deprecated, removed, alternatively, should the `Show` instance be made a non-orphan (e.g. by importing it by the `Prelude` module), or shall this curiousity be just left untouched in `base` in its current form?
Cheers, hvr
-- You received this message because you are subscribed to the Google Groups "haskell-core-libraries" group. To unsubscribe from this group and stop receiving emails from it, send an email to haskell-core-libraries+unsubscribe@googlegroups.com. For more options, visit https://groups.google.com/d/optout.
I think this really brings up the question of what `Show` should be used for. If the goal is to be simple serialization with `Read` as the inverse[1], then this is clearly a nonsense instance and shouldn't be included. If, on the other hand, we consider `Show` to be simple debug output, this makes perfect sense. Similarly, rendering `IO a` as "<IO action>" or something like that makes sense too. An example where this came up recently was adding a Show instance to the Request type in WAI[2]. The goal there is explicitly debugging, and displaying some uninteresting string for any IO actions is very useful. Having such an instance built into base would have been convenient for auto-deriving of this Show instance. Overall, the problem is that we've overloaded Show in (at least) three different ways: * Textual serialization * Debugging * User-friendly display of data I think I give a +0.5 to re-exporting this instance from Prelude/making it non-orphan, since: 1. I agree that orphans in base are a bad idea. 2. Removing the instance will possibly cause breakage for someone. 3. I *do* personally lean towards using Show instances for debugging purposes, and in that context, the Show instance is a good one. Michael [1] I believe the correct term is actually a retraction. [2] https://github.com/yesodweb/wai/issues/290

On Sun, 19 Oct 2014, Michael Snoyman wrote:
Overall, the problem is that we've overloaded Show in (at least) three different ways:
* Textual serialization * Debugging * User-friendly display of data
Unfortunately, the Show class is not used consistently, with the different uses you have listed. The automatically derived Show instances show valid Haskell expressions, that you can enter into GHCi in order to get back the shown value. I think we should stick to that meaning. Strictly conforming to this rule would also mean that using 'show' for formatting numbers is not precisely correct, because we cannot expect that other tools can parse all ways of writing number literals in Haskell. Maybe printf is better here, but it is unfortunately not total. Following the above rule for functions would mean, that 'show' should emit an expression that represents the function, e.g. something like Prelude> show ((\x->x*x) :: Int -> Int) fromJust . flip lookup [(0,0), (1,1), (-1,1), (2,4), (-2,4), ...

On 2014-10-19 at 15:19:42 +0200, Henning Thielemann wrote: [...]
Prelude> show ((\x->x*x) :: Int -> Int) fromJust . flip lookup [(0,0), (1,1), (-1,1), (2,4), (-2,4), ...
That scheme only works for enumerable input-types though, as computing something like 'show fmap' would be quite a challenge :-)

On Sun, Oct 19, 2014 at 8:59 AM, Michael Snoyman
I think this really brings up the question of what `Show` should be used for. If the goal is to be simple serialization with `Read` as the inverse[1], then this is clearly a nonsense instance and shouldn't be included.
I think I've said before that it would be nice if we had a specific class for debugging displays, given that Read/Show are generally oriented toward serialization. Sadly, this would end up requiring a lot of repetition, since you couldn't sanely fall back on a default Show instance to get a notional Gist (or whatever) instance. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Strongly +1 for Show printing valid Haskell. I'd implement showing for functions as data Function = Function instance Show (a -> b) where show f = "Function" (I would not assume Haskellers expect a Show-ed function to be Read-able.) For simple user-friendly display we should add a class to Text.PrettyPrint class Pretty a where pretty :: a -> Doc pretty = text . prettyShow prettyShow :: a -> String prettyShow = render . pretty This class should become standard for implementing simple pretty printing (instead of the abuse of Show). Cheers, Andreas On 19.10.2014 17:36, Brandon Allbery wrote:
On Sun, Oct 19, 2014 at 8:59 AM, Michael Snoyman
mailto:michael@snoyman.com> wrote: I think this really brings up the question of what `Show` should be used for. If the goal is to be simple serialization with `Read` as the inverse[1], then this is clearly a nonsense instance and shouldn't be included.
I think I've said before that it would be nice if we had a specific class for debugging displays, given that Read/Show are generally oriented toward serialization. Sadly, this would end up requiring a lot of repetition, since you couldn't sanely fall back on a default Show instance to get a notional Gist (or whatever) instance.
-- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/

What's the benefit of this implementation of Show (a -> b)? Even if it causes the output to be parseable, it's unlikely to typecheck. On 20/10/2014 22:00, Andreas Abel wrote:
Strongly +1 for Show printing valid Haskell.
I'd implement showing for functions as
data Function = Function
instance Show (a -> b) where show f = "Function"
(I would not assume Haskellers expect a Show-ed function to be Read-able.)
For simple user-friendly display we should add a class to Text.PrettyPrint
class Pretty a where pretty :: a -> Doc pretty = text . prettyShow
prettyShow :: a -> String prettyShow = render . pretty
This class should become standard for implementing simple pretty printing (instead of the abuse of Show).
Cheers, Andreas
On 19.10.2014 17:36, Brandon Allbery wrote:
On Sun, Oct 19, 2014 at 8:59 AM, Michael Snoyman
mailto:michael@snoyman.com> wrote: I think this really brings up the question of what `Show` should be used for. If the goal is to be simple serialization with `Read` as the inverse[1], then this is clearly a nonsense instance and shouldn't be included.
I think I've said before that it would be nice if we had a specific class for debugging displays, given that Read/Show are generally oriented toward serialization. Sadly, this would end up requiring a lot of repetition, since you couldn't sanely fall back on a default Show instance to get a notional Gist (or whatever) instance.

agreed, i'm strongly -1 on forcing a generic catchall a->b instance,
especially since things like Show a => Show (Bool -> a) , are pretty
useful!
On Wed, Oct 22, 2014 at 4:46 PM, Ganesh Sittampalam
What's the benefit of this implementation of Show (a -> b)? Even if it causes the output to be parseable, it's unlikely to typecheck.
On 20/10/2014 22:00, Andreas Abel wrote:
Strongly +1 for Show printing valid Haskell.
I'd implement showing for functions as
data Function = Function
instance Show (a -> b) where show f = "Function"
(I would not assume Haskellers expect a Show-ed function to be Read-able.)
For simple user-friendly display we should add a class to Text.PrettyPrint
class Pretty a where pretty :: a -> Doc pretty = text . prettyShow
prettyShow :: a -> String prettyShow = render . pretty
This class should become standard for implementing simple pretty printing (instead of the abuse of Show).
Cheers, Andreas
On 19.10.2014 17:36, Brandon Allbery wrote:
On Sun, Oct 19, 2014 at 8:59 AM, Michael Snoyman
mailto:michael@snoyman.com> wrote: I think this really brings up the question of what `Show` should be used for. If the goal is to be simple serialization with `Read` as the inverse[1], then this is clearly a nonsense instance and shouldn't be included.
I think I've said before that it would be nice if we had a specific class for debugging displays, given that Read/Show are generally oriented toward serialization. Sadly, this would end up requiring a lot of repetition, since you couldn't sanely fall back on a default Show instance to get a notional Gist (or whatever) instance.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2014-10-19 at 12:20:23 +0200, Herbert Valerio Riedel wrote: [...]
instance Show (a -> b) where showsPrec _ _ = showString "<function>"
PS: An effect of having this instance made default in Prelude is that GHCi would show a somewhat different result in some cases (not sure though if this a good or bad thing): GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. λ:2> id <interactive>:2:1: No instance for (Show (a0 -> a0)) arising from a use of ‘print’ In a stmt of an interactive GHCi command: print it λ:3> import Text.Show.Functions λ:4> id <function> it :: a -> a Cheers, hvr

On Sun, Oct 19, 2014 at 9:18 AM, Herbert Valerio Riedel
On 2014-10-19 at 12:20:23 +0200, Herbert Valerio Riedel wrote:
[...]
instance Show (a -> b) where showsPrec _ _ = showString "<function>"
PS: An effect of having this instance made default in Prelude is that GHCi would show a somewhat different result in some cases (not sure though if this a good or bad thing):
GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. λ:2> id
<interactive>:2:1: No instance for (Show (a0 -> a0)) arising from a use of ‘print’ In a stmt of an interactive GHCi command: print it λ:3> import Text.Show.Functions λ:4> id <function> it :: a -> a
You seem to have ":set +t" on (show types), which isn't the default unless
it changed in HEAD very recently.
I'm -1 for reasons including
* Worse usability in ghci by default. If I see "No instance for (Show
(IOMode -> IO Handle))", I can figure out that I omitted an argument of
type IOMode, but if I see "<function>" I only know that I omitted some
argument, and I have to redo the command with :t to learn more.
* Precludes other instances Show (a -> b), some of which already exist in
the wild, e.g. lambdabot's that uses Typeable to produce a string like
"

On 19 Oct 2014, at 11:20, Herbert Valerio Riedel wrote:
-- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where -- > showsPrec _ _ = showString \"\
\" -- ----------------------------------------------------------------------------- Should this module be deprecated, removed, alternatively, should the `Show` instance be made a non-orphan (e.g. by importing it by the `Prelude` module), or shall this curiousity be just left untouched in `base` in its current form?
Under no circumstances should this instance ever be visible from the Prelude. It was deliberately made an orphan because the instance is non-conformant to the intended semantics of the Show class. Having a default instance of Show for functions would be a disaster, by causing static type error messages that indicate an arity problem, to become erratic runtime behaviours instead (without even throwing an exception). Nevertheless, it was found many years ago that lots of people defined this instance as a convenience, or a debugging aid. And once it accidentally gets into two different released libraries, the orphans conflict, and the libraries become unusable together. This is why a single "standard" orphan was thought preferable to multiple conflicting orphans. In summary, if you want this instance, you should know that it is problematic, and that you need to import it explicitly. Regards, Malcolm

On Sun, Oct 19, 2014 at 4:55 PM, Malcolm Wallace
On 19 Oct 2014, at 11:20, Herbert Valerio Riedel wrote:
-- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where -- > showsPrec _ _ = showString \"\
\" -- -----------------------------------------------------------------------------
Should this module be deprecated, removed, alternatively, should the `Show` instance be made a non-orphan (e.g. by importing it by the `Prelude` module), or shall this curiousity be just left untouched in `base` in its current form?
Under no circumstances should this instance ever be visible from the Prelude.
It was deliberately made an orphan because the instance is non-conformant to the intended semantics of the Show class. Having a default instance of Show for functions would be a disaster, by causing static type error messages that indicate an arity problem, to become erratic runtime behaviours instead (without even throwing an exception).
While I'm sensitive to this position (thus my very reluctant +0.5 on merging into Prelude), I don't see the "disaster" you're referring to. The only case I can picture where this might happen is when you have a value that you are *only* ever displaying, not using in any other way. But won't it become painfully obvious very quickly that you messed up? Can you describe concretely a scenario where the presence of this instance in Prelude would cause a disaster? And if the instance is really as bad as that, I think having it in base at all is a mistake. All it takes it one library upstream from you to import that module, and you've been infected. Michael

On Sun, Oct 19, 2014 at 3:00 PM, Michael Snoyman
And if the instance is really as bad as that, I think having it in base at all is a mistake. All it takes it one library upstream from you to import that module, and you've been infected.
It's useful in ghci. Which suggests a possible solution: perhaps things like this that are mostly useful from ghci should go into a GHC.Interactive hierarchy. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Oct 19, 2014 at 10:03 PM, Brandon Allbery
On Sun, Oct 19, 2014 at 3:00 PM, Michael Snoyman
wrote: And if the instance is really as bad as that, I think having it in base at all is a mistake. All it takes it one library upstream from you to import that module, and you've been infected.
It's useful in ghci.
Which suggests a possible solution: perhaps things like this that are mostly useful from ghci should go into a GHC.Interactive hierarchy.
Based on this thread, I thought it was specifically in GHCi when it was *not* considered helpful. Without the instance: Prelude> print concat <interactive>:2:1: No instance for (Show ([[a0]] -> [a0])) arising from a use of ‘print’ In the expression: print concat In an equation for ‘it’: it = print concat at least tells me what I'm looking at, whereas: Prelude> import Text.Show.Functions Prelude Text.Show.Functions> print concat <function> gives no important info. However, if this is all for GHCi's sake, isn't it really a moot point: Prelude Text.Show.Functions> :t concat concat :: [[a]] -> [a] I'd consider this instance useful for the case of: data Foo = Foo { foo1 :: Int, foo2 :: Double, foo3 :: Char -> Bool } deriving Show Michael

On 19/10/14 22:00, Michael Snoyman wrote:
On Sun, Oct 19, 2014 at 4:55 PM, Malcolm Wallace
wrote: On 19 Oct 2014, at 11:20, Herbert Valerio Riedel wrote:
-- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where -- > showsPrec _ _ = showString \"\
\" -- -----------------------------------------------------------------------------
Should this module be deprecated, removed, alternatively, should the `Show` instance be made a non-orphan (e.g. by importing it by the `Prelude` module), or shall this curiousity be just left untouched in `base` in its current form?
Under no circumstances should this instance ever be visible from the Prelude.
It was deliberately made an orphan because the instance is non-conformant to the intended semantics of the Show class. Having a default instance of Show for functions would be a disaster, by causing static type error messages that indicate an arity problem, to become erratic runtime behaviours instead (without even throwing an exception).
While I'm sensitive to this position (thus my very reluctant +0.5 on merging into Prelude), I don't see the "disaster" you're referring to. The only case I can picture where this might happen is when you have a value that you are *only* ever displaying, not using in any other way. But won't it become painfully obvious very quickly that you messed up?
A simple example would be using show to produce debug output like this: debug $ show $ f x1 x2 ... where you missed some of the arguments for f. For the record, I agree with Malcolm's reasoning and would like the instance to be left as it is now. Roman

Malcolm's reasoning matches mine perfectly here. The instance should not be standard. It should never go into Prelude. It standardizes on one of many viable choices. However, it is one of those things that folks, rightly or wrongly, define fairly often and removing it would increase conflicts among orphans doing the same thing. I'd strongly advocate holding your nose and leaving it there. Sent from my iPhone
On Oct 19, 2014, at 9:55 AM, Malcolm Wallace
wrote: On 19 Oct 2014, at 11:20, Herbert Valerio Riedel wrote:
-- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where -- > showsPrec _ _ = showString \"\
\" -- ----------------------------------------------------------------------------- Should this module be deprecated, removed, alternatively, should the `Show` instance be made a non-orphan (e.g. by importing it by the `Prelude` module), or shall this curiousity be just left untouched in `base` in its current form? Under no circumstances should this instance ever be visible from the Prelude.
It was deliberately made an orphan because the instance is non-conformant to the intended semantics of the Show class. Having a default instance of Show for functions would be a disaster, by causing static type error messages that indicate an arity problem, to become erratic runtime behaviours instead (without even throwing an exception).
Nevertheless, it was found many years ago that lots of people defined this instance as a convenience, or a debugging aid. And once it accidentally gets into two different released libraries, the orphans conflict, and the libraries become unusable together. This is why a single "standard" orphan was thought preferable to multiple conflicting orphans.
In summary, if you want this instance, you should know that it is problematic, and that you need to import it explicitly.
Regards, Malcolm _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2014-10-19 at 23:24:25 +0200, Edward Kmett wrote:
Malcolm's reasoning matches mine perfectly here.
The instance should not be standard.
It should never go into Prelude.
It standardizes on one of many viable choices.
However, it is one of those things that folks, rightly or wrongly, define fairly often and removing it would increase conflicts among orphans doing the same thing.
I'd strongly advocate holding your nose and leaving it there.
Fair enough. But what about adding a WARNING pragma such as (modulo wording): module Text.Show.Functions {-# WARNING "Here Be Dragons, RTFM!" -# } where and adding a bit more documentation pointing out the dos and donts of using that module (like explaining it is not be advisable import that module in a public library package to be placed on Hackage due to the global namespace issue of such instances) Cheers, hvr

I'd have no objection to a well-worded warning.
On Mon, Oct 20, 2014 at 4:57 AM, Herbert Valerio Riedel
On 2014-10-19 at 23:24:25 +0200, Edward Kmett wrote:
Malcolm's reasoning matches mine perfectly here.
The instance should not be standard.
It should never go into Prelude.
It standardizes on one of many viable choices.
However, it is one of those things that folks, rightly or wrongly, define fairly often and removing it would increase conflicts among orphans doing the same thing.
I'd strongly advocate holding your nose and leaving it there.
Fair enough. But what about adding a WARNING pragma such as (modulo wording):
module Text.Show.Functions {-# WARNING "Here Be Dragons, RTFM!" -# } where
and adding a bit more documentation pointing out the dos and donts of using that module (like explaining it is not be advisable import that module in a public library package to be placed on Hackage due to the global namespace issue of such instances)
Cheers, hvr
participants (11)
-
Andreas Abel
-
Brandon Allbery
-
Carter Schonwald
-
Edward Kmett
-
Ganesh Sittampalam
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Malcolm Wallace
-
Michael Snoyman
-
Reid Barton
-
Roman Cheplyaka