{-# OPTIONS_GHC -Wno-orphans #-} {-# LANGUAGE FlexibleInstances #-} module RealFunction ( RealFunction, cmult, fexp ) where -- Presumably this is faster without a newtype wrapper, and that's why -- we're about to define a bunch of orphan instances below. Note the -- GHC pragma thingy at the top of this file to ignore those warnings. type RealFunction a = (a -> Double) -- | A 'Show' instance is required to be a 'Num' instance. instance Show (RealFunction a) where -- | There is nothing of value that we can display about a -- function, so simply print its type. show _ = "" -- | An 'Eq' instance is required to be a 'Num' instance. instance Eq (RealFunction a) where -- | Nothing else makes sense here; always return 'False'. _ == _ = error "You can't compare functions for equality." -- | The 'Num' instance for RealFunction allows us to perform -- arithmetic on functions in the usual way. instance Num (RealFunction a) where (f1 + f2) x = (f1 x) + (f2 x) (f1 - f2) x = (f1 x) - (f2 x) (f1 * f2) x = (f1 x) * (f2 x) (negate f) x = -1 * (f x) (abs f) x = abs (f x) (signum f) x = signum (f x) fromInteger i _ = fromInteger i -- | Takes a constant, and a function as arguments. Returns a new -- function representing the original function times the constant. -- -- ==== __Examples__ -- -- >>> let square x = x**2 -- >>> square 1 -- 1.0 -- >>> square 2 -- 4.0 -- >>> let f = cmult 2 square -- >>> f 1 -- 2.0 -- >>> f 2 -- 8.0 -- cmult :: Double -> (RealFunction a) -> (RealFunction a) cmult coeff f = (*coeff) . f -- | Takes a function @f@ and an exponent @n@. Returns a new function, -- @g@, defined by g(x) = (f(x))^n. This is /not/ @f@ composed -- with itself @n@ times. -- -- ==== __Examples__ -- -- >>> let square x = x**2 -- >>> square 2 -- 4.0 -- >>> let f = fexp square 3 -- >>> f 2 -- 64.0 -- fexp :: (RealFunction a) -> Int -> (RealFunction a) fexp f n | n == 0 = const 1 | otherwise = \x -> (f x)^n