[Haskell-cafe] Deriving vs. type constructors
Michael Sperber
sperber at deinprogramm.de
Wed Oct 15 14:55:52 UTC 2014
I'm struggling with a problem related to generic programming, boiling
down to this:
----snip----
{-# LANGUAGE StandaloneDeriving, KindSignatures, UndecidableInstances #-}
data Foo (v :: * -> *) = Foo (v Bar)
deriving instance (Show (v Bar)) => Show (Foo v)
data Bar = Bar
deriving Show
----snip----
So the Show instance for Foo v wants the rather specific Show instance
for v Bar.
But now imagine that v is always something like Maybe, itself done using
something like this presumably:
instance Show a => Show (Maybe a) where ...
Can I somehow state as a constraint that Foo v has a Show instance if v
is a type constructor like Maybe, i.e. once with a Show instances for
any arguments that has a Show instance?
(You can't see *why* I want to do this in this example - I actually have
something like 100 nested datatypes which thread v through, and *every
single one of them* adds to the context I need for every one of them.)
I feel I want to write something like this:
deriving instance (Show a => Show (v a)) => Show (Foo v)
Is there a way to do this?
Help would be much appreciated!
--
Regards,
Mike
More information about the Haskell-Cafe
mailing list