
Hi-- More silly typeclass questions. I'm not sure the right way to ask it, so I'll start with a failed code snippet: data Foo a = Foo a class TwoPi a where div2pi :: (Floating b) => a -> b instance (Floating a) => TwoPi (Foo a) where div2pi (Foo a) = a / (2*pi) instance TwoPi Float where div2pi a = a / (2*pi) This code is obviously meaningless, but I'm trying to figure out how you can create instances of a typeclass for data types of different kinds. I have a similar piece of code that works: data Foo a = Foo a class Testable a where isPos :: a -> Bool instance (Ord b, Num b) => Testable (Foo b) where isPos (Foo b) = b > 0 instance Testable Float where isPos a = a > 0 One obvious difference is that the type of isPos is a -> Bool, with a defined type as the return. I'd rather not commit to a specific Floating type up front (I'd prefer sometimes Float sometimes Double, depending on the 'a' in Foo a, but trying to declare it as Float doesn't help me. This fails: data Foo a = Foo a class TwoPi a where div2pi :: a -> Float instance (Floating b) => TwoPi (Foo b) where div2pi (Foo b) = b / (2*pi) instance TwoPi Float where div2pi a = a / (2*pi) The errors I'm getting are various permutations of: Couldn't match expected type `Float' against inferred type `b' `b' is a rigid type variable bound by the instance declaration at gcbTestBad.hs:8:19 In the expression: b / (2 * pi) In the definition of `div2pi': div2pi (Foo b) = b / (2 * pi) In the instance declaration for `TwoPi (Foo b)' What is the difference between these last two cases ("a -> Bool" and "a -> Float"), and is there anyway to make "a -> b" work? Thanks-- Greg

El vie, 27-08-2010 a las 01:58 -0700, Greg escribió:
Hi--
More silly typeclass questions. I'm not sure the right way to ask it, so I'll start with a failed code snippet:
data Foo a = Foo a
class TwoPi a where div2pi :: (Floating b) => a -> b
instance (Floating a) => TwoPi (Foo a) where div2pi (Foo a) = a / (2*pi)
a/(2*pi) has type Floating a => a, where a is the type of a in Foo a. the class declaration however requires to be able to return a value of type Floating b => b for any type b, no relation to a whatsoever.
instance TwoPi Float where div2pi a = a / (2*pi)
a/(2*pi) has type Float (because a has type Float), so this again can not work.
You would need a function f::(Floating b) => Float -> b for this to work. In the former, you would need a function f::(Floating a, Floating b) => a -> b.
This code is obviously meaningless, but I'm trying to figure out how you can create instances of a typeclass for data types of different kinds.
I have a similar piece of code that works:
data Foo a = Foo a
class Testable a where isPos :: a -> Bool
instance (Ord b, Num b) => Testable (Foo b) where isPos (Foo b) = b > 0
b > 0 has type Bool, no matter what type of number b is. so this is ok.
instance Testable Float where isPos a = a > 0
same here
One obvious difference is that the type of isPos is a -> Bool, with a defined type as the return. I'd rather not commit to a specific Floating type up front (I'd prefer sometimes Float sometimes Double, depending on the 'a' in Foo a, but trying to declare it as Float doesn't help me. This fails:
data Foo a = Foo a
class TwoPi a where div2pi :: a -> Float
instance (Floating b) => TwoPi (Foo b) where div2pi (Foo b) = b / (2*pi)
b/(2*pi) has type Floating b => b, not Float. You would need a function of type Floating b => b -> Float.
instance TwoPi Float where div2pi a = a / (2*pi)
This is ok
What is the difference between these last two cases ("a -> Bool" and "a -> Float"),
The difference is not between these type, but between (>), and (/). (>) returns Bool, no matter the type of its arguments. (/) returns sth of the same type as its arguments.
and is there anyway to make "a -> b" work?
The closest is probably using a function like: realToFrac::(Real a, Fractional b) => a -> b
then you can write sth like data Foo a = Foo a class TwoPi a where div2pi :: (Floating b) => a -> b instance (Real a, Floating a) => TwoPi (Foo a) where div2pi (Foo a) = a / (2*pi) Jürgen

Hi-- More silly typeclass questions. I'm not sure the right way to ask it, so I'll start with a failed code snippet: data Foo a = Foo a class TwoPi a where div2pi :: (Floating b) => a -> b instance (Floating a) => TwoPi (Foo a) where div2pi (Foo a) = a / (2*pi) a/(2*pi) has type Floating a => a, where a is the type of a in Foo a.
I'm still having a hard time finding a way to make this work, even given the fine suggestions from Tobias and Jürgen. I suspect there's some piece of information that the compiler can't make sense of that I'm just not seeing-- a case of it insisting on doing what I say instead of what I mean... =)
I guess the problem I'm having is finding a way to treat parametric and non-parametric types interchangeably. The syntax doesn't seem to exist that will allow me to say:
div2pi :: (Floating a) => a -> a -- for non parametric types (ie. Float)
and
div2pi :: (Floating b) => a b -> b -- for parametric types (ie. Foo Float)
In addition, I'm having a hard time understanding the errors I'm getting from constructs like this:
data Foo a = Foo a
class TwoPi a where
div2pi :: (Floating b) => a -> b
instance (Floating a) => TwoPi (Foo a) where
div2pi (Foo x) = x / (2*pi)
{- only this code, no other instances in the file -}
It complains that I can't match expected b against inferred a where
`b' is a rigid type variable bound by
the type signature for `div2pi' at gcbTest.hs:6:22
which points immediately before the 'b' in (Floating b) of the div2pi type statement, and
`a' is a rigid type variable bound by
the instance declaration at gcbTest.hs:8:19
which points immediately before the 'a' in the (Floating a) of the instance definition. It sounds like it's saying there's an explicit conflict between two type variables, both constrained identically. Is the problem instead that they aren't well enough constrained? It wants to know what instance of the Floating class to expect? I would hope that it wouldn't care whether I provided Foo Float or Foo Double, and would return whatever type it received.
Here's the full error:
Couldn't match expected type `b' against inferred type `a'
`b' is a rigid type variable bound by
the type signature for `div2pi' at gcbTest.hs:6:22
`a' is a rigid type variable bound by
the instance declaration at gcbTest.hs:8:19
In the expression: x / (2 * pi)
In the definition of `div2pi': div2pi (Foo x) = x / (2 * pi)
In the instance declaration for `TwoPi (Foo a)'
Thanks--
Greg
On Aug 27, 2010, at 02:31 AM, Jürgen Doser
instance TwoPi Float where div2pi a = a / (2*pi) a/(2*pi) has type Float (because a has type Float), so this again can not work.
You would need a function f::(Floating b) => Float -> b for this to work. In the former, you would need a function f::(Floating a, Floating b) => a -> b.
This code is obviously meaningless, but I'm trying to figure out how you can create instances of a typeclass for data types of different kinds. I have a similar piece of code that works: data Foo a = Foo a class Testable a where isPos :: a -> Bool instance (Ord b, Num b) => Testable (Foo b) where isPos (Foo b) = b > 0 b > 0 has type Bool, no matter what type of number b is. so this is ok.
instance Testable Float where isPos a = a > 0 same here One obvious difference is that the type of isPos is a -> Bool, with a defined type as the return. I'd rather not commit to a specific Floating type up front (I'd prefer sometimes Float sometimes Double, depending on the 'a' in Foo a, but trying to declare it as Float doesn't help me. This fails: data Foo a = Foo a class TwoPi a where div2pi :: a -> Float instance (Floating b) => TwoPi (Foo b) where div2pi (Foo b) = b / (2*pi) b/(2*pi) has type Floating b => b, not Float. You would need a function of type Floating b => b -> Float.
instance TwoPi Float where div2pi a = a / (2*pi) This is ok
What is the difference between these last two cases ("a -> Bool" and "a -> Float"),
The difference is not between these type, but between (>), and (/). (>) returns Bool, no matter the type of its arguments. (/) returns sth of the same type as its arguments.
and is there anyway to make "a -> b" work?
The closest is probably using a function like: realToFrac::(Real a, Fractional b) => a -> b then you can write sth like data Foo a = Foo a class TwoPi a where div2pi :: (Floating b) => a -> b instance (Real a, Floating a) => TwoPi (Foo a) where div2pi (Foo a) = a / (2*pi) Jürgen _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 8/27/10 22:58 , Greg wrote:
I'm still having a hard time finding a way to make this work, even given the fine suggestions from Tobias and Jürgen. I suspect there's some piece of information that the compiler can't make sense of that I'm just not seeing-- a case of it insisting on doing what I say instead of what I mean... =)
I guess the problem I'm having is finding a way to treat parametric and non-parametric types interchangeably. The syntax doesn't seem to exist that will allow me to say:
div2pi :: (Floating a) => a -> a -- for non parametric types (ie. Float) and div2pi :: (Floating b) => a b -> b -- for parametric types (ie. Foo Float)
In addition, I'm having a hard time understanding the errors I'm getting from constructs like this:
data Foo a = Foo a
class TwoPi a where div2pi :: (Floating b) => a -> b
You were told about this already: because "b" is only mentioned in the result of div2pi, it must be able to return *any* "b" that has a Floating instance. But then you say
instance (Floating a) => TwoPi (Foo a) where div2pi (Foo x) = x / (2*pi)
An instance applies to a *specific* type; thus, this instance declaration forces a *specific* type on the result of div2pi, when the class declaration says it must be able to return *any* type. Expanding the types, the class declaration says
div2pi :: forall b. (Floating a, Floating b) => a -> b
but the instance declares
div2pi :: (Floating a) => a -> a
The instance doesn't conform to the class definition; it includes a constraint that the class does not, as the class insists that the type of the result must be independent of the type of the argument, while the instance insists that they must be identical. Perhaps the correct question is "what exactly are you trying to do?" - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkx4f0IACgkQIn7hlCsL25WexQCfTWxZxqchxvAB0Dm1wWwYQIrq sBQAoLeaz8Lq6ydO5WJPu679WyNEu8w0 =BnBu -----END PGP SIGNATURE-----

On Aug 27, 2010, at 8:15 PM, Brandon S Allbery KF8NH wrote:
You were told about this already:
No doubt I'm being quite dense here. I think your re-explanation may have clicked though:
because "b" is only mentioned in the result of div2pi, it must be able to return *any* "b" that has a Floating instance.
But then you say
instance (Floating a) => TwoPi (Foo a) where div2pi (Foo x) = x / (2*pi)
An instance applies to a *specific* type; thus, this instance declaration forces a *specific* type on the result of div2pi, when the class declaration says it must be able to return *any* type.
Expanding the types, the class declaration says
div2pi :: forall b. (Floating a, Floating b) => a -> b
but the instance declares
div2pi :: (Floating a) => a -> a
The instance doesn't conform to the class definition; it includes a constraint that the class does not, as the class insists that the type of the result must be independent of the type of the argument, while the instance insists that they must be identical.
I've been working on the assumption, perhaps despite attempts to teach me otherwise, that the class is essentially the interface to the rest of the world. That is, the class is the guarantee. The instance, then, can do no less than the class interface has guaranteed. In this case, for example, I've been assuming that the type variable 'b' in my class definition meant "div2pi will result in a value of a type which is an instance of the Floating class". Then, since my instance method resulted in a Float, which is an instance of the Floating class, everything should be happy. If my instance method resulted in a Double, it would be equally happy. I think what you're saying is that not only can an instance do no less than the class has guaranteed, it can do no *more*-- meaning the instance can't further restrict the return type even if that return type still conforms to the class definition. In this case returning a Float breaks the class contract because I've gone and said what type of Floating type will be returned. The class definition doesn't mean "div2pi can return any type of Floating value", it means "div2pi *will* return any type of floating value". I have a harder time working out why returning a "(Floating a) => a" is seen as different. If I understand what Jürgen was saying, it's because the "a" in this case is specifically the "a" in "Foo a", which nails it down again. If this is right, then my class definition:
class TwoPi a where div2pi :: (Floating b) => a -> b
is essentially impossible to conform to because b is completely untethered to anything else in the code and not all "(Floating b)"'s are created equal. I think the intent of the functional dependency in the suggestion you provided in your second email is essentially to tether b to something. Unfortunately if chokes in the second, non-Foo, instance. Am I getting this right? Rereading Jürgen's response, this seems to fit with his explanation as well-- I just didn't grasp it. I think I've mistakenly been thinking of instances as more like subclasses, but that's apparently not quite right (thus the "instance" keyword, I suppose).
Perhaps the correct question is "what exactly are you trying to do?"
I'm literally just trying to understand the type system and its syntax. It's the part of Haskell that feels most foreign, and I'm trying to work through the implications. Typeclasses provide a mechanism to abstract operations over multiple types, as you mentioned in the thread for my last question. What I'm trying to figure out now is what kinds of types they can be abstracted over. I'm looking to get the result: "((5.6,Foo 9.8),(0.8912676813146139,1.5597184423005745))" From code that looks kind of like this : data Foo a = Foo a deriving (Show) x :: Float x= 5.6 y :: Foo Double y= Foo 9.8 class {-something-} TwoPi {-something-} where div2pi :: {-something-} instance {-something-} TwoPi Foo where div2pi (Foo b) = b / (2*pi) instance TwoPi Float where div2pi a = a / (2*pi) main = do print ((x,y),(div2pi x, div2pi y)) Thanks-- Greg

El sáb, 28-08-2010 a las 03:44 -0700, Greg escribió:
[...]
The class definition doesn't mean "div2pi can return any type of Floating value", it means "div2pi *will* return any type of floating value".
I would say it like this: div2pi does not return a type of Floating value of its own choosing, it is able to return every type of Floating value (the concrete type is then chosen by the context in each case where div2pi is used).
[...]
If this is right, then my class definition:
class TwoPi a where div2pi :: (Floating b) => a -> b
is essentially impossible to conform to because b is completely untethered to anything else in the code and not all "(Floating b)"'s are created equal.
Actually, it is possible, because of functions like realToFrac, which return a type-class polymorphic value. Unfortunately, I have botched up the example in my post. Sorry for that. Corrected code is below.
Typeclasses provide a mechanism to abstract operations over multiple types, as you mentioned in the thread for my last question. What I'm trying to figure out now is what kinds of types they can be abstracted over. I'm looking to get the result: "((5.6,Foo 9.8),(0.8912676813146139,1.5597184423005745))"
From code that looks kind of like this :
data Foo a = Foo a deriving (Show)
x :: Float x= 5.6
y :: Foo Double y= Foo 9.8
class {-something-} TwoPi {-something-} where div2pi :: {-something-}
instance {-something-} TwoPi Foo where div2pi (Foo b) = b / (2*pi)
instance TwoPi Float where div2pi a = a / (2*pi)
main = do print ((x,y),(div2pi x, div2pi y))
This works: data Foo a = Foo a deriving Show x :: Float x= 5.6 y :: Foo Double y= Foo 9.8 class TwoPi a where div2pi :: (Floating b) => a -> b instance (Real a, Floating a) => TwoPi (Foo a) where div2pi (Foo a) = realToFrac a / (2*pi) instance TwoPi Float where div2pi a = realToFrac a / (2*pi) main = print ((x,y),(div2pi x, div2pi y)) *Main> main ((5.6,Foo 9.8),(0.8912676661364157,1.5597184423005745))
The (Real a) restriction in the instance definition for Foo a is necessary. If a would be Complex Double, for example, there is no way you can sensibly expect a Float return value.
Jürgen
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 8/28/10 06:44 , Greg wrote:
On Aug 27, 2010, at 8:15 PM, Brandon S Allbery KF8NH wrote:
The instance doesn't conform to the class definition; it includes a constraint that the class does not, as the class insists that the type of the result must be independent of the type of the argument, while the instance insists that they must be identical.
I think what you're saying is that not only can an instance do no less than the class has guaranteed, it can do no *more*-- meaning the instance can't further restrict the return type even if that return type still conforms to the class definition. In this case returning a Float breaks the class contract because I've gone and said what type of Floating type will be returned.
Right. You're not the only one vexed by this; one of the advanced Haskell tricks is "restricted monads", which are an attempt to deal with the fact that (for example) a Set is a monad but can't be a Monad because Monad doesn't have an Ord constraint. Another way of thinking about this, btw, is that when you use a typeclass function the only things "visible" about the type are the things defined by the class; so if the instance wants to do something different, there's no way to enforce it. Think of it as a mechanical translator that can faithfully translate specific phrases that it knows about but garbles anything else.
The class definition doesn't mean "div2pi can return any type of Floating value", it means "div2pi *will* return any type of floating value".
More precisely, it means that when something invokes div2pi, it has the right to request any type of floating value at its sole discretion. But the instance says "nuh-uh, you get the same type you feed it, nothing else".
class TwoPi a where div2pi :: (Floating b) => a -> b
is essentially impossible to conform to because b is completely untethered to anything else in the code and not all "(Floating b)"'s are created equal.
It's possible, but you need to use a polymorphic function to produce it. Problem is, there is no standard function that does so for Floating. There are ways to do so for Fractional and for RealFloat (the latter being fairly horrid in practice) but not for Floating which sits in between them in the numeric typeclass hierarchy. (This may be another instance of "the Haskell numeric typeclass hierarchy is woefully misdesigned". You might want to take a look at http://www.haskell.org/haskellwiki/Numeric_Prelude. Warning: "well designed" for Haskellers means "conforms to mathematical theory", so expect to get lost in a soup of groups, rings, fields, and the like :)
I think the intent of the functional dependency in the suggestion you provided in your second email is essentially to tether b to something. Unfortunately if chokes in the second, non-Foo, instance.
Probably; when I write code late at night it's likely to be buggy :)
I think I've mistakenly been thinking of instances as more like subclasses, but that's apparently not quite right (thus the "instance" keyword, I suppose).
The OO terminology is somewhat unfortunate; they don't actually follow any standard OO rules fully, only just enough to cause confusion. - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkx5JYcACgkQIn7hlCsL25VAswCeKNt7/jYXjcWVDKob9kGPqov7 M60An2dgLpI/rpkng/IKcFYSxkBLdr45 =9DKm -----END PGP SIGNATURE-----

On Aug 28, 2010, at 8:04 AM, Brandon S Allbery KF8NH wrote:
I think what you're saying is that not only can an instance do no less than the class has guaranteed, it can do no *more*-- meaning the instance can't further restrict the return type even if that return type still conforms to the class definition. In this case returning a Float breaks the class contract because I've gone and said what type of Floating type will be returned.
Another way of thinking about this, btw, is that when you use a typeclass function the only things "visible" about the type are the things defined by the class; so if the instance wants to do something different, there's no way to enforce it. Think of it as a mechanical translator that can faithfully translate specific phrases that it knows about but garbles anything else.
The class definition doesn't mean "div2pi can return any type of Floating value", it means "div2pi *will* return any type of floating value".
More precisely, it means that when something invokes div2pi, it has the right to request any type of floating value at its sole discretion. But the instance says "nuh-uh, you get the same type you feed it, nothing else".
On Aug 28, 2010, at 5:11 AM, Jürgen Doser wrote:
I would say it like this: div2pi does not return a type of Floating value of its own choosing, it is able to return every type of Floating value (the concrete type is then chosen by the context in each case where div2pi is used).
And here is the "a-ha" moment! I've been looking at return types as values "pushed" from the functions, but they are in fact "pulled" by the caller. That makes a lot of sense in the functional paradigm of Haskell, but it didn't click how this relates to the type system. In an imperative language like C, the function declares what it is going to return, and the caller is responsible for dealing with it. In Haskell, the function is more of a transformation applied to its inputs and the caller requests that a value of a certain type be returned. The class definition gives the range of choices available. Thank you both. Also, Jürgen, thank you for the worked example you provided. It runs just fine on my side as well and gives me something to toy with: On Aug 28, 2010, at 5:11 AM, Jürgen Doser wrote:
This works:
data Foo a = Foo a deriving Show
x :: Float x= 5.6
y :: Foo Double y= Foo 9.8
class TwoPi a where div2pi :: (Floating b) => a -> b
instance (Real a, Floating a) => TwoPi (Foo a) where div2pi (Foo a) = realToFrac a / (2*pi)
instance TwoPi Float where div2pi a = realToFrac a / (2*pi)
main = print ((x,y),(div2pi x, div2pi y))
*Main> main ((5.6,Foo 9.8),(0.8912676661364157,1.5597184423005745))
The (Real a) restriction in the instance definition for Foo a is necessary. If a would be Complex Double, for example, there is no way you can sensibly expect a Float return value.
Jürgen

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 8/27/10 22:58 , Greg wrote:
I guess the problem I'm having is finding a way to treat parametric and non-parametric types interchangeably. The syntax doesn't seem to exist that will allow me to say:
div2pi :: (Floating a) => a -> a -- for non parametric types (ie. Float) and div2pi :: (Floating b) => a b -> b -- for parametric types (ie. Foo Float)
It occurs to me that what you really want *may* be:
class (Floating a, Floating b) => TwoPi a b | a -> b where div2pi :: a -> b
which says that, given a specific type a, the compiler can infer a specific type b corresponding to it, without specifying what that type is (leaving the instance declaration to do so). - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkx4gMwACgkQIn7hlCsL25UaKwCgpe6hlJQ0yCDL2GtbO7EsrePe Cp4An3mEUz6PH23v9z0SHbmP6ikmm/yL =YIZH -----END PGP SIGNATURE-----
participants (3)
-
Brandon S Allbery KF8NH
-
Greg
-
Jürgen Doser