Search code examples
haskellequality

Equality of functions in Haskell


I am trying to define a function which would take a Double -> Double function and return its mathematical derivative. I have tried doing the following:

der :: (Double -> Double) -> (Double -> Double)
der f
    | f == exp = exp
    | otherwise = undefined

but Haskell does not support == on Double -> Double values. Is what I am trying to do impossible in Haskell?


Solution

  • Yes, what you are trying to do is impossible in Haskell, and in general: deciding whether two functions are equal for all possible inputs (without just checking every input value, if that is even possible) is equivalent to solving the Halting problem.

    However, in your specific case, you can get around it, using a custom type that simulates a Double (i.e. has the same instances, and so can be used in place of it) but instead of evaluating to a number, it constructs an abstract representation of the operations the functions does. Expr represents the right-hand side of a mathematical function definition f(x) = ....

    data Expr = X | Const Double |
                Add Expr Expr | Mult Expr Expr |
                Negate Expr | Inverse Expr |
                Exp Expr | Log Expr | Sin Expr | ...
           deriving (Show, Eq)
    
    instance Num Expr where
        (+) = Add
        (*) = Mult
        ...
    instance Fractional Expr where
        recip = Inverse
        ...
    instance Floating Expr where
        pi = Const pi
        exp = Exp
        log = Log
        sin = Sin
        ...
    

    Then, using rank-2 types, you can define conversion functions that convert between functions that take any Floating and Exprs:

    {-# LANGUAGE Rank2Types #-}
    
    fromFunction :: (forall a. Floating a => (a -> a)) -> Expr
    fromFunction f = f X
    
    toFunction :: Expr -> (Double -> Double)
    toFunction X = \x -> x
    toFunction (Const a) = const a
    toFunction (Add a b) = \x -> (toFunction a x) + (toFunction b x)
    ...
    

    You can also define a function diff :: Expr -> Expr that differentiates the expression:

    diff X = Const 1
    diff (Const _) = Const 0
    diff (Add a b) = Add (diff a) (diff b)
    diff (Exp a) = Mult (diff a) (Exp a)
    ...
    

    Having all these parts should mean that you can differentiate (some) functions, e.g.

    f x = sin x + cos x * exp x
    f' = toFunction . diff . fromFunction $ f
    

    Caveats:

    • this won't work in general,
    • defining a complete Eq instance for Expr is tricky (it is equivalent to the Halting problem, since it is basically asking if two functions are equal),
    • I haven't actually tested any of this code,
    • the differentiation and reconstruction are done at runtime, so the resulting function is highly likely to be very slow.