1 {-# OPTIONS_GHC -Wno-orphans #-}
2 {-# LANGUAGE FlexibleInstances #-}
10 -- Presumably this is faster without a newtype wrapper, and that's why
11 -- we're about to define a bunch of orphan instances below. Note the
12 -- GHC pragma thingy at the top of this file to ignore those warnings.
13 type RealFunction a = (a -> Double)
16 -- | A 'Show' instance is required to be a 'Num' instance.
17 instance Show (RealFunction a) where
18 -- | There is nothing of value that we can display about a
19 -- function, so simply print its type.
20 show _ = "<RealFunction>"
23 -- | An 'Eq' instance is required to be a 'Num' instance.
24 instance Eq (RealFunction a) where
25 -- | Nothing else makes sense here; always return 'False'.
26 _ == _ = error "You can't compare functions for equality."
29 -- | The 'Num' instance for RealFunction allows us to perform
30 -- arithmetic on functions in the usual way.
31 instance Num (RealFunction a) where
32 (f1 + f2) x = (f1 x) + (f2 x)
33 (f1 - f2) x = (f1 x) - (f2 x)
34 (f1 * f2) x = (f1 x) * (f2 x)
35 (negate f) x = -1 * (f x)
37 (signum f) x = signum (f x)
38 fromInteger i _ = fromInteger i
41 -- | Takes a constant, and a function as arguments. Returns a new
42 -- function representing the original function times the constant.
46 -- >>> let square x = x**2
51 -- >>> let f = cmult 2 square
57 cmult :: Double -> (RealFunction a) -> (RealFunction a)
58 cmult coeff f = (*coeff) . f
61 -- | Takes a function @f@ and an exponent @n@. Returns a new function,
62 -- @g@, defined by g(x) = (f(x))^n. This is /not/ @f@ composed
63 -- with itself @n@ times.
67 -- >>> let square x = x**2
70 -- >>> let f = fexp square 3
74 fexp :: (RealFunction a) -> Int -> (RealFunction a)
77 | otherwise = \x -> (f x)^n