Nested Type-Level Programming - haskell

I'm attempting to use DataKinds to do type-level programming, but am running into difficulties when I have one of these structures nested in another.
{-# LANGUAGE DataKinds, TypeFamilies, GADTs, MultiParamTypeClasses, FlexibleInstances #-}
module Temp where
data Prop1 = D | E
data Lower :: Prop1 -> * where
SubThing1 :: Lower D
SubThing2 :: Lower E
class ClassLower a where
somefunc2 :: a -> String
instance ClassLower (Lower D) where
somefunc2 a = "string3"
instance ClassLower (Lower E) where
somefunc2 a = "string4"
data Prop2 = A | B | C
data Upper :: Prop2 -> * where
Thing1 :: Upper A
Thing2 :: Upper B
Thing3 :: Lower a -> Upper C
class ClassUpper a where
somefunc :: a -> String
instance ClassUpper (Upper A) where
somefunc a = "string1"
instance ClassUpper (Upper B) where
somefunc a = "string2"
instance ClassUpper (Upper C) where
somefunc (Thing3 x) = somefunc2 x
As soon as I add that last instance of ClassUpper, I end up with an error.
Temp.hs:37:25: error:
• Could not deduce (ClassLower (Lower a))
arising from a use of ‘somefunc2’
from the context: 'C ~ 'C
bound by a pattern with constructor:
Thing3 :: forall (a :: Prop1). Lower a -> Upper 'C,
in an equation for ‘somefunc’
at /Users/jdouglas/jeff/emulator/src/Temp.hs:37:13-20
• In the expression: somefunc2 x
In an equation for ‘somefunc’: somefunc (Thing3 x) = somefunc2 x
In the instance declaration for ‘ClassUpper (Upper 'C)’
I understand that 'C ~ 'C indicates type equality, but I don't understand what the underlying problem is, much less the solution or workaround.
What am I not understanding, and what is the best way to tackle this problem?

The problem here is a bit subtle. The reason one might expect GHC to accept this is that you have instances for all possible Lower a since you only provide ways of making Lower D and Lower E. However, one could construct a pathological definition for Lower like
import GHC.Exts (Any)
data Lower :: Prop1 -> * where
SubThing1 :: Lower D
SubThing2 :: Lower E
SubThing3 :: Lower Any
The point is that not only D and E have kind Prop1. It isn't just with things like Any that we can play such shenanigans - even the following constructor is allowed (so F Int :: Prop1 too)!
SubThing4 :: Lower (F Int)
type family F x :: Prop1 where {}
So, in summary, the underlying problem is that GHC really can't be sure that the ClassLower (Lower a) constraint (needed due to the use of somefunc2) is going to be satisfied. To do so, it would have to do a fair bit of work checking the GADT constructors and making sure that every possible case is covered by some instance.
In this case, you could solve your problem by adding the ClassLower (Lower a) constraint to the GADT constructor (an enabling FlexibleContexts).
data Upper :: Prop2 -> * where
Thing1 :: Upper A
Thing2 :: Upper B
Thing3 :: ClassLower (Lower a) => Lower a -> Upper C

Or you could write out your ClassLower instance like this, using pattern matching (rather than the type variable) to distinguish the cases of the GADT:
instance ClassLower (Lower a) where
somefunc2 SubThing1 = "string3"
somefunc2 SubThing2 = "string4"

Related

differences: GADT, data family, data family that is a GADT

What/why are the differences between those three? Is a GADT (and regular data types) just a shorthand for a data family? Specifically what's the difference between:
data GADT a where
MkGADT :: Int -> GADT Int
data family FGADT a
data instance FGADT a where -- note not FGADT Int
MkFGADT :: Int -> FGADT Int
data family DF a
data instance DF Int where -- using GADT syntax, but not a GADT
MkDF :: Int -> DF Int
(Are those examples over-simplified, so I'm not seeing the subtleties of the differences?)
Data families are extensible, but GADTs are not. OTOH data family instances must not overlap. So I couldn't declare another instance/any other constructors for FGADT; just like I can't declare any other constructors for GADT. I can declare other instances for DF.
With pattern matching on those constructors, the rhs of the equation does 'know' that the payload is Int.
For class instances (I was surprised to find) I can write overlapping instances to consume GADTs:
instance C (GADT a) ...
instance {-# OVERLAPPING #-} C (GADT Int) ...
and similarly for (FGADT a), (FGADT Int). But not for (DF a): it must be for (DF Int) -- that makes sense; there's no data instance DF a, and if there were it would overlap.
ADDIT: to clarify #kabuhr's answer (thank you)
contrary to what I think you're claiming in part of your question, for a plain data family, matching on a constructor does not perform any inference
These types are tricky, so I expect I'd need explicit signatures to work with them. In that case the plain data family is easiest
inferDF (MkDF x) = x -- works without a signature
The inferred type inferDF :: DF Int -> Int makes sense. Giving it a signature inferDF :: DF a -> a doesn't make sense: there is no declaration for a data instance DF a .... Similarly with foodouble :: Foo Char a -> a there is no data instance Foo Char a ....
GADTs are awkward, I already know. So neither of these work without an explicit signature
inferGADT (MkGADT x) = x
inferFGADT (MkFGADT x) = x
Mysterious "untouchable" message, as you say. What I meant in my "matching on those constructors" comment was: the compiler 'knows' on rhs of an equation that the payload is Int (for all three constructors), so you'd better get any signatures consistent with that.
Then I'm thinking data GADT a where ... is as if data instance GADT a where .... I can give a signature inferGADT :: GADT a -> a or inferGADT :: GADT Int -> Int (likewise for inferFGADT). That makes sense: there is a data instance GADT a ... or I can give a signature at a more specific type.
So in some ways data families are generalisations of GADTs. I also see as you say
So, in some ways, GADTs are generalizations of data families.
Hmm. (The reason behind the question is that GHC Haskell has got to the stage of feature bloat: there's too many similar-but-different extensions. I was trying to prune it down to a smaller number of underlying abstractions. Then #HTNW's approach of explaining in terms of yet further extensions is opposite to what would help a learner. IMO existentials in data types should be chucked out: use GADTs instead. PatternSynonyms should be explained in terms of data types and mapping functions between them, not the other way round. Oh, and there's some DataKinds stuff, which I skipped over on first reading.)
As a start, you should think of a data family as a collection of independent ADTs that happen to be indexed by a type, while a GADT is a single data type with an inferrable type parameter where constraints on that parameter (typically, equality constraints like a ~ Int) can be brought into scope by pattern matching.
This means that the biggest difference is that, contrary to what I think you're claiming in part of your question, for a plain data family, matching on a constructor does not perform any inference on the type parameter. In particular, this typechecks:
inferGADT :: GADT a -> a
inferGADT (MkGADT n) = n
but this does not:
inferDF :: DF a -> a
inferDF (MkDF n) = n
and without type signatures, the first would fail to type check (with a mysterious "untouchable" message) while the second would be inferred as DF Int -> Int.
The situation becomes quite a bit more confusing for something like your FGADT type that combines data families with GADTs, and I confess I haven't really thought about how this works in detail. But, as an interesting example, consider:
data family Foo a b
data instance Foo Int a where
Bar :: Double -> Foo Int Double
Baz :: String -> Foo Int String
data instance Foo Char Double where
Quux :: Double -> Foo Char Double
data instance Foo Char String where
Zlorf :: String -> Foo Char String
In this case, Foo Int a is a GADT with an inferrable a parameter:
fooint :: Foo Int a -> a
fooint (Bar x) = x + 1.0
fooint (Baz x) = x ++ "ish"
but Foo Char a is just a collection of separate ADTs, so this won't typecheck:
foodouble :: Foo Char a -> a
foodouble (Quux x) = x
for the same reason inferDF won't typecheck above.
Now, getting back to your plain DF and GADT types, you can largely emulate DFs just using GADTs. For example, if you have a DF:
data family MyDF a
data instance MyDF Int where
IntLit :: Int -> MyDF Int
IntAdd :: MyDF Int -> MyDF Int -> MyDF Int
data instance MyDF Bool where
Positive :: MyDF Int -> MyDF Bool
you can write it as a GADT just by writing separate blocks of constructors:
data MyGADT a where
-- MyGADT Int
IntLit' :: Int -> MyGADT Int
IntAdd' :: MyGADT Int -> MyGADT Int -> MyGADT Int
-- MyGADT Bool
Positive' :: MyGADT Int -> MyGADT Bool
So, in some ways, GADTs are generalizations of data families. However, a major use case for data families is defining associated data types for classes:
class MyClass a where
data family MyRep a
instance MyClass Int where
data instance MyRep Int = ...
instance MyClass String where
data instance MyRep String = ...
where the "open" nature of data families is needed (and where the pattern-based inference methods of GADTs aren't helpful).
I think the difference becomes clear if we use PatternSynonyms-style type signatures for data constructors. Lets start with Haskell 98
data D a = D a a
You get a pattern type:
pattern D :: forall a. a -> a -> D a
it can be read in two directions. D, in "forward" or expression contexts, says, "forall a, you can give me 2 as and I'll give you a D a". "Backwards", as a pattern, it says, "forall a, you can give me a D a and I'll give you 2 as".
Now, the things you write in a GADT definition are not pattern types. What are they? Lies. Lies lies lies. Give them attention only insofar as the alternative is writing them out manually with ExistentialQuantification. Let's use this one
data GD a where
GD :: Int -> GD Int
You get
-- vv ignore
pattern GD :: forall a. () => (a ~ Int) => Int -> GD a
This says: forall a, you can give me a GD a, and I can give you a proof that a ~ Int, plus an Int.
Important observation: The return/match type of a GADT constructor is always the "data type head". I defined data GD a where ...; I got GD :: forall a. ... GD a. This is also true for Haskell 98 constructors, and also data family constructors, though it's a bit more subtle.
If I have a GD a, and I don't know what a is, I can pass into GD anyway, even though I wrote GD :: Int -> GD Int, which seems to say I can only match it with GD Ints. This is why I say GADT constructors lie. The pattern type never lies. It clearly states that, forall a, I can match a GD a with the GD constructor and get evidence for a ~ Int and a value of Int.
Ok, data familys. Lets not mix them with GADTs yet.
data Nat = Z | S Nat
data Vect (n :: Nat) (a :: Type) :: Type where
VNil :: Vect Z a
VCons :: a -> Vect n a -> Vect (S n) a -- try finding the pattern types for these btw
data family Rect (ns :: [Nat]) (a :: Type) :: Type
newtype instance Rect '[] a = RectNil a
newtype instance Rect (n : ns) a = RectCons (Vect n (Rect ns a))
There are actually two data type heads now. As #K.A.Buhr says, the different data instances act like different data types that just happen to share a name. The pattern types are
pattern RectNil :: forall a. a -> Rect '[] a
pattern RectCons :: forall n ns a. Vect n (Rect ns a) -> Rect (n : ns) a
If I have a Rect ns a, and I don't know what ns is, I cannot match on it. RectNil only takes Rect '[] as, RectCons only takes Rect (n : ns) as. You might ask: "why would I want a reduction in power?" #KABuhr has given one: GADTs are closed (and for good reason; stay tuned), families are open. This doesn't hold in Rect's case, as these instances already fill up the entire [Nat] * Type space. The reason is actually newtype.
Here's a GADT RectG:
data RectG :: [Nat] -> Type -> Type where
RectGN :: a -> RectG '[] a
RectGC :: Vect n (RectG ns a) -> RectG (n : ns) a
I get
-- it's fine if you don't get these
pattern RectGN :: forall ns a. () => (ns ~ '[]) => a -> RectG ns a
pattern RectGC :: forall ns' a. forall n ns. (ns' ~ (n : ns)) =>
Vect n (RectG ns a) -> RectG ns' a
-- just note that they both have the same matched type
-- which means there needs to be a runtime distinguishment
If I have a RectG ns a and don't know what ns is, I can still match on it just fine. The compiler has to preserve this information with a data constructor. So, if I had a RectG [1000, 1000] Int, I would incur an overhead of one million RectGN constructors that all "preserve" the same "information". Rect [1000, 1000] Int is fine, though, as I do not have the ability to match and tell whether a Rect is RectNil or RectCons. This allows the constructor to be newtype, as it holds no information. I would instead use a different GADT, somewhat like
data SingListNat :: [Nat] -> Type where
SLNN :: SingListNat '[]
SLNCZ :: SingListNat ns -> SingListNat (Z : ns)
SLNCS :: SingListNat (n : ns) -> SingListNat (S n : ns)
that stores the dimensions of a Rect in O(sum ns) space instead of O(product ns) space (I think those are right). This is also why GADTs are closed and families are open. A GADT is just like a normal data type except it has equality evidence and existentials. It doesn't make sense to add constructors to a GADT any more than it makes sense to add constructors to a Haskell 98 type, because any code that doesn't know about one of the constructors is in for a very bad time. It's fine for families though, because, as you noticed, once you define a branch of a family, you cannot add more constructors in that branch. Once you know what branch you're in, you know the constructors, and no one can break that. You're not allowed to use any constructors if you don't know which branch to use.
Your examples don't really mix GADTs and data families. Pattern types are nifty in that they normalize away superficial differences in data definitions, so let's take a look.
data family FGADT a
data instance FGADT a where
MkFGADT :: Int -> FGADT Int
Gives you
pattern MkFGADT :: forall a. () => (a ~ Int) => Int -> FGADT a
-- no different from a GADT; data family does nothing
But
data family DF a
data instance DF Int where
MkDF :: Int -> DF Int
gives
pattern MkDF :: Int -> DF Int
-- GADT syntax did nothing
Here's a proper mixing
data family Map k :: Type -> Type
data instance Map Word8 :: Type -> Type where
MW8BitSet :: BitSet8 -> Map Word8 Bool
MW8General :: GeneralMap Word8 a -> Map Word8 a
Which gives patterns
pattern MW8BitSet :: forall a. () => (a ~ Bool) => BitSet8 -> Map Word8 a
pattern MW8General :: forall a. GeneralMap Word8 a -> Map Word8 a
If I have a Map k v and I don't know what k is, I can't match it against MW8General or MW8BitSet, because those only want Map Word8s. This is the data family's influence. If I have a Map Word8 v and I don't know what v is, matching on the constructors can reveal to me whether it's known to be Bool or is something else.

How to create an instance for Floating only?

There is a class, for which I would like to define an instance.
It looks like this:
data MyValue a = MyValue a
class TestClass a where
funcOne:: (Real b) => a b -> a b
funcTwo:: (Real b) => a b -> a b -> a b
instance TestClass MyValue where
funcOne (MyValue x) = MyValue (x*pi)
funcTwo (MyValue x) (MyValue y) = MyValue (x*y)
I get the following error:
Could not deduce (Floating b) arising from a use of `pi'
from the context: Real b
I understand the error, but I don't know how should I solve it.
I can't change the (Real b) to (Floating b) because other instances should work with Integral types too. But MyValue makes sense with Floating only. Is it possible to tell the compiler, that the instance TestClass MyValue works only with Floating?
If it is not, then how is it possible to cast the result x*pi back to the same Real as the x parameter? It does not matter what happens if the type is for example Integral, because the MyValue does not make sense in that case
You can achieve this, but you'll need to modify either that data type or the class.
If MyValue in particular makes sense with Floating only then it makes perhaps sense to bake that constraint into its constructor.
{-# LANGUAGE GADTs #-}
data MyValue :: * -> * where
MyValue :: Floating a => a -> MyValue a
This guarantees to any function accepting a MyValue a that a is actually a Floating instance, hence
funcOne (MyValue x) = MyValue $ x*pi
will then work.
If this is a common theme, requiring a particular constraint on the contained type, then you can, instead of always requiring Real, make the constraint dependent on the instance:
{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
import GHC.Exts (Constraint)
class TestClass a where
type Testable a b :: Constraint
type Testable a b = Real b -- default constraint
funcOne:: Testable b => a b -> a b
funcTwo:: Testable b => a b -> a b -> a b
instance TestClass MyValue where
type Testable MyValue b = Floating b
funcOne (MyValue x) = MyValue $ x*pi
...
But perhaps it's not the right decision to let TestClass deal with parameterised (* -> *) types in the first place, if you then need to artificially constrain the parametricity again. Why not instead do simply
class TestClass q where
funcOne :: q -> q
funcTwo :: q -> q -> q
instance Floating a => TestClass (MyValue a) where
funcOne (MyValue x) = MyValue $ x*pi
funcTwo (MyValue x) (MyValue y) = MyValue $ x*y
That would seem cleaner to me anyway. If some of the methods do require access to the contained type, that's also possible with this approach, using an associated type family:
class TestClass q where
type ToTest q :: *
...
instance Floating a => TestClass (MyValue a) where
type ToTest (MyValue a) = a
...
There is no way of restricting b for that one instance. TestClass says that funcOne works for any Real b. If that is not the case for MyValue, then MyValue is not an instance of TestClass. Furthermore there is no way to cast from a Floating to Real without always loosing accuracy. The only way to get to the Real type would be fromInteger, but if you cast your type first to Integer you will always loose the fractional part.
The only thing you could do (that I am aware of) is using a different MyValue type that restricts b to always have a Floating constraint by using GADTs:
{-# LANGUAGE GADTs #-}
data MyValue' = Floating a => MyValue' a
instance TestClass MyValue' where
-- Pattern matching on MyValue' brings the 'Floating' constraint into scope.
funcOne (MyValue' x) = MyValue' $ x * pi
...
Now every time you have a value of type MyValue' a pattern matching on that value is proof that a is an instance of Floating.
Note that this approach fails if TestClass has a function that does not take a value of type a:
class TestClass a where
...
pureTest :: Real b => b -> a b
Now in pureTest b does not have to be Floating and therefore pureTest b = MyValue' b would be a type error.

Defining a Function for Multiple Types

How is a function defined for different types in Haskell?
Given
func :: Integral a => a -> a
func x = x
func' :: (RealFrac a , Integral b) => a -> b
func' x = truncate x
How could they be combined into one function with the signature
func :: (SomeClassForBoth a, Integral b) => a -> b
With a typeclass.
class TowardsZero a where towardsZero :: Integral b => a -> b
instance TowardsZero Int where towardsZero = fromIntegral
instance TowardsZero Double where towardsZero = truncate
-- and so on
Possibly a class with an associated type family constraint is closer to what you wrote (though perhaps not closer to what you had in mind):
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts
class TowardsZero a where
type RetCon a b :: Constraint
towardsZero :: RetCon a b => a -> b
instance TowardsZero Int where
type RetCon Int b = Int ~ b
towardsZero = id
instance TowardsZero Double where
type RetCon Double b = Integral b
towardsZero = truncate
-- and so on
This is known as ad hoc polymorphism, where you execute different code depending on the type. The way this is done in Haskell is using typeclasses. The most direct way is to define a new class
class Truncable a where
trunc :: Integral b => a -> b
And then you can define several concrete instances.
instance Truncable Integer where trunc = fromInteger
instance Truncable Double where trunc = truncate
This is unsatisfying because it requires an instance for each concrete type, when there are really only two families of identical-looking instances. Unfortunately, this is one of the cases where it is hard to reduce boilerplate, for technical reasons (being able to define "instance families" like this interferes with the open-world assumption of typeclasses, among other difficulties with type inference). As a hint of the complexity, note that your definition assumes that there is no type that is both RealFrac and Integral, but this is not guaranteed -- which implementation should we pick in this case?
There is another issue with this typeclass solution, which is that the Integral version doesn't have the type
trunc :: Integral a => a -> a
as you specified, but rather
trunc :: (Integral a, Integral b) => a -> b
Semantically this is not a problem, as I don't believe it is possible to end up with some polymorphic code where you don't know whether the type you are working with is Integral, but you do need to know that when it is, the result type is the same as the incoming type. That is, I claim that whenever you would need the former rather than the latter signature, you already know enough to replace trunc by id in your source. (It's a gut feeling though, and I would love to be proven wrong, seems like a fun puzzle)
There may be performance implications, however, since you might unnecessarily call fromIntegral to convert a type to itself, and I think the way around this is to use {-# RULES #-} definitions, which is a dark scary bag of complexity that I've never really dug into, so I don't know how hard or easy this is.
I don't recommend this, but you can hack at it with a GADT:
data T a where
T1 :: a -> T a
T2 :: RealFrac a => a -> T b
func :: Integral a => T a -> a
func (T1 x) = x
func (T2 x) = truncate x
The T type says, "Either you already know the type of the value I'm wrapping up, or it's some unknown instance of RealFrac". The T2 constructor existentially quantifies a and packs up a RealFrac dictionary, which we use in the second clause of func to convert from (unknown) a to b. Then, in func, I'm applying an Integral constraint to the a which may or may not be inside the T.

What can type families do that multi param type classes and functional dependencies cannot

I have played around with TypeFamilies, FunctionalDependencies, and MultiParamTypeClasses. And it seems to me as though TypeFamilies doesn't add any concrete functionality over the other two. (But not vice versa). But I know type families are pretty well liked so I feel like I am missing something:
"open" relation between types, such as a conversion function, which does not seem possible with TypeFamilies. Done with MultiParamTypeClasses:
class Convert a b where
convert :: a -> b
instance Convert Foo Bar where
convert = foo2Bar
instance Convert Foo Baz where
convert = foo2Baz
instance Convert Bar Baz where
convert = bar2Baz
Surjective relation between types, such as a sort of type safe pseudo-duck typing mechanism, that would normally be done with a standard type family. Done with MultiParamTypeClasses and FunctionalDependencies:
class HasLength a b | a -> b where
getLength :: a -> b
instance HasLength [a] Int where
getLength = length
instance HasLength (Set a) Int where
getLength = S.size
instance HasLength Event DateDiff where
getLength = dateDiff (start event) (end event)
Bijective relation between types, such as for an unboxed container, which could be done through TypeFamilies with a data family, although then you have to declare a new data type for every contained type, such as with a newtype. Either that or with an injective type family, which I think is not available prior to GHC 8. Done with MultiParamTypeClasses and FunctionalDependencies:
class Unboxed a b | a -> b, b -> a where
toList :: a -> [b]
fromList :: [b] -> a
instance Unboxed FooVector Foo where
toList = fooVector2List
fromList = list2FooVector
instance Unboxed BarVector Bar where
toList = barVector2List
fromList = list2BarVector
And lastly a surjective relations between two types and a third type, such as python2 or java style division function, which can be done with TypeFamilies by also using MultiParamTypeClasses. Done with MultiParamTypeClasses and FunctionalDependencies:
class Divide a b c | a b -> c where
divide :: a -> b -> c
instance Divide Int Int Int where
divide = div
instance Divide Int Double Double where
divide = (/) . fromIntegral
instance Divide Double Int Double where
divide = (. fromIntegral) . (/)
instance Divide Double Double Double where
divide = (/)
One other thing I should also add is that it seems like FunctionalDependencies and MultiParamTypeClasses are also quite a bit more concise (for the examples above anyway) as you only have to write the type once, and you don't have to come up with a dummy type name which you then have to type for every instance like you do with TypeFamilies:
instance FooBar LongTypeName LongerTypeName where
FooBarResult LongTypeName LongerTypeName = LongestTypeName
fooBar = someFunction
vs:
instance FooBar LongTypeName LongerTypeName LongestTypeName where
fooBar = someFunction
So unless I am convinced otherwise it really seems like I should just not bother with TypeFamilies and use solely FunctionalDependencies and MultiParamTypeClasses. Because as far as I can tell it will make my code more concise, more consistent (one less extension to care about), and will also give me more flexibility such as with open type relationships or bijective relations (potentially the latter is solver by GHC 8).
Here's an example of where TypeFamilies really shines compared to MultiParamClasses with FunctionalDependencies. In fact, I challenge you to come up with an equivalent MultiParamClasses solution, even one that uses FlexibleInstances, OverlappingInstance, etc.
Consider the problem of type level substitution (I ran across a specific variant of this in Quipper in QData.hs). Essentially what you want to do is recursively substitute one type for another. For example, I want to be able to
substitute Int for Bool in Either [Int] String and get Either [Bool] String,
substitute [Int] for Bool in Either [Int] String and get Either Bool String,
substitute [Int] for [Bool] in Either [Int] String and get Either [Bool] String.
All in all, I want the usual notion of type level substitution. With a closed type family, I can do this for any types (albeit I need an extra line for each higher-kinded type constructor - I stopped at * -> * -> * -> * -> *).
{-# LANGUAGE TypeFamilies #-}
-- Subsitute type `x` for type `y` in type `a`
type family Substitute x y a where
Substitute x y x = y
Substitute x y (k a b c d) = k (Substitute x y a) (Substitute x y b) (Substitute x y c) (Substitute x y d)
Substitute x y (k a b c) = k (Substitute x y a) (Substitute x y b) (Substitute x y c)
Substitute x y (k a b) = k (Substitute x y a) (Substitute x y b)
Substitute x y (k a) = k (Substitute x y a)
Substitute x y a = a
And trying at ghci I get the desired output:
> :t undefined :: Substitute Int Bool (Either [Int] String)
undefined :: Either [Bool] [Char]
> :t undefined :: Substitute [Int] Bool (Either [Int] String)
undefined :: Either Bool [Char]
> :t undefined :: Substitute [Int] [Bool] (Either [Int] String)
undefined :: Either [Bool] [Char]
With that said, maybe you should be asking yourself why am I using MultiParamClasses and not TypeFamilies. Of the examples you gave above, all except Convert translate to type families (albeit you will need an extra line per instance for the type declaration).
Then again, for Convert, I am not convinced it is a good idea to define such a thing. The natural extension to Convert would be instances such as
instance (Convert a b, Convert b c) => Convert a c where
convert = convert . convert
instance Convert a a where
convert = id
which are as unresolvable for GHC as they are elegant to write...
To be clear, I am not saying there are no uses of MultiParamClasses, just that when possible you should be using TypeFamilies - they let you think about type-level functions instead of just relations.
This old HaskellWiki page does an OK job of comparing the two.
EDIT
Some more contrasting and history I stumbled upon from augustss blog
Type families grew out of the need to have type classes with
associated types. The latter is not strictly necessary since it can be
emulated with multi-parameter type classes, but it gives a much nicer
notation in many cases. The same is true for type families; they can
also be emulated by multi-parameter type classes. But MPTC gives a
very logic programming style of doing type computation; whereas type
families (which are just type functions that can pattern match on the
arguments) is like functional programming.
Using closed type families
adds some extra strength that cannot be achieved by type classes. To
get the same power from type classes we would need to add closed type
classes. Which would be quite useful; this is what instance chains
gives you.
Functional dependencies only affect the process of constraint solving, while type families introduced the notion of non-syntactic type equality, represented in GHC's intermediate form by coercions. This means type families interact better with GADTs. See this question for the canonical example of how functional dependencies fail here.

Haskell Typeclass Instance based on canonical view

As a self assigned exercise of sorts, I'm playing around with implementing an algebra based numeric type heirarchy.
I'd like to specify that if a structure can be viewed in a canonical way as something that satisfies one of my typeclasses, then it should be an instance of that typeclass as well. To that end I've tried essentially the following:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleContexts, FlexibleInstances #-}
class AbGp s a where
plus :: a -> a -> s -> a
zero :: s -> a
minus :: a -> a -> s -> a
class View a b c | a c -> b
view :: a -> b
instance (View s s1 a, AbGp s1 a) => AbGp s a
plus x y s = plus x y (view s)
zero = zero . view
minus x y s = minus x y (view s)
s should be thought of as holding the definitions of the operations in the group, and a as the type of the elements in the group.
But this doesn't work, which isn't surprising, but what I want to do now is:
Suppose I know that some type s, say s that represents a Ring, can be mapped canonically to s1 which is a datastructure I already have an instance for as an AbGp, then I would like s to also be automatically an instance of AbGp. How can I do this?
I'm thinking of doing the following, if it'll work, but I'd like to know if there is a better way:
instance (AbGp s1 a) => AbGp (s1,b) a where
-- ...

Resources