Deep fmap with GADTs and type families.

Greetings, Someone on comp.lang.functional was asking how to map through arbitrary nestings of lists, so I thought I'd demonstrate how his non-working ML function could actually be typed in GHC, like so: --- snip --- {-# LANGUAGE TypeFamilies, GADTs, EmptyDataDecls, Rank2Types, ScopedTypeVariables #-} data Z data S n data Nat n where Z :: Nat Z S :: Nat n -> Nat (S n) type family Nest n (f :: * -> *) a :: * type instance Nest Z f a = f a type instance Nest (S n) f a = f (Nest n f a) deepMap :: Nat n -> (a -> b) -> Nest n [] a -> Nest n [] b deepMap Z f = map f deepMap (S n) f = map (deepMap n f) --- snip --- This works. However, the straight forward generalisation doesn't: --- snip --- deepFMap :: Functor f => Nat n -> (a -> b) -> Nest n f a -> Nest n f b deepFMap Z f = fmap f deepFMap (S n) f = fmap (deepFMap n f) --- snip --- This fails with a couple errors like: Map.hs:25:19: Couldn't match expected type `Nest n1 f b' against inferred type `Nest n1 f1 b' In the expression: fmap (deepFMap n f) In the definition of `deepFMap': deepFMap (S n) f = fmap (deepFMap n f) for reasons I don't really understand. So I tried the following: --- snip --- newtype FuntorD f = F { fdmap :: forall a b. (a -> b) -> f a -> f b } deepFDMap :: FunctorD f -> Nat n -> (a -> b) -> Nest n f a -> Nest n f b deepFDMap d Z f = fdmap d f deepFDMap d (S n) f = fdmap d (deepFDMap d n f) --- snip --- This works, but to my surprise "deepFMap = deepFDMap (F fmap)" gives the exact same error as above. Bringing my situation to #haskell, two solutions were found: --- snip --- deepFMap :: forall n f a b. Functor f => Nat n -> (a -> b) -> Nest n f a -> Nest n f b deepFMap = deepFDMap (F fmap :: FunctorD f) data Proxy (f :: * -> *) = Proxy deepFMap' :: Functor f => Proxy f -> Nat n -> (a -> b) -> Nest n f a -> Nest n f b deepFMap' _ Z f = fmap f deepFMap' p (S n) f = fmap (deepFMap p n f) --- snip --- But we've so far not been able to find a way of merely annotating the original into working. So, I was wondering if any of the more knowledgeable folks here could illuminate what's going wrong here, and whether I should expect my original code to work or not. Thanks in advance. -- Dan

On Thu, Mar 5, 2009 at 10:07 PM, Dan Doel
But we've so far not been able to find a way of merely annotating the original into working. So, I was wondering if any of the more knowledgeable folks here could illuminate what's going wrong here, and whether I should expect my original code to work or not.
I'll bet the problem has to do with the fact that "f" only appears in
"Nest n f a", so the type checker can't figure out what "f" is.
Here are two other variants that work.
deepFMap :: Functor f => Nat n -> (a -> b) -> Nest n f a -> Nest n f b
deepFMap Z f = fmap f
deepFMap (S n) f = deepFMapS n f
deepFMapS :: Functor f => Nat n -> (a -> b) -> f (Nest n f a) -> f (Nest n f b)
deepFMapS Z f = fmap (fmap f)
deepFMapS (S n) f = fmap (deepFMapS n f)
-- alternative:
-- deepFMapS (S n) f = fmap (deepFMap (S n) f)
type family Nest' n (f :: * -> *) a :: *
type instance Nest' Z f a = a
type instance Nest' (S n) f a = f (Nest' n f a)
deepFMap' :: Functor f => Nat n -> (a -> b) -> f (Nest' n f a) -> f
(Nest' n f b)
deepFMap' Z f = fmap f
deepFMap' (S n) f = fmap (deepFMap' n f)
--
Dave Menendez

David Menendez:
On Thu, Mar 5, 2009 at 10:07 PM, Dan Doel
wrote: But we've so far not been able to find a way of merely annotating the original into working. So, I was wondering if any of the more knowledgeable folks here could illuminate what's going wrong here, and whether I should expect my original code to work or not.
I'll bet the problem has to do with the fact that "f" only appears in "Nest n f a", so the type checker can't figure out what "f" is.
Exactly. In other words, the signature is ambiguous. Manuel

