
Hi This is a long message, containing a program which makes heavy use of type classes with functional dependencies, and a query about how the typechecker treats them. It might be a bit of an effort, but I'd be grateful for any comment and advice more experienced Haskellers can spare the time to give me. Er, this ain't no undergrad homework... I'm a dependently typed programmer and a bit of an old Lisphead. What's common to both is that it's fairly easy to write `program reconstruction operations', like the argument permutation function (of which flip is an instance), specified informally thus: Given a permutation p on [1..n] and an n-ary function f, permArg p f x_p(1) .. x_p(n) = f x_1 .. x_n It's easy in Lisp because you can just compute the relevant lambda-expression for permArg p f syntactically, then use it as a program: of course, there's no type system to make sure your p is really a perm and your f has enough arguments. To give permArg a precise type, we have to compute an n-ary permutation of the argument types for an n-ary function space. That is, we need a representation of permutations p from which to compute (1) the type of the permutation function (2) the permutation function itself This isn't that hard with dependent types, because we can use the same kinds of data and program as easily at the level of types as we can at the level of terms. I'm relatively new to Haskell: what attracted me is that recent extensions to the language have introduced a model of computation at the type level via multi-parameter classes with functional dependencies. Although type-level Haskell programming is separate from, different to, and not nearly as powerful as term-level Haskell programming, it's still possible to do some pretty interesting stuff: here's permArg as a Haskell program... Although we can't compute with types over a data encoding of permutations, we can use type classes to make `fake' datatypes one level up. Here's a class representing the natural numbers. Each type in the class has a single element, which we can use to tell the typechecker which instance of the class we mean.
class Nat n
data O = O instance Nat O
data (Nat n) => S n = S n instance (Nat n) => Nat (S n)
Now, for each n in Nat, we need a class Fin n with exactly n instances. A choice of instance represents the position the first argument of an n-ary function gets shifted to. We can make Fin (S n) by embedding Fin n with one type constructor, FS, and chucking in a new type with another, FO.
class (Nat n) => Fin n x | x -> n
data (Nat n) => FO n = FO n instance (Nat n) => Fin (S n) (FO n)
data (Nat n,Fin n x) => FS n x = FS n x instance (Nat n,Fin n x) => Fin (S n) (FS n x)
The class Factorial n contains n! types---enough to represent the permutations. It's computed in the traditional way, but this time the product is cartesian...
class (Nat n) => Factorial n p | p -> n
instance Factorial O () instance (Factorial n p,Fin (S n) x) => Factorial (S n) (x,p)
The operation InsertArg n x r s, where x is in Fin (S n), takes an n-ary function type s and inserts an extra argument type r at whichever of the (S n) positions is selected by x. The corresponding function, insertArg permutes a (S n)-ary function in r -> s by flipping until the first argument has been moved to the nominated position. FS codes `flip the argument further in and keep going'; FO codes `stop flipping'.
class (Nat n,Fin (S n) x) => InsertArg n x r s t | x -> n, x r s -> t, x t -> r s where insertArg :: x -> (r -> s) -> t
instance (Nat n) => InsertArg n (FO n) r s (r -> s) where insertArg (FO _) f = f
instance (Nat n,Fin (S n) x,InsertArg n x r s t) => InsertArg (S n) (FS (S n) x) r (a -> s) (a -> t) where insertArg (FS _ x) f a = insertArg x (flip f a)
PermArg simply works its way down the factorial, performing the InsertArg indicated at each step. permArg is correspondingly built with insertArg.
class (Nat n,Factorial n p) => PermArg n p s t | p s -> t, p t -> s where permArg :: p -> s -> t
instance PermArg O () t t where permArg () t = t
instance (InsertArg n x r t u,PermArg n p s t) => PermArg (S n) (x,p) (r -> s) u where permArg (x,p) f = insertArg x (\r -> permArg p (f r))
This code is accepted by the Feb 2000 version of Hugs, of course with -98 selected. Let's look at some examples: the interesting thing is how the typechecker copes. Here's the instance of permArg which corresponds to flip Main> permArg (FS (S O) (FO O),(FO O,())) ERROR: Unresolved overloading *** Type : (InsertArg (S O) (FS (S O) (FO O)) a b c, InsertArg O (FO O) d e b, PermArg O () f e) => (a -> d -> f) -> c *** Expression : permArg (FS (S O) (FO O),(FO O,())) OK, I wasn't expecting that to work, because I didn't tell it the type of the function to permute: however, the machine did figure it out. Look at where it got stuck: I'd have hoped it would compute that e is f, and hence that b is d -> f, then possibly even that c is d -> a -> f. Isn't that what the functional dependencies say? On the other hand, if I tell it the answer, it's fine. Main> :t permArg (FS (S O) (FO O),(FO O,())) :: (a -> b -> c) -> b -> a -> c permArg (FS (S O) (FO O),(FO O,())) :: (a -> b -> c) -> b -> a -> c First, a nice little monomorphic function.
elemChar :: Char -> [Char] -> Bool elemChar = elem
There's no doubt about the type of the input, but this happens: Main> permArg (FS (S O) (FO O),(FO O,())) elemChar ERROR: Unresolved overloading *** Type : (InsertArg (S O) (FS (S O) (FO O)) Char a b, InsertArg O (FO O) [Char] c a, PermArg O () Bool c) => b *** Expression : permArg (FS (S O) (FO O),(FO O,())) elemChar What am I doing wrong? I hope my program says that c is Bool, and so on. Again, tell it the answer and it checks out: Main> :t (permArg (FS (S O) (FO O),(FO O,())) elemChar) :: [Char] -> Char -> Bool permArg (FS (S O) (FO O),(FO O,())) elemChar :: [Char] -> Char -> Bool Adding some arguments gives enough information about `the answer' to get rid of the explicit typing. Main> permArg (FS (S O) (FO O),(FO O,())) elemChar ['a','b','c'] 'b' True :: Bool It's the same story with arity 3... Main> :t permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) :: (a -> b -> c -> d) -> (c -> a -> b -> d) permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) :: (a -> b -> c -> d) -> c -> a -> b -> d Main> permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) foldl ERROR: Unresolved overloading *** Type : (InsertArg (S (S O)) (FS (S (S O)) (FO (S O))) (a -> b -> a) c d, InsertArg (S O) (FS (S O) (FO O)) a e c, InsertArg O (FO O) [b] f e, PermArg O () a f) => d *** Expression : permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) foldl Main> :t (permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) :: (a -> b -> c -> d) -> (c -> a -> b -> d)) foldl permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) foldl :: [a] -> (b -> a -> b) -> b -> b Main> permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) foldl [1,2,3] (+) 0 6 :: Integer So, am I failing to explain to Hugs why PermArg and InsertArg are programs, despite the explicit functional dependencies, or is the typechecker just not running them? It seems to be expanding PermArg's step case ok, but not executing the base case, leaving InsertArg blocked. Can anyone shed some light on the operational semantics of programming at the type level? Having, said all that, I'm really impressed that even this much is possible in Haskell. It's so nice to be able to write a type that says exactly what I mean. Cheers Conor

