People,
Here is a very important point about basAlgPropos.
And it is a question to the haskellites that understand the Haskell
constructor classes, and such technique.
To my question on how to express a domain depending on the run-time-
found parameter
>> What we have for the *variable dimension* n ?
>> [..]
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes
> Haskell does have polymorphic recursion, and I hope local universal
> quantification will get into Haskell2. Thus variable length vectors
> can be expressed in a statically typed style, when the type alone
> determines the domain:
>
> data Vec0 a = Vec0
> data Vec v a = Vec a (v a)
>
> class Vector v where
> listToVec :: [a] -> v a
> vecToList :: v a -> [a]
> dim :: v a -> Int -- Sample argument, may be translated to Const.
> zero :: HasZero a => v a
> [..]
I tried various attempts with the constructor classes 3,2,1 years
ago. All failed.
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.
And of course, the problem of a constant as operation to be solved.
It stucks immediately: resBase :: a is an ambiguous operation for
class ... => Residue r a.
I could not find the solution, and therefore apply the sample
argument approach, which does not fit well the Haskell air.
If we replace class...Residue r a
with a single parameter constructor class...Residue r,
the problems with resBase remain.
I do not believe one can do anything here without the sample
argument.
Even with Mercury, how can one pretend to define a constant in a
domain (type) depending on the value b, if this "constant" is b?
Can you write the below program in Mercury?
------------------
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 invertibles":
type Z = Integer
ni :: EuclideanRing a => [a] -> a -> Z
ni bs c =
genericLength $
filter isJust [inv_m $ (R b) c | b <- bs]
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).
ni tries to find the inverse of each rc in a/(b):
inv_m rc --> Just _ | Nothing.
Then, ni counts the total number of Just-s.
Still the example is a bit contrived, let it be so.
For example, for a = Z, ni [3,4,5] 2
acts as follows. Builds the residue domains [Z/(3), Z/(4), Z/(5)].
In our attempt, they are represented as the type constructors
[R 3, R 4, R 5] being the values of the variable constructor r
of class Residue. R 3 a, R 4 a, R 5 a ...have the instances of Ring.
For example,
rc + rc in R 3 Z = -- computing modulo 3
(R 3 2)+(R 3 2) = R 3 (rem (2+2) (base of (R 3)) =
R 3 (rem 4 3) = R 3 1
- which means " (2+2) modulo 3 is 1 ".
Similarly, the inverse inv_m rc = Just $ (R 3) 2,
because 2*2 = modulo 3 = 1.
In R 4 Z, 2 is not invertible, inv_m returns Nothing.
in R 5 Z, inv_m rc gives Just $ R 5 3 (2*3 = mod 5 = 1).
The final result of ni is 2 - the two invertions succeeded.
The program ni 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 = Z3, a = Z = Integer give Z3 Z
-- as the model for Z/(3) = Integer modulo 3
resBase :: a -- constant depending on r
resRepr :: r a -> a
res :: a -> r a
res a = r $ rem a resBase
-- Example: for c' = Z3 2, resBase = 3
-- resRepr c' = 2
-- res 2 = c'
-- res 6 = Z3 $ rem 6 3 = Z3 0
instance (Residue r a) => Ring (r a)
where
x+y = res ((resRepr x)+(resRepr y))
x*y = ...
fromInteger = res . fromInteger
inv_m x = ...find inverse of x modulo resBase -done via gcd...
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 ??