[Haskell-cafe] Type-class conditional behavior

dm-list-haskell-cafe at scs.stanford.edu dm-list-haskell-cafe at scs.stanford.edu
Sun May 8 16:42:08 CEST 2011


At Sat, 7 May 2011 22:14:27 -0700,
Nicholas Tung wrote:
> 
> Dear all,
> 
>     I'd like to write a function "maybeShow :: a -> Maybe String", which runs
> "show" if its argument is of class Show.

You can't do this, because in general there is no way to know whether
an arbitrary object a is of class Show.  In fact, in the worst case,
you could even have two different instances of Show for the same type
defined in two different modules of your program.  Obviously you can't
import both modules with both instances into the same module, but what
if you didn't import either--how would the compiler know where to find
the Show function or which one to use.

The best you could hope for is to run show if type a is *known* to be
in class Show at your call site.  But that would lead to some pretty
weird behavior.  For instance, the following two functions would be
different--f1 would always return Just, and f2 would always return
Nothing, which is why I assume no combination of LANGUAGE pragmas
would allow it:

f1 :: (Show a) => a -> Maybe String
f1 = maybeShow

f2 :: a -> Maybe String
f2 = maybeShow

In fact, I suspect that your arrow example is more like f2, in that
you don't have a Show dictionary around, so maybeShow will always
return nothing.

Is there any way you can pass the function around explicitly, as in:

data AV t where
  AVLeft :: AV (a, a -> Maybe String)
         -> AV (Either (a, a -> Maybe String) b)

It is also possible to pass dictionaries around explicitly using the
ExistentialQuantification extension (which is required by the standard
library exception mechanism, so is probably a reasonably safe one to
rely on).  Can you do something like the following?

{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}

data Showable a = forall a. (Show a) => Showable a

data AV t where
  AVLeft :: AV (Showable a) -> AV (Either (Showable a) b)

David



More information about the Haskell-Cafe mailing list