C T McBride wrote:
Hi
This is a long message, containing a program which makes heavy use of type classes with functional dependencies, and a query about how the typechecker treats them. It might be a bit of an effort, but I'd be grateful for any comment and advice more experienced Haskellers can spare the time to give me. Er, this ain't no undergrad homework...
Without delving too deeply into your example, it looks like you've bumped into a known bug in Hugs implementation of functional dependencies. You should try GHCI if you can - it doesn't suffer from this bug. --Jeff

Hi Jeff, | Without delving too deeply into your example, it looks like | you've bumped into a known bug in Hugs implementation of | functional dependencies. You should try GHCI if you can - it | doesn't suffer from this bug. Are there any plans to fix the bug in Hugs? (And is there anywhere that the bug is documented?) All the best, Mark

C T McBride wrote:
Hi
This is a long message, containing a program which makes heavy use of type classes with functional dependencies, and a query about how the typechecker treats them. It might be a bit of an effort, but I'd be grateful for any comment and advice more experienced Haskellers can spare the time to give me. Er, this ain't no undergrad homework...
Jeffrey R. Lewis:
Without delving too deeply into your example, it looks like you've bumped into a known bug in Hugs implementation of functional dependencies. You should try GHCI if you can - it doesn't suffer from this bug.
Thanks for the tip! Our local Haskell supremo has pointed me to a version I can run, and that has improved the situation... a bit. Now I get Perm> permArg (FS (S O) (FO O),(FO O,())) No instance for `Show ((r -> s -> s) -> s -> r -> s)' Obviously, there's no Show method, but I was expecting a more general type. But if I tell it the right answer, it believes me Perm> permArg (FS (S O) (FO O),(FO O,())) :: (a -> b -> c) -> b -> a -> c No instance for `Show ((a -> b -> t) -> b -> a -> t)' The main thing is that I can permute a function correctly, without needing an explicit signature: Perm> permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) foldl No instance for `Show ([b] -> (t -> b -> t) -> t -> t)' Still, those too-specific inferred types are disturbing me a little Perm> permArg (FS (S (S O)) (FO (S O)),(FS (S O) (FO O),(FO O,()))) No instance for `Show ((r -> s -> s -> s) -> s -> r -> s -> s)' The above examples show that my code works with the generality it needs to. Is there some `defaulting' mechanism at work here for the inferred types making all those s's the same? But this is definitely progress! Thanks Conor

