[Haskell-cafe] Type-class conditional behavior

Gábor Lehel illissius at gmail.com
Sun May 8 09:28:07 CEST 2011


On Sun, May 8, 2011 at 7:14 AM, Nicholas Tung <ntung at ntung.com> wrote:
> Dear all,
>     I'd like to write a function "maybeShow :: a -> Maybe String", which
> runs "show" if its argument is of class Show.
>     The context and motivation for this are as follows. I have a GADT type
> which encapsulates abstract-value computation (or constants or error codes),
> a snippet of which is below.
> data AV t where
>     AVLeft :: AV a -> AV (Either a b)
>     This is used to implement an arrow transformer, and due to Arrows
> mapping all Haskell functions, I cannot put some kind of qualification on
> the constructor, like "AVLeft :: Show a => ...".
>     Of course any replies are welcome, but I do need something implemented
> and stable. If there are GHC-compatible hacks, even an "unsafeShow :: a ->
> String", that'd be great. I'd also prefer not to branch on all types which
> could possibly be maybeShow's argument.

To the best of my knowledge, this is impossible. Haskell/GHC lets you
require that certain type-level (predicates/assertions/constraints be
true? evidence/proof be supplied? I'm not sure what the correct
terminology is), but it doesn't let you branch over *whether* it is
so. A natural solution would be OverlappingInstances, but that doesn't
help in this case: instances are matched only by the instance head,
and the context is checked only afterwards. So if you have

class MaybeShow a where maybeShow :: a -> Maybe String
instance MaybeShow a where maybeShow = const Nothing
instance Show a => MaybeShow a where maybeShow = Just . show

you have two instances which both match for any 'a', resulting in
overlap any time you try to use it, and rendering this 'solution'
unworkable. There's a section on advanced overlap in the wiki[1], but
it's Really Ugly and doesn't (to my mind) actually solve the problem
(you still have to branch on every potential type).

You could do:

class MaybeShow a where maybeShow :: a -> Maybe String
instance MaybeShow a where maybeShow = const Nothing
newtype Showable a = Showable { getShowable :: a }
instance Show a => MaybeShow (Showable a) where maybeShow = Just .
show . getShowable

which lets you write further MaybeShow instances for specific types to
'forward' the Show instance (which isn't any worse than the
AdvancedOverlap solution, if you have to handle every type explicitly
anyways), and you can also write maybeShow (Showable x) at the use
site if you know that x has a Show instance. But at that point you
might as well perform some 'optimization' and just use show directly,
so this doesn't really get you anywhere.

[1] http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap



>
>
>     (Concretely, if I have "newtype AVFunctor a b c = AVF (a (AV b) (AV
> c))", then the Arrow class declaration forces all types, c.f. variable b, to
> be potential variables of type AV),
> class (Category a) => Arrow a where
>   arr :: (b -> c) -> a b c
>
> Thanks very much,
> Nicholas — https://ntung.com — CS major @ UC Berkeley
>
> p.s. I posted this question on StackOverflow if you care to get brownie
> points there, http://goo.gl/PrmYW
> p.s. 2 -- if there is a general "dump var" function in ghci, which does more
> than ":info", I'd love to know :)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
Work is punishment for failing to procrastinate effectively.



More information about the Haskell-Cafe mailing list