I come up a solution as this: --------------------------------------------------- module Vector where data Vector =Vector [Double] fromVector :: Vector -> [Double] fromVector (Vector v) = v fromList :: [Double] -> Vector fromList v = Vector v toVector :: Double -> Vector toVector x = Vector (repeat x) instance Eq Vector where v1 ==v2 = (fromVector v1) == (fromVector v2) instance Show Vector where show v = show (fromVector v) instance Num Vector where v1 + v2 =Vector (zipWith (+) (fromVector v1) (fromVector v2)) v1 - v2 =Vector (zipWith (-) (fromVector v1) (fromVector v2)) v1 * v2 =Vector (zipWith (*) (fromVector v1) (fromVector v2)) signum v = Vector (map signum (fromVector v)) abs v = Vector ((repeat.sqrt.sum.fromVector) (v*v)) fromInteger n =Vector (repeat (fromInteger n)) instance Fractional Vector where v1 / v2 = Vector (zipWith (/) (fromVector v1) (fromVector v2)) fromRational r =Vector (repeat (fromRational r)) -------------------------------------------------------------------------- rk4 :: ((Vector,Vector)->Vector)->Vector->Vector->Vector->[Vector] rk4 _ _ _ (Vector []) = [] rk4 f h y0 (Vector (x0:xs)) = y0 :rk4 f h y1 (Vector xs) where y1=yp f h (toVector x0) y0 yp ::((Vector,Vector)->Vector)->Vector->Vector->Vector->Vector yp f h x y = y + (k1 + 2 * (k2 + k3) + k4) where k1=h*f(x,y) k2=h*f(x+0.5*h, y +(0.5*k1)) k3=h*f(x+0.5*h, y +(0.5*k2)) k4=h*f(x+h, y+k3)
a=let g (x,y1) = y1 x0 = 0 h = 0.01 x =Vector [x0,x0+h..3] y0 =Vector [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. ======= 2003-07-12 12:18:00 Jon Fairbairn Wrote:======= >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? Fairbairn [EMAIL PROTECTED] >31 Chalmers Road [EMAIL PROTECTED] >Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only, please!) > > >_______________________________________________ >Haskell mailing list >[EMAIL PROTECTED] >http://www.haskell.org/mailman/listinfo/haskell = = = = = = = = = = = = = = = = = = = = Regards, Liu Junfeng [EMAIL PROTECTED] 2003-07-12 _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell