[Haskell-beginners] instances of different kinds

Jürgen Doser jurgen.doser at gmail.com
Sat Aug 28 08:11:01 EDT 2010


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



More information about the Beginners mailing list