[Haskell-cafe] rip in the class-abstraction continuum

Christopher Howard christopher.howard at frigidcode.com
Tue May 21 04:50:21 CEST 2013


On 05/19/2013 10:10 PM, Tillmann Rendel wrote:
> 
> This is not easily possible. If you could just put the constraint into
> the instance, there would be a problem when youc all toXy in a
> polymorphic context, where a is not known. Example:
> 
>   class XyConv a where
>     toXy :: a b -> [Xy b]
> 
>   shouldBeFine :: XyConv a => a String -> [Xy String]
>   shouldBeFine = toXy
> 
> This code compiles fine, because the type of shouldBeFine is an instance
> of the type of toXy. The type checker figures out that here, b needs to
> be String, and since there is no class constraint visible anywhere that
> suggests a problem with b = String, the code is accepted.
> 
> The correctness of this reasoning relies on the fact that whatever
> instances you add in other parts of your program, they can never
> constrain b so that it cannot be String anymore. Such an instance would
> invalidate the above program, but that would be unfair: How would the
> type checker have known in advance whether or not you'll eventually
> write this constraining instance.
> 
> So this is why in Haskell, the type of a method in an instance
> declaration has to be as general as the declared type of that method in
> the corresponding class declaration.
> 
> 
> Now, there is a way out using some of the more recent additions to the
> language: You can declare, in the class, that each instance can choose
> its own constraints for b. This is possible by combining constraint
> kinds and associated type families.
> 
>   {-# LANGUAGE ConstraintKinds, TypeFamilies #-}
>   import GHC.Exts
> 
> The idea is to add a constraint type to the class declaration:
> 
>   class XyConv a where
>     type C a :: * -> Constraint
>     toXy :: C a b => a b -> [Xy b]
> 
> Now it is clear to the type checker that calling toXy requires that b
> satisfies a constraint that is only known when a is known, so the
> following is not accepted.
> 
>   noLongerAccepted :: XyConv a => a String -> [Xy String]
>   noLongerAccepted = toXy
> 
> The type checker complains that it cannot deduce an instance of (C a
> [Char]) from (XyConv a). If you want to write this function, you have to
> explicitly state that the caller has to provide the (C a String)
> instance, whatever (C a) will be:
> 
>   haveToWriteThis :: (XyConv a, C a String) => a String -> [Xy String]
>   haveToWriteThis = toXy
> 
> So with associated type families and constraint kinds, the class
> declaration can explicitly say that instances can require constraints.
> The type checker will then be aware of it, and require appropriate
> instances of as-yet-unknown classes to be available. I think this is
> extremely cool and powerful, but maybe more often than not, we don't
> actually need this power, and can provide a less generic but much
> simpler API.
> 
>   Tillmann

Thank you for the quick and thorough response. To be honest though, I
had some difficulty following your explanation of the constraints
problem. I had an even more difficult time when I tried to read up on
what Type Families are -- ended up at some wiki page trying to explain
Type Families by illustrating them with Generic Finite Maps (a.k.a.,
Generic Prefix Trees). The rough equivalent of learning German through a
Latin-German dictionary. :|

Anyway, I played around with my code some more - and it seems like what
I am trying to do can be done with multi-parameter type classes:

code:
--------
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

class XyConv a b where

  toXy :: a b -> [Xy b]

instance (Integral a, Floating b) => XyConv (CircAppr a) b where

  toXy (CircAppr divns ang rad) =
      let dAng = 2 * pi / (fromIntegral divns) in
      let angles = map ((+ ang) . (* dAng) . fromIntegral) [0..divns] in
      map (\a -> am2xy a rad) angles
--------

Seems to work okay:

code:
--------
h> toXy (CircAppr 4 0.0 1.0)
[Xy 1.0 0.0,Xy 6.123233995736766e-17 1.0,Xy (-1.0)
1.2246467991473532e-16,Xy (-1.8369701987210297e-16) (-1.0),Xy 1.0
(-2.4492935982947064e-16)]
h> :t toXy (CircAppr 4 0.0 1.0)
toXy (CircAppr 4 0.0 1.0) :: Floating b => [Xy b]
--------

Is there anything bad about this approach?

-- 
frigidcode.com

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 555 bytes
Desc: OpenPGP digital signature
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130520/f00c8327/attachment.pgp>


More information about the Haskell-Cafe mailing list