Claus Reinke wrote:
the usual way to achieve this uses the overloading of Nums in Haskell:
when you write '1' or '1+2', the meaning of those expressions depends
on their types. in particular, the example above uses 'T Double', not
just 'Double'.

However there is nothing in the functions themselves that restricts their use to just T Double. Thus the functions can be compared for equality by supplying an argument of type T Double but used elsewhere in the program with args of type (plain) Double eg:

-- Change to module AbsNum
instance (Simplify a)=>Eq (T a) where
   (==) (Const x) (Const y) = x == y
   (==) (Var x) (Var y) = x == y
   (==) (Add xs) (Add ys) = and (map (\(x, y) -> x==y) (zip xs ys))
   (==) _ _ = False -- Not needed for the example

module Main where
import AbsNum

f x = x + 2.0
g x = x + 1.0 + 1.0

funeq :: (T Double -> T Double) -> (T Double -> T Double) -> Bool
funeq p q = let y = Var "y" in p y == q y

main = do
print (funeq f g)
print (f 10)
print (g 10)
putStrLn ""
print (funeq f f)
print (f 10)
print (g 10)

main
False
12.0
12.0

True
12.0
12.0

Thus we can determine that f is implemented by different code from g (The example would be even more convincing if Int's were used instead of Double's) and so f and g are not interchangeable.

... nothing prevents us from defining that instance in such a way that we construct a
representaton instead of doing any additions.

Thus referential transparency of polymorphic functions is foiled.

Regards, Brian.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to