Wed, 10 May 2000 15:32:41 +0400 (MSD), S.D.Mechveliani <[EMAIL PROTECTED]> pisze:

> Here is a small, concrete and real example, more illustrative
> than the variable vector space, though, very similar with respect
> to Haskell.
> If this can be programmed adequately with the constructor classes,
> and such, this will mean a great deal.

Below is a discussion about sample arguments, but first the residue
problem.

It can be done without classes at all.

I don't know how to compute the inverse in Z/(n), but whatever the
implementation is, its interface does not have to represent the ring
of residues as the type, which cannot be done conveniently.

Especially as you give the list of residue values. You don't
expect to be able to easily provide a list of types to test, like
[Rational,Float,Double], and get a number of types which, say, are
able to distinguish between 1 and 1+10^^(-8)?

You can represent domains as types (and overload operations on them
using the syntax of classes), or as values (and manipulate domains
themselves in crazy ways), but not both.

You can stretch the type language to express more than usual, e.g. to
parametrize types by natural numbers. It only gets messy, inconvenient
and inefficient when gone too far.

As an example, here is the representation of the residue ring over an
integral type, with the residue being a natural number, as the _type_.
It can be given instances of Haskell numeric classes, although they
are not well suited for types that differ too much from numbers: they
require operations that don't apply here. Below is an ugly proof that
the type variable representing the residue value can be determined
at runtime and hidden inside the implementation of a function.

I don't say that it is the preferred way of working with residue rings.

------------------------------------------------------------------------
data Zero   = Zero
data Succ n = Succ

class Nat n where value :: Integral i => n -> i
instance Nat Zero where value _ = 0
instance Nat n => Nat (Succ n) where
    value (_::Succ n) = 1 + value (undefined::n)

newtype (Integral a, Nat r) => Residue r a = R a deriving (Eq, Ord, Show)

instance (Integral a, Nat r) => Num (Residue r a) where
    (R x::Residue r a) + R y = R ((x+y) `mod` value (undefined::r))
    (R x::Residue r a) - R y = R ((x-y) `mod` value (undefined::r))
    (R x::Residue r a) * R y = R ((x*y) `mod` value (undefined::r))
    fromInteger x = n undefined
        where
        n :: r -> Residue r a
        n r = R (fromInteger x `mod` value r)
        -- It will get simpler when GHC fully implements
        -- result type signatures:
        -- fromInteger x :: Residue r a =
        --     R (fromInteger x `mod` value (undefined::r))
    abs    = error "abs undefined on Residue"
    signum = error "signum undefined on Residue"

instance (Integral a, Nat r) => Enum (Residue r a) where
    toEnum   = fromInteger . toInteger
    fromEnum = fromInteger . toInteger

instance (Integral a, Nat r) => Real (Residue r a) where
    toRational = toRational . toInteger

instance (Integral a, Nat r) => Integral (Residue r a) where
    toInteger (R x) = toInteger x
    quotRem = error "I don't know how to compute quotRem on Residue"

-- Example of work with a residue type determined at runtime:
modulo:: Integral a => a -> a -> a
(x::a) `modulo` y = m (undefined::Residue Zero a) x (toInteger y)
    where
    m :: (Integral b, Nat r) => Residue r b -> b -> Integer -> b
    m (_::Residue r b) x 0 = fromIntegral (fromIntegral x :: Residue r b)
    m (_::Residue r b) x n = m (undefined::Residue (Succ r) b) x (n-1)
------------------------------------------------------------------------



Sample arguments can mean two things:

1. We sometimes want to map types to values, when the type of such
   value does not depend on the type being the argument. Example:
   various methods like sizeOf, cardinality, precision etc.
   
   One solution is to extend the type of the value with a sample
   argument whose value is never examined, and it is only used to
   disambiguate uses of the value.

2. To store part of the information about a domain in values from
   that domain themselves, instead of seeing it in their types.
   
   You want to use sample arguments for this too. Each overloaded
   function that needs to work in such domain gets a sample argument
   from which it extracts the needed information about the domain it
   is expected to work in, unless it already has at least one real
   argument of that type. If it has more than one real argument, there
   is a runtime error or wrong answer when their domains don't match,
   it is not checked statically.

The problem is that interfaces of various generic overloaded operations
must be different, depending on whether implementations will be able
to extract context from some values or not.

Unfortunately it must be done consistently. Either none or all
operations must have sample arguments if they are expected to be
mixed in. For example if the implementation of fromInteger on complex
numbers wants to use an overloaded zero, the existence of the sample
argument for zero implies its existence for fromInteger!

Note that it does not apply to the first meaning of sample arguments.
There the value of the sample argument is never examined, and one can
always pass bottom of the appropriate type. But in the second meaning
the sample argument must already contain enough information about the
context. Any overloaded function using another function that needs
the context must require the context in its own interface as well.

Almost all types used in Haskell libraries and programs are simple
enough that they contain the necessary information to implement all
needed overloaded operations without a runtime context. That's why
current Haskell consistently does not use sample arguments in the
second meaning.

You want to introduce the second meaning. But it would imply that
almost all functions overloaded only on their result get a sample
argument! From the standard Prelude, they are:
    minBound, maxBound
    fromInteger, fromRational
    fromIntegral, realToFrac
    toEnum
    pi
    sum, product
    properFraction, truncate, round, ceiling, floor
    readsPrec, readList, readIO, readLn

That's why I am opposed to sample arguments. In 99.9% of cases
they are not needed, and they uglify every place they are used in,
independently of whether they are actually needed there or not.

We will no longer have
    sum :: Num a => [a] -> a
because sum must invent a sample argument from the empty list to pass
to zero. sum must get a sample argument itself.

Do you really want pi to have an argument?!

We will no longer have overloaded numeric literals, because
fromIntegral needs a sample argument, and literals obviously don't
have a place to specify one.

No, it cannot be done.

You can often rely on implicit conversions between domains: all domains
in question live in the same type, so there is no technical problem
in it. For example the overloaded zero in the type of all polynomials
would mean a zero polynomial, not stating the variables; and when two
polynomials get added, sets of their variables would be added too. It
is not nice if you expected zero to already have the needed variables,
but they cannot be determined from the context of the generic zero,
because they are not part of the type. It's a world of dynamic typing,
with its advantages and disadvantages: you can have polynomials using
different sets of variables in one list, or domains parametrized by
functions, but you cannot let the compiler determine the context from
the usage.

You can represent domains as types, or as values, which lead to very
different styles. You can have a statically typed or dynamically
typed language. But you cannot have both in one.

-- 
 __("<    Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/              GCS/M d- s+:-- a23 C+++$ UL++>++++$ P+++ L++>++++$ E-
  ^^                  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK                  5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-


Reply via email to