How overload operator in Haskell?
Liu Junfeng
liujf@softhome.net
Sat, 12 Jul 2003 20:27:57 +0800
I come up a solution as this:
---------------------------------------------------
module Vector where
data Vector =3DVector [Double]
fromVector :: Vector -> [Double]
fromVector (Vector v) =3D v
fromList :: [Double] -> Vector
fromList v =3D Vector v
toVector :: Double -> Vector
toVector x =3D Vector (repeat x)
instance Eq Vector where
v1 =3D=3Dv2 =3D (fromVector v1) =3D=3D (fromVector v2)
instance Show Vector where
show v =3D show (fromVector v)
instance Num Vector where
v1 + v2 =3DVector (zipWith (+) (fromVector v1) (fromVector v2))
v1 - v2 =3DVector (zipWith (-) (fromVector v1) (fromVector v2))
v1 * v2 =3DVector (zipWith (*) (fromVector v1) (fromVector v2))
signum v =3D Vector (map signum (fromVector v))
abs v =3D Vector ((repeat.sqrt.sum.fromVector) (v*v))
fromInteger n =3DVector (repeat (fromInteger n))
instance Fractional Vector where
v1 / v2 =3D Vector (zipWith (/) (fromVector v1) (fromVector=
v2))
fromRational r =3DVector (repeat (fromRational r))
-----------------------------------------------------------------=
---------
rk4 ::=
((Vector,Vector)->Vector)->Vector->Vector->Vector->[Vector]
rk4 _ _ _ (Vector []) =3D []
rk4 f h y0 (Vector (x0:xs)) =3D y0 :rk4 f h y1 (Vector xs) where=
y1=3Dyp f h (toVector x0) y0
yp ::((Vector,Vector)->Vector)->Vector->Vector->Vector->Vector
yp f h x y =3D y + (k1 + 2 * (k2 + k3) + k4)
where k1=3Dh*f(x,y)
k2=3Dh*f(x+0.5*h, y +(0.5*k1))
k3=3Dh*f(x+0.5*h, y +(0.5*k2))
k4=3Dh*f(x+h, y+k3)
a=3Dlet g (x,y1) =3D y1
x0 =3D 0
h =3D 0.01
x =3DVector [x0,x0+h..3]
y0 =3DVector [0,0.5]
in rk4 g (toVector h) y0 x
-----------------------------------------------------------------=
---------
The main problem is how to make type convert implicitly.
Whem a function needs a vector as its parameter, pass a double=
and it is
converted to vector implicitly.
=3D=3D=3D=3D=3D=3D=3D 2003-07-12 12:18:00 Jon Fairbairn Wrote=A3=BA=3D=3D=3D=3D=3D=3D=3D
>On 2003-07-12 at 20:20+1000 Andrew J Bromage wrote:
>> G'day all.
>>
>> On Fri, Jul 11, 2003 at 04:28:19PM -0400, Dylan Thurston=
wrote:
>>
>> > Don't be silly [...]
>>
>> Never!
>
>Or only sometimes. I'm surprised that no-one has yet
>answered the question "How overload operator in Haskell?"
>with "Overload operator in Haskell fine". (cf Cary Grant)
I am also surprised at this, it can be done by C++ .
>
>--
>J=F3n Fairbairn =
Jon.Fairbairn@cl.cam.ac.uk
>31 Chalmers Road =
jf@cl.cam.ac.uk
>Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only,=
please!)
>
>
>_______________________________________________
>Haskell mailing list
>Haskell@haskell.org
>http://www.haskell.org/mailman/listinfo/haskell
=3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D =3D
=09=09=09
Regards,=09=09=09=09
Liu Junfeng
liujf@softhome.net
2003-07-12