x^y. Reply

2001-12-20 Thread S.D.Mechveliani

Toralf Wittner [EMAIL PROTECTED]

writes

 [..]
 data PowerNum = INT Integer | DBL Double deriving (Eq, Show, Read)
 [..]
 Now it basically works. However wouldn't it have been easier to write  
 something like this:
 
 powPos :: Integer - Integer - Integer
 [..]
 powNeg :: Integer - Integer - Double
 [..]
   | 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!


For this particular task, the most natural solution is, probably,   

  pow :: Fractional a = a - Integer - a
  pow a n = 
   if n  0 then a^n  else (1/a)^(- n)

(^) is of standard, only  pow  adds the facility of negative n.

Then, you need each time to convert the argument to appropriate
type of Fractional: 

   pow (fromInteger 2 :: Ratio.Rational) 2 -- 4 % 1
   pow (fromInteger 2 :: Ratio.Rational) (-2)  -- 1 % 4
   pow (2 :: Double) (-2)  -- 0.25
   pow (2 :: Integer) (-2) --
   ... No instance for (Fractional Integer)

If you replace standard (and not lucky)  Fractional  with some 
class  Foo  (with multiplication  mul  and  division  div), 
make  Integer  an instance of  Foo  
(where  div  may fail for some data),
and program 
  pow :: Foo a = a - Integer - a
via  mul, div,
then it would work like this:

  pow (2 :: Integer)  2-- 4
  pow (2 :: Integer)  (-2) -- Error: cannot invert 2 :: Integer
  pow (2 :: Rational) (-2) -- 1%4

Another way is to try to straggle with overlapping instances by
defining something like this:

  class Pow a b where pow :: a - Integer - b

  instance Num a = Pow a a   where  pow = (^)
   Fractional ? 
  instance Num a = Pow Integer a where  pow = ?

If this succeeds, there will be also no need in new type 
constructors.

-
Serge Mechveliani
[EMAIL PROTECTED]





___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



x^y. Reply

2001-12-19 Thread S.D.Mechveliani

Toralf Wittner [EMAIL PROTECTED] writes

 [..]
 power x y
 [..]
   | y  0 = x * power x (y-1)
   | y  0 = 1 / fromInteger x * power x (y+1)

 One recognizes that the function returns either an integer value 
 if y  0 or a float value if y  0. Therefore I can't write a 
 signature like 
 pow :: Integer - Integer - Integer nor can I do 
 pow :: Integer - Integer - Double. 

 [..]
 How then would I write this function in Haskell (concerning types)?


The type  Rational  fits the case n  0 too, and it includes Integer.

But if you still need  Integer | Double,  you can, for example,
introduce a new type of a disjoint union of the above two, and then,
to compute like this:
  pow (Intg 2) 2 --  Intg 4  
  pow (Intg 2) (-2)  --  D 0.25
  pow (D 2.0)  (-2)  --  D 0.25
This is achieved by

  data PowerDom = Intg Integer | D Double  deriving(Eq,Show)

  pow :: PowerDom - Integer - PowerDom
  pow x n = p x n
where
p (Intg m) n = if  n  0  then  Intg $ powerInteger m n
   else  D $ powerDouble (fromInteger m :: Double) n
p(D d) n = D $ powerDouble d n

powerInteger m n = m^n  :: Integer

powerDouble :: Double - Integer - Double
powerDoubled n   =  ... usual way for float

- something like this.


-
Serge Mechveliani
[EMAIL PROTECTED]



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: x^y. Reply

2001-12-19 Thread Toralf Wittner

On Wednesday, 19. December 2001 09:12, S.D.Mechveliani wrote:
[...]
 But if you still need  Integer | Double,  you can, for example,
 introduce a new type of a disjoint union of the above two, and then,
 to compute like this:
   pow (Intg 2) 2 --  Intg 4
   pow (Intg 2) (-2)  --  D 0.25
   pow (D 2.0)  (-2)  --  D 0.25
 This is achieved by

   data PowerDom = Intg Integer | D Double  deriving(Eq,Show)

   pow :: PowerDom - Integer - PowerDom
   pow x n = p x n
 where
 p (Intg m) n = if  n  0  then  Intg $ powerInteger m n
else  D $ powerDouble (fromInteger m :: Double) n
 p(D d) n = D $ powerDouble d n

 powerInteger m n = m^n  :: Integer

 powerDouble :: Double - Integer - Double
 powerDoubled n   =  ... usual way for float

 - something like this.

This seems to be what I want. I tried it this way:

module Main where
import System

main = do
[a1, a2] - getArgs
let x = read a1 
let y = read a2 in
putStrLn (show x ++  ^  ++ show y ++  =  ++ show (pow x y))

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
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)



While GHC compiled this code I get a runtime error: 

Fail: Prelude.read: no parse

and HUGS reports:

ERROR: Illegal Haskell 98 class constraint in inferred type
*** Expression : pow 1 2
*** Type   : Num PowerNum = PowerNum


Could you tell me what I did wrong? Thank you very much!
Toralf



 -
 Serge Mechveliani
 [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell