Ahh - sorry, too much cut and paste ;-)
data PowerNum = INT Integer | DBL Double deriving (Eq, Show, Read) pow :: PowerNum -> Integer -> PowerNum pow x y = z x y where z (INT x) y = if y > 0 then INT $ powInteger x y else if y == 0 then INT $ 1 else DBL $ powDouble (fromInteger x) y z (DBL x) y = DBL $ powDouble x y powInteger x y | x == 0 = 0 | y == 0 = 1 | y > 0 = x * powInteger x (y - 1) powDouble x y | x == 0 = 0 | y == 0 = 1 | y < 0 = 1 / x * powDouble x (y + 1) Now it basically works. However wouldn't it have been easier to write something like this: module Main where import System main = do [a1, a2] <- getArgs let x = read a1 let y = read a2 in if y >= 0 then putStrLn (show x ++ " ^ " ++ show y ++ " = " ++ show (powPos x y)) else putStrLn (show x ++ " ^ " ++ show y ++ " = " ++ show (powNeg x y)) powPos :: Integer -> Integer -> Integer powPos x y | x == 0 = 0 | y == 0 = 1 | y > 0 = x * powPos x (y - 1) powNeg :: Integer -> Integer -> Double powNeg x y | x == 0 = 0 | y == 0 = 1 | y < 0 = 1 / fromInteger x * powNeg x (y + 1) Initially I wanted something as terse as the Python version, now I either have to write two functions or I need to define a type. Is there not an easier way to come as close as possible to the Python version? Thanks anyway - learnt a lot! Toralf _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell