Dear Haskell implementors,

I suggest the following small extension to the instance declaration in 
the language. So far -- for  Haskell + glasgow-ext.
I think that they are easy to implement.
This is the  "instance union"  proposal.
It is needed to write shorter several `old' instance declarations.
This will make programs easier to read.
It suggests the so-called
                   inherited decl  and, more general,  union decl.

Inherited instance decl proposal
--------------------------------

Union several instance declarations with the same condition part and such 
that among the conclusion  classes there exists some which inherits all 
others.  
Example 1.  My program uses the class tower

                       Field a                 Picture 1.
                       |
                       ERing
                       |
                       CRing a
                       |
                       Ring a 
                      /    \
            AddGroup a      MulSemigroup a     
                     |      |
            AddSemigroup a  |
                     \     /
                      Set a

-- "|" means that the upper inherits from the lower. 
Now, by the application meaning, I need to write 

  instance (Show a, CRing a) => CRing (Pol a)
    where
    <implement operations of Set>
    <implement operations of AddGroup>
    ...
    <implement operations of CRing>

>From the class decls it is clear to the compiler that  CRing  inherits 
all that is lower on the picture. Therefore, the conditional  
`instance (Show a, CRing a) =>' and 'where'
is written only once.
In the existing language, I need to write this conditional 6 times.


Union instance decl proposal
---------------------------- 

It is a generalization for  inhereted decl.

instances (cond_1, ..., cond_n)     -- of the type parameters a_1 ... a_m 
          => 
          <typeTuple> (<params>)  has  {<conclInstList>}
          where
          <implement operations for each member of <conclInstList>.
 
It differs from the old instance declaration in that 
1) it unions several old declarations having the same conditional part,
2) each member of <conclInstList> can be conditional,
3) in <conclInstList> it can be skipped any instance which is inherited 
   by some other member in this list.
         
<params> is a subset of {a_1 ... a_m},
<typeTuple> (<params>)  
            is a tuple of type expressions, as in old declaration,
            for example,  `(a, b)', `Vector a', `[(a,b), Vector a]'.
            It is the argument for the conclusion instance declarations.

<conclInstList> is a list of inst-members separated by comma.
Each member of  <conclInstList>  is either an  
                            old  conclusion instance declaration
                            or a conditional declaration.

Example.  
In the situtation of  Picture 1,  I need to declare

  instance (Show a, CRing a) => 
           (Pol a) has { CRing,  if (has a Field) then ERing }
    where       
    <define operations for  Set (Pol a)>
    <define operations for  AddSemigroup (Pol a)>
    ...
    <define operations for  CRing (Polynomial a)>

    <define operations for  ERing (Pol a)>  -- this part has the 
                                      -- additional condition  (Field a)

Its meaning is that the complier extends this into several `old' 
instance declarations:
  instance (Show a, CRing a) => Set (Pol a) where 
                                    <define operations for  Set (Pol a)>
  ...
  instance (Show a, CRing a) => CRing (Pol a) where 
                                    <define operations for  Set (Pol a)>

  instance (Show a, Field a) => ERing (Pol a) where 
                                  <define operations for  ERing (Pol a)>

(in the last decl `Field a' has been moved to LHS).

In this example  <typeTuple> === (Pol a).
For bi-parametric instances, the concusion part may be, for example
      =>
      [a, Pol a] has {Foo1, Foo2} ...

This means the two instance assertions  Foo1 a (Pol a),  Foo a (Pol a),
and `[a, Pol a]' is the agrument tuple for the instance conclusions.  


This is a draft proposal. If the idea is accepted, some generalizations 
and corrections are expected.

Regards,

-----------------
Serge Mechveliani
mech...@botik.ru


_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to