Hi all,

when I reported a typechecker performance problem related to functional dependencies
   http://hackage.haskell.org/trac/ghc/ticket/5970
I promised to try to convert from functional dependencies to type families.

Thus I converted my code and the llvm package to type-families:
   http://code.haskell.org/~thielema/llvm-tf/


Here are some of my experiences:

== Advantages of TypeFamilies ==

* Speed

For what I did the type families solution was considerably faster than the functional dependencies code at least in GHC-7.4.1. Thus the bug in ticket 5970 does no longer hurt me. (In GHC-6.12.3 the conversion to type families made the compilation even slower.)


* Anonymous type function values

One of the most annoying type classes of the llvm package was the IsSized class:

  class (LLVM.IsType a, IsPositive size) => IsSized a size | a -> size

where size is a type-level decimal natural number.

Many llvm functions require that an LLVM type has a size where the particular size is not important. However, I always have to name the size type. I also cannot get rid of it using a subclass, like

  class (IsSized a size) => IsAnonymouslySized a where

The 'size' type is somehow sticky.

The conversion of this type class to type families is straightforward:

  class (IsType a, PositiveT (SizeOf a)) => IsSized a where
     type SizeOf a :: *

Now I have to use SizeOf only if needed. I can also easily define sub-classes like

  class (IsSized a) => C a where


* No TypeSynonymInstances

At the right hand side of a 'type instance' I can use type synonyms like

  type instance F T = String

without the TypeSynonymInstance extension. This feels somehow more correct than refering to a type synonym in a class instance head like in

  instance C T String where

The compiler does not need to analyze String in order to find the correct instance.


* No FlexibleInstances

The same applies to

  instance C (T a) (A (B a))

which is a flexible instance that is not required for

  type instance F (T a) = A (B a)


* No MultiParamTypeClass, No UndecidableInstances

I have some type classes that convert a type to another type and a tuple of types to another tuple of types where the element types are converted accordingly. With functional dependencies:

  class MakeValueTuple haskellTuple llvmTuple | haskellTuple -> llvmTuple where

  instance (MakeValueTuple ha la, MakeValueTuple hb lb) =>
               MakeValueTuple (ha,hb) (la,lb)

The class is a multi-parameter type class and the instance is undecidable.

This is much simpler with type families:

  class MakeValueTuple haskellTuple where
    type ValueTuple haskellTuple :: *

  instance (MakeValueTuple ha, MakeValueTuple hb) =>
               MakeValueTuple (ha,hb) where
    type ValueTuple (ha,hb) = (ValueTuple ha, ValueTuple hb)



Thus summarized: Type families may replace several other type extensions. If I ignore the associated type functions then many classes become Haskell 98 with Haskell 98 instances. This is good because those instances prevent instance conflicts with other non-orphan instances.


== Disadvantage of TypeFamilies ==

* Redundant instance arguments

I have to write the type arguments both in the instance head and in the function argument. This is especially annoying in the presence of multi-parameter type classes with bidirectional dependencies. E.g.

class (a ~ Input parameter b, b ~ Output parameter a) => C parameter a b where
   type Input  parameter b :: *
   type Output parameter a :: *
   process :: Causal p (parameter, a) b

instance (...) => C (FilterParam a) v (FilterResult v) where
   type Input  (FilterParam a) (FilterResult v) = v
   type Output (FilterParam a) v = FilterResult v


With functional dependencies it was:

class C parameter a b | parameter a -> b, parameter b -> a where
   process :: Causal p (parameter, a) b

instance (...) => C (FilterParam a) v (FilterResult v) where


* Bidirectional dependencies

In GHC-6.12.3 it was not possible to write

  class (a ~ Back b, b ~ Forth a) => C a b where

Fortunately, this is now allowed in GHC-7. But bidirectional dependencies are still cumbersome to work with as shown in the example above.


* Equality constraints are not supported for newtype deriving

Not so important, just for completeness:
  http://hackage.haskell.org/trac/ghc/ticket/6088


== Confusions ==

* Upper case type function names

Why are type function names upper case, not lower case? They are not constructors after all. Maybe this is one reason, why I forget from time to time that type functions are not injective.

Sure, lower-case type variables are implicitly forall quantified in Haskell 98. In the presence of lower-case type functions we would need explicit forall quantification.

* Why can associated types not be exported by C(AssocType) syntax?

Why must they be exported independently from the associated class?


* FlexibleContexts

The context (Class (TypeFun a)) requires FlexibleContexts extension, whereas the equivalent (TypeFun a ~ b, Class b) does not require FlexibleContexts.



Best,
Henning

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to