[Haskell-cafe] Type-class conditional behavior

Ryan Ingram ryani.spam at gmail.com
Sun May 8 09:06:13 CEST 2011


The behavior you are asking for "maybeShow" violates parametricity, so it
can't exist without some sort of typeclass constraint.

That said, in your particular situation, it's an interesting question.

The Show instance for Either is

instance (Show a, Show b) => Show (Either a b) where ...

so we as programmers know that, given some instance Show (Either a b) that
there must be an instance for a.  But we can't get at it!

Inside the compiler, this instance looks something like this:

data ShowDict a = ShowDict {
     showsPrec :: Int -> a -> String -> String,
     show :: a -> String,
     shows :: a -> String -> String,
     showsList :: [a] -> String -> String
   }

showEither :: (ShowDict a, ShowDict b) -> ShowDict (Either a b)
showEither (sda, sdb) = ShowDict ...

Note that inside the functions returned by showEither we've "lost" the
parent dictionaries sda/sdb.

However we know the behavior of these functions, and you can hack around it
with a manual show instance that takes advantage of that knowledge:

instance Show t => Show (AV t) where
    show (AVLeft a) = drop 5 $ show (Left a)

The 'drop 5' takes off the 'Left ' in the returned string.  To be a bit
smarter you'd also look for surrounding parens and remove them as well, but
this is how you could solve your problem.

All this said, I agree that the presence of 'arr' in Arrow is a problem for
many types of generalized computing.  It overly constrains what can be an
arrow, in my opinion.  I think a better analysis of the primitives required
for arrow notation to work would solve a lot of problems of this type.

  -- ryan

On Sat, May 7, 2011 at 10:14 PM, 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.
>
>
>
>     (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
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110508/84b70c23/attachment-0001.htm>


More information about the Haskell-Cafe mailing list