To my
> 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.
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes on 10 May 2000
> 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.
People, there is a small "error" in my example.
Namely, no inversion is needed. It suffices to find, say, c*c == c
in each domain.
I enclose the improved example to the letter - sorry.
Please, how to program it in a good style, in the most extended
Haskell that ever exists?
Only, please - this precise example with function fsq.
It is very simple and important.
> It can be done without classes at all.
All the algorithmic programming can be done without classes and
even without types, in somewhat typeless Scheme language, or such.
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),
where Z = Integer,
P = UnivariatePolynomial a, a - any field, for example,
a = Rational, f,g polynomials.
There are also other types `a' for which fsq computes things in
a/(b) in the same way: via the instances of
(==),(+),(-),(*),quotRem
on `a'.
In particular, for such cases the class EuclideanRing a
is designed.
As Haskell cannot handle in a "pure" style this example with c*c==c
in a parametric residue domain (can it?), we have the following
choice.
(1) Indeed, do not use classes in the complex cases like above, and
re-program the same algorithm individually.
(2) Assume the sample argument style and operate with the domain
attributes dynamically and explicitly.
(1) - I do not like it.
This is programming the same method many times.
(2) Touches only the users who deal with such subtle parametric
domains.
If the user does not use Residue ring, and such, one has not
questions, one does not see the sample arguments at all. One skips
-fadvancedAlgebra
and writes as usual
0 :: T, fromInteger n :: T, fromInteger n `asTypeOf` x.
One also ignores baseSet, MulMonoid, and other fancy categories.
And if one does use Residue ring, and such, then
why others had not developed for several years any better
approach for this than the poor sample argument of basAlgPropos ?
As they had not developed it, maybe, let them give others the
standard possibility to use the sample argument approach?
------------------
Sergey Mechveliani
[EMAIL PROTECTED]
------------------------------------------------------------------
This is variable residue domain EuclideanRing a => a/(b)
Here EuclideanRing is something like the class Integral
of Haskell-98.
class Num a => Ring a -- approximately
class Integral a => EuclideanRing a -- we'll use rem
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]
Here each b maps to the type constructor R b,
(R b) applies to c and makes a residue rc = (R b) c
modeling the (residue of c modulo b) - element of a/(b).
Example: b = 3, c = 2 creates rc = (R 3) 2
- a residue element of 2 modulo 3 - element of Z/(3).
In each domain a/(b) has only to apply once (*) and (==).
Example a = Z, fsq [4,5,6] 3
-------
acts as follows. Builds the residue domains [Z/(4), Z/(5), Z/(6)].
In our attempt, they are represented as the type constructors
[R 4, R 5, R 6] being the values of the variable constructor r
of class Residue. R 4 a, R 5 a, R 6 a ...have the instances of Ring.
For example,
R b x == R b y = rem x b == rem y b -- generic instance
rc*rc in R 4 Z = -- computing modulo 4
(R 4 3)*(R 4 3) = R 4 (rem (3*3) (base of (R 4))) =
R 4 (rem 9 4) = R 4 1
- which means " (3*3) modulo 4 is 1 ".
similar is rc1 + rc2
In our example, rc*rc == rc in False for Z/(4), Z/(5) and
True for Z/(6),
and the result of fsq is 1.
The program fsq should work for any list bs
(assuming that bs does not contain the "incorrect" values, like
b = 0,1,-1).
Attempt: -----------------------------------------------------------
class EuclideanRing a => Residue r a
where
-- Constructor r and type a are related so that r a
-- models the residue domain made from a with r.
-- Example: r = Z4, a = Z = Integer give Z4 Z
-- as the model for Z/(4) = Integer modulo 4
resBase :: a -- constant depending on r
resRepr :: r a -> a
res :: a -> r a
res a = r $ rem a resBase
-- Example: for c' = Z4 3, resBase = 4
-- resRepr c' = 3
-- res 3 = c'
-- res 8 = Z4 $ rem 8 4 = Z4 0
instance (Residue r a) => Ring (r a)
where
x+y = res ((resRepr x)+(resRepr y))
x*y = ...
fromInteger = res . fromInteger
data R a = R -- ?? Has to model a constructor r depending
-- on the value of type a.
-- Example: 2 <--> R 2 ??
instance (EuclideanRing a) => Residue (R a) a
where
resBase = ??
resRepr ((R _) a) = a ??