A sample revised prelude for numeric classes

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
12 Feb 2001 00:26:35 GMT


Sun, 11 Feb 2001 17:42:15 -0500, Dylan Thurston <dpt@math.harvard.edu> pisze:

> I've started writing up a more concrete proposal for what I'd like
> the Prelude to look like in terms of numeric classes.  Please find
> it attached below.  It's still a draft and rather incomplete,
> but please let me know any comments, questions, or suggestions.

I must say I like it. It has a good balance between generality and
usefulness / convenience.

Modulo a few details, see below.

> > class (Num a, Additive b) => Powerful a b where
> >     (^) :: a -> b -> a
> > instance (Num a) => Powerful a (Positive Integer) where
> >     a ^ 0 = one
> >     a ^ n = reduceRepeated (*) a n
> > instance (Fractional a) => Powerful a Integer where
> >     a ^ n | n < 0 = recip (a ^ (negate n))
> >     a ^ n         = a ^ (positive n)

I don't like the fact that there is no Powerful Integer Integer.
Since the definition on negative exponents really depends on the first
type but can be polymorphic wrt. any Integral exponent, I would make
other instances instead:

instance RealIntegral b          => Powerful Int       b
instance RealIntegral b          => Powerful Integer   b
instance (Num a, RealIntegral b) => Powerful (Ratio a) b
instance                            Powerful Float     Int
instance                            Powerful Float     Integer
instance                            Powerful Float     Float
instance                            Powerful Double    Int
instance                            Powerful Double    Integer
instance                            Powerful Double    Double

This requires more instances for other types, but I don't see how to
make it better with (^), (^^) and (**) unified. It's a bit irregular:
Int can be raised to custom integral types without extra instances,
but Double not.

It's simpler to unify only (^) and (^^), leaving
    (**) :: Floating a => a -> a -> a
with the default definition of \a b -> exp (b * log a).
I guess that we always know which one we mean, although in math the
notation is the same.

Then the second argument of (^) is always arbitrary RealIntegral,
so we can have a single-parameter class with a default definition:

class (Num a) => Powerful a where
    (^) :: RealIntegral b => a -> b -> a
    a ^ 0 = one
    a ^ n = reduceRepeated (*) a n

instance Powerful Int
instance Powerful Integer
instance (Num a) => Powerful (Ratio a) where
    -- Here unfortunately we must write the definition explicitly,
    -- including the positive exponent case: we don't have access to
    -- whatever the default definition would give if it was not
    -- replaced here. We should probably provide the default definition
    -- for such cases as a global function:
    --     fracPower :: (Fractional a, RealIntegral b) => a -> b -> a
    -- (under a better name).
instance Powerful Float
    -- Ditto here.
instance Powerful Double
    -- And here.

> > class (Real a, Floating a) => RealFrac a where
> > -- lifted directly from Haskell 98 Prelude
> >     properFraction   :: (Integral b) => a -> (b,a)
> >     truncate, round  :: (Integral b) => a -> b
> >     ceiling, floor   :: (Integral b) => a -> b

Should be RealIntegral instead of Integral.

Perhaps RealIntegral should be called Integral, and your Integral
should be called somewhat differently.

> > class (Real a, Integral a) => RealIntegral a where
> >     quot, rem        :: a -> a -> a   
> >     quotRem          :: a -> a -> (a,a)
> >
> >       -- Minimal definition: toInteger

You forgot toInteger.

> > class (Lattice a, Num a) => NumLattice a where
> >     abs :: a -> a -> a
> >     abs x = meet x (negate x)

Should be:
        abs :: a -> a

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK