
Hello,
I would say that type families should do the joke:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
type family Prod a where
Prod String = Int
Prod (Maybe a) = a
data Foo e a
where
Foo :: e -> Foo (Prod e) a
Regards.
2016-07-04 22:43 GMT+02:00 Corentin Dupont
Hi all, I have a data type looking like this:
data Foo e a where
Foo :: e → Foo e a
I would like to instantiate it to make it equivalent to:
data Bar a where
A :: String → Bar Int B :: Maybe a → Bar a
How can I do that? With a functional dependency? I probably need to change the definition of Foo.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.