Dan's example fails thus: | Map.hs:25:19: | Couldn't match expected type `Nest n1 f b' | against inferred type `Nest n1 f1 b' | In the expression: fmap (deepFMap n f) | In the definition of `deepFMap': | deepFMap (S n) f = fmap (deepFMap n f) | | for reasons I don't really understand. So I tried the following: For what it's worth, here's why. Suppose we have type family N a :: * f :: forall a. N a -> Int f = <blah> g :: forall b. N b -> Int g x = 1 + f x The defn of 'g' fails with a very similar error to the one above. Here's why. We instantiate the occurrence of 'f' with an as-yet-unknown type 'alpha', so at the call site 'f' has type N alpha -> Int Now, we know from g's type sig that x :: N b. Since f is applies to x, we must have N alpha ~ N b Does that imply that (alpha ~ b)? Alas no! If t1=t2 then (N t1 = N t2), of course, but *not* vice versa. For example, suppose that type instance N [c] = N c Now we could solve the above with (alpha ~ [b]), or (alpha ~ [[b]]). You may say a) There is no such instance. Well, but you can see it pushes the search for a (unique) solution into new territory. b) It doesn't matter which solution the compiler chooses: any will do. True in this case, but false if f :: forall a. (Num a) => N a -> Int. Now it matters which instance is chosen. This kind of example encapsulates the biggest single difficulty with using type families in practice. What is worse is that THERE IS NO WORKAROUND. You *ought* to be able to add an annotation to guide the type checker. Currently you can't. The most obvious solution would be to allow the programmer to specify the types at which a polymorphic function is called, like this: g :: forall b. N b -> Int g x = 1 + f {b} x The {b} says that f takes a type argument 'b', which should be used to instantiate its polymorphic type variable 'a'. Being able to do this would be useful in other circumstances (eg impredicative polymorphism). The issue is really the syntax, and the order of type variables in an implicit forall. Anyway I hope this helps clarify the issue. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Dan Doel | Sent: 06 March 2009 03:08 | To: glasgow-haskell-users@haskell.org | Subject: Deep fmap with GADTs and type families. | | Greetings, | | Someone on comp.lang.functional was asking how to map through arbitrary | nestings of lists, so I thought I'd demonstrate how his non-working ML | function could actually be typed in GHC, like so: | | --- snip --- | | {-# LANGUAGE TypeFamilies, GADTs, EmptyDataDecls, | Rank2Types, ScopedTypeVariables #-} | | data Z | data S n | | data Nat n where | Z :: Nat Z | S :: Nat n -> Nat (S n) | | type family Nest n (f :: * -> *) a :: * | | type instance Nest Z f a = f a | type instance Nest (S n) f a = f (Nest n f a) | | deepMap :: Nat n -> (a -> b) -> Nest n [] a -> Nest n [] b | deepMap Z f = map f | deepMap (S n) f = map (deepMap n f) | | --- snip --- | | This works. However, the straight forward generalisation doesn't: | | --- snip --- | | deepFMap :: Functor f => Nat n -> (a -> b) -> Nest n f a -> Nest n f b | deepFMap Z f = fmap f | deepFMap (S n) f = fmap (deepFMap n f) | | --- snip --- | | This fails with a couple errors like: | | Map.hs:25:19: | Couldn't match expected type `Nest n1 f b' | against inferred type `Nest n1 f1 b' | In the expression: fmap (deepFMap n f) | In the definition of `deepFMap': | deepFMap (S n) f = fmap (deepFMap n f) | | for reasons I don't really understand. So I tried the following: | ...rest snipped...

On Monday 09 March 2009 11:56:14 am Simon Peyton-Jones wrote:
For what it's worth, here's why. Suppose we have
type family N a :: *
f :: forall a. N a -> Int f = <blah>
g :: forall b. N b -> Int g x = 1 + f x
The defn of 'g' fails with a very similar error to the one above. Here's why. We instantiate the occurrence of 'f' with an as-yet-unknown type 'alpha', so at the call site 'f' has type N alpha -> Int Now, we know from g's type sig that x :: N b. Since f is applies to x, we must have N alpha ~ N b
I think this explains my confusion. I was thinking roughly in terms like, "I need 'N b -> Int'; I have 'forall a. N a -> Int', so instantiate 'a' to 'b'." Not in terms of collecting constraints and unifying after the fact. From the latter perspective the ambiguity makes sense.
This kind of example encapsulates the biggest single difficulty with using type families in practice. What is worse is that THERE IS NO WORKAROUND.
I suppose one can always add arguments like the "Proxy" to functions to disambiguate, but that certainly isn't ideal.
Anyway I hope this helps clarify the issue.
Yes; thanks. -- Dan
participants (4)
-
Dan Doel
-
David Menendez
-
Manuel M T Chakravarty
-
Simon Peyton-Jones