A small (?) problem with type families
 
            Hi all, This email is literate Haskell. I'm trying to use type families to express some dependencies between type classes, and I'm running into trouble, I think because I'm producing chains of dependencies which the checker can't resolve... Here's a minimised version of the state I've got myself into. :-)
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-}
module Families where
First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
Now another type family, where the type Q is functionally dependent on the type P, _and_ it must also be an instance of the X class.
class (X (Q s)) => P s where type Q s
(Perhaps there's a better way to express that dependency?) Now a function which takes a value whose type is an instance of the Y depending on the Q depending on the P. (Phew!) The function just tries to call enact on that value.
bar :: P s => Y (Q s) -> () bar w = enact w
The error we get is: src/Families.lhs:35:16: Couldn't match expected type `Y a' against inferred type `Y (Q s)' In the first argument of `enact', namely `w' In the expression: enact w In the definition of `bar': bar w = enact w Presumably this way I'm chaining type dependencies is flawed. Any suggestions on how to improve it, and/or what to read to understand what I'm dealing with better? (So far I've read "Fun with type functions V2", but that's about it, and I admit I didn't grok it all.) Thanks! -Andy
 
            On Fri, Nov 13, 2009 at 3:26 PM, Andy Gimblett 
First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
This is ambiguous. Type families are not injective (that is, Y a ~ Y b
does not imply a ~ b), so there's no way for the compiler to figure
out which instance of X is being used when it encounters enact.
Given these instances,
instance X Int where
    type Y Int = Bool
    enact _ = ()
instance X Char where
    type Y Char = Bool
    enact _ = undefined
What is "enact False"?
I recall seeing a discussion of this in the GHC documentation, but I
can't seem to locate it.
-- 
Dave Menendez 
 
            Am Freitag 13 November 2009 21:36:59 schrieb David Menendez:
On Fri, Nov 13, 2009 at 3:26 PM, Andy Gimblett
wrote: First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
This is ambiguous. Type families are not injective (that is, Y a ~ Y b does not imply a ~ b), so there's no way for the compiler to figure out which instance of X is being used when it encounters enact.
Given these instances,
instance X Int where type Y Int = Bool enact _ = ()
instance X Char where type Y Char = Bool enact _ = undefined
What is "enact False"?
I recall seeing a discussion of this in the GHC documentation, but I can't seem to locate it.
Perhaps http://www.haskell.org/haskellwiki/GHC/Type_families#Frequently_asked_questi... ?
 
            On Fri, Nov 13, 2009 at 4:00 PM, Daniel Fischer
Am Freitag 13 November 2009 21:36:59 schrieb David Menendez:
I recall seeing a discussion of this in the GHC documentation, but I can't seem to locate it.
Perhaps http://www.haskell.org/haskellwiki/GHC/Type_families#Frequently_asked_questi... ?
That's the one. I keep forgetting there's additional material on the wiki.
-- 
Dave Menendez 
 
            On Fri, Nov 13, 2009 at 3:36 PM, David Menendez 
On Fri, Nov 13, 2009 at 3:26 PM, Andy Gimblett
wrote: First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
This is ambiguous. Type families are not injective (that is, Y a ~ Y b does not imply a ~ b), so there's no way for the compiler to figure out which instance of X is being used when it encounters enact.
Note: that if you need this injectivity you can use a data family instead.
 
            Ack. I've just realised that P/Q is not a functional dependency. I need to use a multi-parameter type class there. So my question is probably completely pointless - sorry! Thanks anyway, -Andy On 13 Nov 2009, at 20:26, Andy Gimblett wrote:
Hi all,
This email is literate Haskell. I'm trying to use type families to express some dependencies between type classes, and I'm running into trouble, I think because I'm producing chains of dependencies which the checker can't resolve... Here's a minimised version of the state I've got myself into. :-)
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-}
module Families where
First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
Now another type family, where the type Q is functionally dependent on the type P, _and_ it must also be an instance of the X class.
class (X (Q s)) => P s where type Q s
(Perhaps there's a better way to express that dependency?)
Now a function which takes a value whose type is an instance of the Y depending on the Q depending on the P. (Phew!) The function just tries to call enact on that value.
bar :: P s => Y (Q s) -> () bar w = enact w
The error we get is:
src/Families.lhs:35:16: Couldn't match expected type `Y a' against inferred type `Y (Q s)' In the first argument of `enact', namely `w' In the expression: enact w In the definition of `bar': bar w = enact w
Presumably this way I'm chaining type dependencies is flawed. Any suggestions on how to improve it, and/or what to read to understand what I'm dealing with better? (So far I've read "Fun with type functions V2", but that's about it, and I admit I didn't grok it all.)
Thanks!
-Andy
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            Hahaha, this is what I get for trying to think about Haskell on a Friday night. Now I think it _is_ a functional dependency after all. Who knows how long it will be before I change my mind again? :-) I shall think about this more carefully tomorrow... Thanks again, -Andy On 13 Nov 2009, at 20:48, Andy Gimblett wrote:
Ack. I've just realised that P/Q is not a functional dependency. I need to use a multi-parameter type class there. So my question is probably completely pointless - sorry!
Thanks anyway,
-Andy
On 13 Nov 2009, at 20:26, Andy Gimblett wrote:
Hi all,
This email is literate Haskell. I'm trying to use type families to express some dependencies between type classes, and I'm running into trouble, I think because I'm producing chains of dependencies which the checker can't resolve... Here's a minimised version of the state I've got myself into. :-)
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-}
module Families where
First a type family where the type Y is functionally dependent on the type X, and we have a function from Y to ().
class X a where type Y a enact :: Y a -> ()
Now another type family, where the type Q is functionally dependent on the type P, _and_ it must also be an instance of the X class.
class (X (Q s)) => P s where type Q s
(Perhaps there's a better way to express that dependency?)
Now a function which takes a value whose type is an instance of the Y depending on the Q depending on the P. (Phew!) The function just tries to call enact on that value.
bar :: P s => Y (Q s) -> () bar w = enact w
The error we get is:
src/Families.lhs:35:16: Couldn't match expected type `Y a' against inferred type `Y (Q s)' In the first argument of `enact', namely `w' In the expression: enact w In the definition of `bar': bar w = enact w
Presumably this way I'm chaining type dependencies is flawed. Any suggestions on how to improve it, and/or what to read to understand what I'm dealing with better? (So far I've read "Fun with type functions V2", but that's about it, and I admit I didn't grok it all.)
Thanks!
-Andy
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
- 
                 Andy Gimblett Andy Gimblett
- 
                 Daniel Fischer Daniel Fischer
- 
                 David Menendez David Menendez
- 
                 Edward Kmett Edward Kmett