Hi,

I spent about a half hour toying around with this and came up with the
following, which seems to work (in ghci, but not hugs -- question for
smart people: which is correct, if either?)...


class Mul a b c | a b -> c where
  mul :: a -> b -> c    -- our standard multiplication, with fundeps

data Commute a b = Commute a b   -- just pair them

-- now, our helper class
class Mul2 x a b c | a b -> c where
  mul2 :: x a b -> c

-- given a helper instance with Commute, we have an instance of the
-- original Mul class
instance Mul2 Commute a b c => Mul a b c where
  mul a b = mul2 (Commute a b)

-- now, we make Mul2 commutative over Commute:
instance Mul2 Commute a b c => Mul2 Commute b a c where
  mul2 (Commute i j) = mul2 (Commute j i)

-- helper function:
i2d :: Int -> Double
i2d = fromInteger . toInteger

-- finally we can make our definition:
instance Mul2 Commute Int Int Int where 
  mul2 (Commute i j) = i * j

instance Mul2 Commute Int Double Double where 
  mul2 (Commute i j) = i2d i * j
-- note that we don't have to define Mul2 Commute Double Int Double

instance Mul Commute Double Double Double where
  mul2 (Commute i j) = i * j

-- we can now test these
i :: Int
i = 3
d :: Double 
d = 5

-- now, in ghci:

*TryCommute> mul i i
9
*TryCommute> mul i d
15.0
*TryCommute> mul d d
25.0
*TryCommute> mul d i
15.0

Woohoo, even the last one worked.

Of course, like so many things, this requires
-fallow-overlapping-instances as well as -fallow-undecidable-instances.

Interestingly, with -98, Hugs doesn't allow this program, saying:

ERROR "TryCommute.hs":23 - Instances are not consistent with dependencies
*** This instance    : Mul2 Commute a b c
*** Conflicts with   : Mul2 Commute Int Int Int
*** For class        : Mul2 a b c d
*** Under dependency : b c -> d

I'm not entirely sure why....

--
Hal Daume III

 "Computer science is no more about computers    | [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Sat, 14 Dec 2002 [EMAIL PROTECTED] wrote:

> I want to use functional dependencies in a way I've not yet seen: to enforce 
>commutativity.
> 
> I define
> 
> class Mul a b c | a b -> c, b a -> c where mul :: a -> b -> c
> 
> I want
> 
> instance (Mul a b c) => Mul b a c where mul x y = mul y x
> 
> do what I expect: if I can multiply a and b, then I can multiply b and a _and always 
>have the same type_.  In a sense, this makes multiplication commute (in the land of 
>types).
> 
> For a whole variety of reasons, the many (4 or 5 now) ways I've tried to make this 
>work have failed, both using Hugs and GHC.
> 
> I mentioned I wanted typed multiplication to commute.  Let me explain more 
>thoroughly:  suppose I had
> 
> data Unit u v = Unit u v
> 
> I want (Unit u1 value1) `mul` (Unit u2 value2) to have the same type as (Unit u2 
>value2) `mul` (Unit u1 value1).  So say u1 :: Int, u2 :: Float, then
> 
> (Unit u1 value1) `mul` (Unit u2 value2) :: (Unit Int (Unit Float blah))
> and
> (Unit u2 value2) `mul` (Unit u1 value1) :: (Unit Int (Unit Float blah))
> 
> I don't care if the result type is Unit Int ... or Unit Float ..., as long as it is 
>a) consistent and b) inferred and c) enforced.  So far, no luck.
> 
> A few other questions:
> 
> What happenned to +m in Hugs?
> 
> In general, if I wanted a fundep to specify that a pair (a, b) determined c 
>_regardless of the order of a and b_, how could it be done?  Why doesn't a b -> c, b 
>a -> c do this?  What I mean is that if I have one of a, b and Int (say) and c a 
>Float, then I could infer the other of a, b once I have a single instance.
> 
> And a 'bug' report: in the overlapping instance one-liner above, the Mul a b c => 
>Mul b a c, I can have this in place and write contradictory instances that violate 
>the fundeps that are not caught in GHC.  (Hugs does not allow the overlapping 
>instances to begin with, even worse.)
> 
> Well, that became a clearinghouse for the frustrations of the last several days.  
>Sorry.
> 
> Thanks,
> Nick
> _______________________________________________
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 


_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to