Antoine Latter wrote:

On 8/3/07, Chris Smith <[EMAIL PROTECTED]> wrote:

Yes, unless of course you did:

   instance (Monad m, Num n) => Num (m n)

or some such nonsense. :)


I decided to take this as a dare - at first I thought it would be easy
to declare (Monad m, Num n) => m n to be an instance of Num (just lift
or return the operators as necessary), but I ran into trouble once I
realized I needed two things I wasn't going to get:

An instance of Eq (m n), and an instance of Show (m n) for all monads
m.  Eq would need a function of the form:

(==) :: Monad m => m a -> m a -> Bool

and Show would need a function of type m a -> String

What about Eq1 and Show1 classes? In the same vein as Typeable1:

> class Eq1 f where
>      eq1  :: Eq a => f a -> f a -> Bool
>      neq1 :: Eq a => f a -> f a -> Bool

> class Show1 f where
>      show1      :: Show a => f a -> String
>      showsPrec1 :: Show a => Int -> f a -> ShowS

Now you can declare the Num instance:

> instance (Monad m, Eq1 m, Show1 m, Num n) => Num (m n) where
>      (+) = liftM2 (+)
>      (-) = liftM2 (-)
>      (*) = liftM2 (*)
>      abs = liftM abs
>      signum = liftM signum
>      negate = ligtM negate
>      fromInteger = return . fromInteger

And just to show that such instances can exist:

> instance Eq1 [] where
>       eq1  = (==)
>       neq1 = (/=)

> instance Show1 [] where
>       show1 = show
>       showsPrec1 = showsPrec


Note: All of this is untested code.

Twan
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to