Thu, 11 May 2000 13:43:20 +0400 (MSD), S.D.Mechveliani <[EMAIL PROTECTED]> pisze:
> Why the classes are desirable here?
> Because the example functions fsq, (==), (+), (*)
> act in a *uniform way* for the residue domains
> Z/(4), Z/(5) ... P/(f), P/(g),
They are not desirable because these domains cannot be conveniently
expressed by types!
Classes are convenient and useful, but their usage is limited to cases
when the type unambiguously determines the context: implementation
of overloaded operations we use.
Before I do your example, let me present a simple example about using
and abusing classes. We have two functions:
sortBy :: (a -> a -> Ordering) -> [a] -> [a]
sort :: Ord a => [a] -> [a]
Note that the first is more general, and the second is more convenient
to use _in cases it applies_. The second one would theoretically
suffice, but it would be very unnatural when you want to sort a list
of lists by their kth elements. You could do it thus:
data ByKth a = ByKth Int a
instance Eq a => Eq (ByKth a) where
ByKth k x == ByKth _ y = x!!k == y!!k
instance Ord a => Ord (ByKth a) where
ByKth k x `compare` ByKth _ y = x!!k `compare` y!!k
sortByKth :: Ord a => Int -> [[a]] -> [[a]]
sortByKth k = map (\(ByKth _ x) -> x) . sort . map (ByKth k)
The value of k is really a parameter of the sorting process, or of
the comparison function. Here we are forced to attach it to each
value and extract it from one of values we have at hand, failing to
statically detect the possibility of mismatches. Using sortBy does
not have this problem, you can create the comparison dynamically.
It's because sort uses a class, i.e. assumes that for each type
there is a single comparison we ever want to apply to that type.
It takes this operation from an implicitly passed dictionary, which
is determined by the type only. This approach is convenient while it
works, but fails when the assumption is no longer true.
This is exactly what you want to do with algebra. You assume that for
each value that belongs to some group, this group is the only group
the value belongs to! And more: you use a language of classes, which
assumes that the group is determined by the type only.
You show that the second assumption is not always true, and want to
introduce sample arguments to remedy it. But the first assumption is
not true too!
How would you handle the case when there are several group structures
in a given set, and you use different group operations on the same
elements?
Your solution abuses classes. In cases that can be naturally handled by
classes, it is unnecessarily ugly: forces having sample arguments even
in functions like sum and fromIntegral. In cases that cannot be handled
by classes at all, of course it does not work. It works better than
two other approaches that I will describe only in border cases, when
the domain is expressed partly by the type and partly by some value,
using the ugly kludge of attaching the value to elements of the domain.
Back to sort and sortBy. Note that generic functions that use sort
must have a different interface than functions that use sortBy, even
if they do exactly the same thing, only taking the comparison from
different places. Unfortunately the interfaces of sort and sortBy are
fundamentally different in this respect. These functions are both
very useful: convenient sort for simple cases and universal sortBy
when you need more flexibility.
Similar approach IMHO should be used for algebra. There will be two
sublanguages. One is what we have now: simple classes to overload
common operations on primitive types. Currently it is focused on
various sorts of numbers. It can be extended if necessary to cover more
generic groups, rings etc. which are self-described by their types,
but probably not much. Especially the part that goes into the Prelude
must be simple. It can be redesigned to better fit various patterns
of usage, to avoid being forced to define an operation a type does
not really support. It should be good and universal enough to build
any kind of program on it: an advanced algebra system, a compiler,
a web browser, a pretty printer for source code, a graph plotter,
a natural language processor, an interface between WWW and a database,
a game or a text editor.
When you want to write a complex algebra system, it does not suffice
to overload everything using classes. Domains are computed at runtime,
complex mathematical objects are managed. A separate library written
by you can provide a large and flexible collection of algebraic stuff.
Haskell's type system is powerful, but cannot express anything at
compile time. Very dynamic domains must be represented as runtime
objects, i.e. values. These values and elements of those domains have
carefully designed types, because Haskell is statically typed and
requires certain discipline in this respect, but types themselves
are not sufficient to determine domains.
This is an opposite approach than I presented in the previous mail.
Classes are not the appropriate tool for modelling domains of a
sufficiently advanced algebra system.
There is one technical subtlety in the domains-as-values style. You
cannot reuse names of record fields in Haskell. It's painful if you
want to extract the same field from different types of records and
this will happen a lot. Several possibilities arise:
- Make record structure hierarchical and extract the path to the base
record first. This is what superclasses implicitly do for classes.
- Make classes for reusing field names, i.e.
class HasFoo a b where foo :: a -> b
instance HasFoo Record-having-field-foo Type-of-field-foo
- Change the Haskell language. IMHO it is the best approach for the
long time. Record syntax would be changed, field selection would
look like in traditional languages - using a dot, and equivalents
of the above classes will be maintained implicitly.
> Program "the number of fix-squares":
>
> type Z = Integer
>
> fsq :: EuclideanRing a => [a] -> a -> Z
> fsq bs c =
> let
> rcs = [(R b) c | b <- bs]
> in
> genericLength [rc | rc <- rcs, (rc*rc)==rc]
It would go approximately like this. Sorry if I got the math wrong,
I'm not sure if residue in fact makes a ring from an Euclidean ring
or whatever.
data Ring a = ...
-- Includes the fields:
-- eq :: a -> a -> Bool
-- zero :: a
-- plus :: a -> a -> a
-- ...
data EuclideanRing a = ...
residue:: EuclideanRing a -> a -> Ring a
residue r a = Ring {
zero = zero r,
plus = \x y -> modulo r (plus r x y) a,
...}
-- In reality field names cannot be reused :-(
fsq:: EuclideanRing a -> [a] -> a -> Z
fsq ring bs c = genericLength [
b <- bs,
let res = residue ring b,
let (==) = eq res,
let (*) = times res,
c * c == c]
It gets a bit nicer if the syntax of working with records changes:
...
x + y = x r.+ y `r.modulo` a
...
fsq:: EuclideanRing a -> [a] -> a -> Z
fsq ring bs c = genericLength [
b <- bs,
let res = residue ring b,
c res.* c res.== c]
--
__("< 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-