On 11-Feb-2001, Brian Boutel <[EMAIL PROTECTED]> wrote:
>> There may be some misunderstanding here. If you are talking about type
>> for which equality is always undefined, then I agree with you, but that
>> is not what I was talking about. I was thinking about types where
>> equality is defined for some pairs of argument values and undefined for
>> others - I think the original example was some kind of arbitrary
>> precision reals.

On Sun, Feb 11, 2001 at 06:24:33PM +1100, Fergus Henderson wrote:
> The original example was treating functions as a numeric type.  In the
> case of functions, computing equality is almost always infeasible.
> But you can easily define addition etc. pointwise:
>       
>       f + g = (\ x -> f x + g x)

I have a fairly complete implementation of this with dummy instances of
Eq and Show for those who want to see the consequences of this. I found,
interestingly enough, that any type constructor f with the following
three properties could have an instance of Num defined upon f a:

        (1) it has a unary constructor to lift scalars 
        (2) it has a Functor instance
        (3) it has an analogue of zip which can be defined upon it

or, more precisely:

\begin{code}
instance (Eq (f a), Show (f a), Num a, Functor f,
                        Zippable f, HasUnaryCon f) => Num (f a)
        where
                f + g = fmap (uncurry (+)) $ fzip f g
                f * g = fmap (uncurry (*)) $ fzip f g
                f - g = fmap (uncurry (-)) $ fzip f g
                negate = fmap negate
                abs = fmap abs
                signum = fmap signum
                fromInteger = unaryCon . fromInteger

class Zippable f where
        fzip :: f a -> f b -> f (a,b)

class HasUnaryCon f where
        unaryCon :: a -> f a

instance Functor ((->) a) where
        fmap = (.)

instance Zippable ((->) a) where
        fzip f g = \x -> (f x, g x)

instance HasUnaryCon ((->) a) where
        unaryCon = const
\end{code}

and this generalizes nicely to other data types:

\begin{code}
instance Zippable Maybe where
        fzip (Just x) (Just y) = Just (x,y)
        fzip _ Nothing = Nothing
        fzip Nothing _ = Nothing

instance HasUnaryCon Maybe where
        unaryCon = Just

instance Zippable [ ] where
        fzip = zip

instance HasUnaryCon [ ] where
        unaryCon = cycle . (:[])
\end{code}

On 11-Feb-2001, Brian Boutel <[EMAIL PROTECTED]> wrote:
>> Returning to the basic issue, I understood the desire to remove Eq as a
>> superclass of Num was so that people were not required to implement
>> equality if they did not need it, not that there were significant
>> numbers of useful numeric types for which equality was not meaningful. 

On Sun, Feb 11, 2001 at 06:24:33PM +1100, Fergus Henderson wrote:
> The argument is the latter, with functions as the canonical example.

Well, usually equality as a mathematical concept is meaningful, but
either not effectively or efficiently computable. Given an enumerable
and bounded domain, equality may be defined (perhaps inefficiently)
on functions by

\begin{code}
instance (Enum a, Bounded a, Eq b) => Eq (a->b) where
        f == g = all (uncurry (==))
                        $ zipWith (\x -> (f x, g x)) [minBound..maxBound]
\end{code}

and as I've said in another post, equality instances on data structures
expected to be infinite, very large, or where the semantics of equality
are make it difficult to compute, or perhaps even cases where it's just
not useful are also not good to be forced.


Cheers,
Bill

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

Reply via email to