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

2

6

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).

Lsd answered 28/7, 2016 at 14:59 Comment(10)
Type families generally perform much better than fundeps - especially when implementing type functions.Crosstree
There's also a matter of readability. The equivalent of type F a = G (H (G a) (G a)) expressed through FunDeps requires several constraints, involving a few auxiliary type variables. When I read such constraints, I found myself to try to express them in a functional form. Perhaps this is because I'm more used to read functional code than prolog.Bailor
@Crosstree Why is that? That seems incredibly strange because the examples where both options are viable look completely identical in terms of type resolution and what not to me. Is it just a flaw in the current implementation of either FunctionalDependencies or MultiParamTypeClasses or their interaction? Or is it something more fundamental? I am really hoping for the former as it would be nice to not have to use a different and seemingly more verbose syntax half the time for the same thing just for performance reasons.Lsd
@Bailor would you mind going a little more in depth with what you mean there? I am a little confused because usually I see either type F a or type F a :: * with no = or I see type F G = ... with a concrete type immediately after F, why do you have a type variable after F AND an =. I am somewhat new to this stuff.Lsd
@Bailor if you are talking about using type outside of TypeFamilies which seems like the only way to make your example work, then I don't see how anything is different between TypeFamilies and FunctionalDependencies, if there is any difference would it be alleviated by TypeSynonymInstances?Lsd
My example is indeed short, but assume you have type families G,H suitably defined. Then you can define type family F a :: * ; type instance F a = G (H (G a) (G Bool)) -- or you could even do that through a type synonym (in this simple setting). Now, assume that G,H are instead typeclasses with fundeps: class G a b | a -> b ; instance .... How to achieve the same composition F does? You indeed can, but it is not very convienient nor readable, at least to me.Bailor
@Bailor What would be the point of such an instance / family? Because the family cannot have any additional instances added to it, as forall a. a is the most polymorphic type possible, and you have already given an install for forall a. a. At that point why not just use type F a = G (H (G a) (G Bool)) and use it directly whenever needed?Lsd
My point is that I can use type F a = G (H (G a) (G Bool)) if G,H are families, but not if they are classes with fundeps.Bailor
@Bailor Oohhh, ok thank you that makes a lot more sense. I'm starting to see why TypeFamilies are more "functional" and thus more nestable / composable / flexible etc.Lsd
A challenge from #haskell yesterday: write a function to convert a list to an HList (existentially quantified). Addendum to the challenge: make sure you can convert it back. Now it may be possible to do this without type families, but I found type family Replicate (n :: Nat) a :: [*] very helpful.Bathulda
C
3

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.

Cristie answered 28/7, 2016 at 16:32 Comment(2)
Ok I think I finally more or less get it. Am I correct in thinking that if all you are doing is specifying type relations like I did in the original post AND you don't use them in any particularly non-standard way then FunctionalDependencies and MultiParamTypeClasses work quite well. But if you try to go beyond that and do true type level programming, then you are much better off with TypeFamilies. In terms of both flexibility and general elegance. And thus because of that you should just stick to TypeFamilies in general to maintain that elegance and flexibility.Lsd
@Lsd Yep, that's a good summary. TypeFamilies is newer than MultiParamTypeClasses and was, IFRC, meant to make type level programming much more like value type programming (instead of logical equivalences).Cristie
C
1

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.

Cerotype answered 28/7, 2016 at 17:35 Comment(1)
Type-level type equality was figured out in HList 2004. Some improvements to FunDeps (and overlaps) has made it smoother in GHC 7.10. (It also needs UndecidableInstances, but that's a benign extension.) I see no "fail" in that question/answers.Autosuggestion

© 2022 - 2024 — McMap. All rights reserved.