Here are some questions and suggestions for Haskell-2.
They concern the
* (composed) constructs in a class or instance context,
* identity constructor expression
* deriving "all" for `newtype'
* ambiguity resolving via first argument in a class operation
In mathematics, the first need for the multi-parameter classes arises
when dealing with a vector space v over a field k, or let it better
be a Module m over a Ring r. One of possibilities is to express
a RightModule over a Ring as a constructor class:
class AddGroup a where add :: a -> a -> a
times :: a -> Integer -> a
...
class AddGroup a => Ring a where mul :: a -> a -> a
instance AddGroup Int where add = (+)
times = (*)
instance Ring Int where mul = (*)
class (Ring r,AddGroup (m r)) => RightModule m r
where
cMul :: m r -> r -> m r
-- "vector" (m r) multiplied by "coefficient" r'
Obstacle 1:
------------
Haskell rejects this (m r) in the context. Could Haskell-2 allow it?
For this particular case, we can remove the superclass AddGroup (m r)
and say that it is a "presumed condition".
But the class RightModule could well contain the default definition
for some operation that uses, say, (add (m r1) (m r2)), `add' from
AddGroup.
This need and restriction is familiar to many.
I just add the example and my vote.
Move further: data Vector a = Vec [a]
instance Ring r => RightModule Vector r
where
cMul (Vec rs) r = Vec (map (mul r) rs)
This fits all right. Further:
instance Ring r => RightModule r r where cMul = mul
This says that any Ring is a module over itself, with the module
multiplication being the Ring one.
Obstacle 2:
------------
Haskell rejects this `=> RightModule r r'
How can we express the meaning
... RightModule m r where m is the identical constructor
(m a = a)
?
Scripting
newtype Id a = Id a deriving(...)
instance Ring r => RightModule Id r where
cMul (Id r) r' = Id (mul r r')
is an awkward way-out.
Because from this point on, the programmer has to convert the data
explicitly between r and Id r. This is not exactly what the
application domain means.
Now, suppose we decide to tolerate this style. Then we meet
Obstacle 3:
------------
`newtype' cannot derive all the instances automatically.
Thus, in our case, add (Id 1) (Id 2) is illegal.
This may occur a stupid question, but
why Haskell allows the `newtype' derivation only for the standard
classes?
Why not support declarations like
newtype N a b = N (T a b) deriving(Eq,Ord,AddGroup,Ring)
or newtype N a b = N (T a b) deriving( all )
?
Is there any ambiguity in conversion between (T a b) and N (T a b)
when N (T a b) inherits all the instances (T a b) matches in a
program?
Finally, we declare
instance AddGroup a => RightModule a Int where cMul = times
-- an additive group is a module over the ring of integers with
-- the module multiplication by n being the addition repeated
-- n times
Haskell rejects this. And what we meant was
... RightModule m Int where m _ = a
We can also script
instance AddGroup (m Int) => RightModule m Int where cMul = times
or better
instance AddGroup (m a) => RightModule m Int where cMul = times
--
-- it is immaterial here what is `a'
Haskell rejects both. This is
Obstacle 4:
-----------
Again, the (composed) construct restriction in the instance context is
well known. I only add this application example.
Remark and question on the ambiguity problem
--------------------------------------------
M.Jones & S.P.Jones paper "...Exploration of Design Space."
says that there was not found a good solution for the ambiguity problem
even in the case of the single parameter classes.
Because the main instrument for the type resolving was the requirement
for any class operation ... => C a where o :: ...
to take the first argument from `a': o :: a -> ...
And the authors say that this restriction has proved impracticable,
and, in particular, the Num class does not satisfy it
(i recall 0 :: a and fromInt :: Int -> a).
After my 3 year experience in programming algebra in Haskell i find
this restriction *is practicable*.
Thus, my DoCon program contains things like
class...=> Ring a where i :: a -> Integer -> a
- instead of ...fromInteger :: Integer -> a
and
class...=> MulMonoid a where unity :: a -> a
instead of ...unity :: a
For example, if we choose ...fromInteger :: Integer -> a
...unity :: a,
we will often have to write things like (fromInteger 2) `asTypeOf' x,
unity `asTypeOf' x
So it is better to write (i x 2), (unity x) by adding the first
argument.
And it is, probably, better to change Num to fromInt :: a -> Int -> a.
Generally, what i mean is: if Haskell can solve types sufficiently
under this first-argument restriction, then OK, to my experience,
adding the first argument in extra cases is tolerable.
The paper also points out that this first-argument approach cannot be
generalized to the constructor classes.
The question is: having, say,
class...=> C m a where c :: Int -> m a
cannot we improve it to
class...=> C m a where c :: m a -> Int -> m a
similarly as in the single-parameter classes with b -> Int -> b ?
What has changed in the sense of ambiguity resolution as this
constructor class m appered?
Regards.
------------------
Sergey Mechveliani
[EMAIL PROTECTED]