Recent Haskell ignores the possibility of the automatic type 
conversion. Thus, 
                          1 + 1%2  
is ill-typed.
Probably, this is because of the lack of a definite concept of which
value has to convert to which between the types.
On the other hand, my computer algebra project has reached the point,
where the usefulness of the rich type (algebraic domain) conversion 
becomes clear. For example, 
                        2 + x + x%3      (x :: Polynomial Int)

has (under natural circumstances) to transform atomatically to

       (2%1)*x^0 + (1%1)*x^1 + (1%3)*x^1     :: Polynomial (Ratio Int)

In practice, more complex transformations are usually applied.

Also do not think of `fromInteger' as panacea; for in other examples 
we have not integers but something else. 

As i am not a specialist in the "typeful" language design, i am sorry
if the following re-invents something well-known.


----------------------------------------------------------------------
               Proposal to Haskell-2 language.
               Instance-ruled type conversion.


(1) To introduce into the standard Prelude

    class Convertible a b  where  cv :: a -> b -> b
                              
           (probably this has to be some particular symbol, say, :>  :
            2 :> (1%1) --> 2%1   
           )
    and, maybe, some general purpose instances:  

    instance Convertible a a  where  cv a _ = a

    instance (Convertible a b,Convertible b c) => Convertible a c
      where
      cv a c =  cv (cv a b) c

    instance (Convertible a b,Integral b) => Convertible a (Ratio b)
      where
                                       -- Ratio  is also of standard
      cv a f =  (cv a (numerator f)) % 1
    ...

(2) To relax the Haskell syntax so as to allow the "mixed" 
    expressions, like, say, 
                             2 + x + x%3                          (*)
    - providing the simple rules according to which any value
    <e> ::<T>  in an expression actually means (and is transformed by
    the compiler to)   (cv <e> <e'>>   for appropriate  e'.
---------------------------------------------------------------------

Motivation.

Not changing the language, but only by introducing (1) in the user 
program, one obtains the possibility to write in the above example:

       let  p = ... :: Polynomial (Ratio Int)
            x = ... :: Polynomial Int
       in 
            (cv 2 p) + (cv x p) + (cv x p)/(cv 3 p)               (**)

This is achieved via the declarations like

  data Pol a =  Pol [(a,Int)]  deriving(Show,Read,Eq)

  instance Num a=> Num (Pol a)  where  (Pol mons)+(Pol mons')= Pol ...

  instance Convertible a b => Convertible a (Pol b)
    where
    cv a (Pol ((b,_):_)) =  Pol [(cv a b,0)]    -- a -> a'*x^0


Generally, this means that 
        the user instances define the type conversion for the 
        several constructor levels per one `cv' application.

This is better than nothing. But not sufficient:

     the compiler has mostly to set these cv -s automatically.
 
For example, seeing                   [x,y]   (for  x::a, y::b)
the compiler may form the expression  
  e =
    IF  there exists Convertible a b  THEN  [cv x y, y] 
    ELSE
      IF  there exists Convertible b a  THEN  [x, cv y x] 
      ELSE
        error "...cannot convert types..."

So,    
  type conversion = 
               user instances  +  compiler rules for type conversion


If the idea is appreciated in general, we could discuss it further.

Regards,


------------------
Sergey Mechveliani
[EMAIL PROTECTED]



Reply via email to