Dear Conor, thanks for posing the `argument permutation' problem. I had several hours of fun hacking up a solution that works under `ghci' (as Jeff pointed out Hugs probably suffers from a bug). The solution is relatively close to your program, I only simplified the representation of the `factorial numbers' that select a permutation. The program is attached below. Here is a sample interaction (using `ghci -fglasgow-exts PermArg.lhs'): PermArgs> :t pr Int -> Bool -> Char -> [Char] PPermArgs> :t perm (a0 <: a0 <: nil) pr Int -> Bool -> Char -> [Char] ermArgs> :t perm (a0 <: a1 <: nil) pr Int -> Char -> Bool -> [Char] PermArgs> :t perm (a1 <: a0 <: nil) pr Bool -> Int -> Char -> [Char] PermArgs> :t perm (a1 <: a1 <: nil) pr Char -> Int -> Bool -> [Char] PermArgs> :t perm (a2 <: a0 <: nil) pr Bool -> Char -> Int -> [Char] PermArgs> :t perm (a2 <: a1 <: nil) pr Char -> Bool -> Int -> [Char] Cheers, Ralf ---
module PermArgs where
Natural numbers.
data Zero = Zero data Succ nat = Succ nat
Some syntactic sugar.
a0 = Zero a1 = Succ a0 a2 = Succ a1 a3 = Succ a2
Inserting first argument.
class Insert nat a x y | nat a x -> y, nat y -> a x where insert :: nat -> (a -> x) -> y
instance Insert Zero a x (a -> x) where insert Zero f = f instance (Insert nat a x y) => Insert (Succ nat) a (b -> x) (b -> y) where insert (Succ n) f a = insert n (flip f a)
Some test data.
pr :: Int -> Bool -> Char -> String pr i b c = show i ++ show b ++ show c
An example session (using `ghci -fglasgow-exts PermArg.lhs'): PermArgs> :t insert a0 pr Int -> Bool -> Char -> String PermArgs> :t insert a1 pr Bool -> Int -> Char -> String PermArgs> :t insert a2 pr Bool -> Char -> Int -> [Char] PermArgs> :t insert a3 pr No instance for `Insert (Succ Zero) Int String y' arising from use of `insert' at <No locn> Lists.
data Nil = Nil data Cons nat list = Cons nat list
Some syntactic sugar.
infixr 5 <:
(<:) = Cons nil = a0 <: Nil
Permuting arguments.
class Perm list x y | list x -> y, list y -> x where perm :: list -> x -> y
instance Perm Nil x x where perm Nil f = f instance (Insert n a y z, Perm list x y) => Perm (Cons n list) (a -> x) z where perm (Cons d ds) f = insert d (\a -> perm ds (f a))
An example session (using `ghci -fglasgow-exts PermArg.lhs'): PermArgs> :t perm (a0 <: a0 <: nil) pr Int -> Bool -> Char -> [Char] PermArgs> :t perm (a0 <: a1 <: nil) pr Int -> Char -> Bool -> [Char] PermArgs> :t perm (a1 <: a0 <: nil) pr Bool -> Int -> Char -> [Char] PermArgs> :t perm (a1 <: a1 <: nil) pr Char -> Int -> Bool -> [Char] PermArgs> :t perm (a2 <: a0 <: nil) pr Bool -> Char -> Int -> [Char] PermArgs> :t perm (a2 <: a1 <: nil) pr Char -> Bool -> Int -> [Char] PermArgs> :t perm (a2 <: a2 <: nil) pr No instance for `Insert (Succ Zero) Int y y1' arising from use of `perm' at <No locn> No instance for `Insert (Succ Zero) Bool [Char] y' arising from use of `perm' at <No locn>
participants (4)
-
C T McBride
-
Jeffrey R. Lewis
-
Mark P Jones
-
Ralf Hinze