[Haskell-cafe] Confused about types

Lanny Ripple lanny at cisco.com
Fri Sep 30 23:35:24 EDT 2005


I thought I was doing ok with haskell until I tried to program in 
it.  :/  I figured the first thing to tackle was something easy 
so I hacked up newton's method.  Worked great for Double's.  Then 
I figured I would extend it to work with different types of 
Fractionals.  What a pain.  I finally got that working for Floats 
and Rationals but I'm drawing a blank on Complex.

I've got:

<Newton.hs>
import Data.Complex
import Data.Ratio
import Debug.Trace

main = putStrLn $ "answer = " ++ show (newton myd $ -5)

newton :: (Fractional a, Ord a) => (a -> a) -> a -> a
newton f x = newton_h f x 1.0e-6

newton_h, next_x_h, dy_h :: (Fractional a, Ord a) => (a -> a) -> 
a -> a -> a
newton_h f x h = until ((<= h) . abs . f) (next_x_h f h) x

next_x_h f h x = trace ("next_x = " ++ show foo) foo
         where foo = x - (f x) / (dy_h f x h)

dy_h f x h = ( (f $ x + h) - f x ) / h

-- roundTo :: Fractional a => a -> a -> a
-- roundTo x eps = ((fromRational . toRational) (round $ x / 
eps)) * eps

myd :: Double -> Double
myd x = ((x/100 + 1) * x + 1) * x - 10

myf :: Float -> Float
myf x = ((x/100 + 1) * x + 1) * x - 10

myr :: Rational -> Rational
myr x = approxRational myr' 1e-6
         where myr' = ((x/100 + 1) * x + 1) * x - 10

myc :: RealFloat a => Complex a -> Complex a
myc x = x * x + 1
</Newton.hs>

When I try

   newton myc 5

in ghci I get a warning about newton wanting Ords.  Complex 
aren't ordered.  I figure I need to specify a newton_h that can 
handle complex

   newton_h f (Complex x) h =
       until ((<= h) . realPart . abs . f) (next_x_h f h) x

laughs at me.  So does

   newton_h f (:+ r im) h =
       until ((<= h) .realPart . abs . f) (next_x_h f h) (:+ r im)

although I sure thought I had read that constructors could be 
used in pattern matching.  I've been working on this for too long 
and getting frustrated.  Can someone clue me in?

   Thanks,
   -ljr

-- 
Lanny Ripple <lanny at cisco.com>
CC Tools / Cisco Systems, Inc.


More information about the Haskell-Cafe mailing list