1 {-# LANGUAGE TypeSynonymInstances #-}
7 type RealFunction a = (a -> Double)
10 -- | A 'Show' instance is required to be a 'Num' instance.
11 instance Show (RealFunction a) where
12 -- | There is nothing of value that we can display about a
13 -- function, so simply print its type.
14 show _ = "RealFunction"
17 -- | An 'Eq' instance is required to be a 'Num' instance.
18 instance Eq (RealFunction a) where
19 -- | Nothing else makes sense here; always return 'False'.
23 -- | The 'Num' instance for RealFunction allows us to perform
24 -- arithmetic on functions in the usual way.
25 instance Num (RealFunction a) where
26 (f1 + f2) x = (f1 x) + (f2 x)
27 (f1 - f2) x = (f1 x) - (f2 x)
28 (f1 * f2) x = (f1 x) * (f2 x)
29 (negate f) x = -1 * (f x)
31 (signum f) x = signum (f x)
32 fromInteger i _ = fromInteger i
35 -- | Takes a constant, and a function as arguments. Returns a new
36 -- function representing the original function times the constant.
37 cmult :: Double -> (RealFunction a) -> (RealFunction a)
38 cmult coeff f = (*coeff) . f
41 -- | Takes a function f and an exponent n. Returns a new function,
43 fexp :: (RealFunction a) -> Int -> (RealFunction a)
46 | otherwise = \x -> (f x)^n