Symbolic simplification in Haskell (using recursion?) - haskell

How can I give a general rule that includes all the expressions below?
E.g one expression, another one for sub and one for mult.
I need to use recursion but i got confused...
simplify :: Expr->Expr
simplify (Mult (Const 0)(Var"x"))
= Const 0
simplify (Mult (Var "x") (Const 0))
= Const 0
simplify (Plus (Const 0) (Var "x"))
= Var "x"
simplify (Plus (Var "x") (Const 0))
= Var "x"
simplify (Mult (Const 1) (Var"x"))
= Var "x"
simplify (Mult(Var"x") (Const 1))
= Var "x"
simplify (Minus (Var"x") (Const 0))
= Var "x"
simplify (Plus (Const x) (Const y))
= Const (x + y)
simplify (Minus (Const x) (Const y))
= Const (x - y)
simplify (Mult (Const x) (Const y))
= Const (x * y)
simplify x = x

First up: I know reasonably little about Haskell, and my total time spent programming the language is no more than 8 hours spread over 5 years or so, though I have read plenty about the language. Thus, forgive my no doubt horrible style.
I tackled this problem since it looked like an easy way to get into a little bit of Haskell programming. First up, I made a data type inspired by the sample:
data Expr = Const Int | Mult Expr Expr | Plus Expr Expr | Var String
I made it a little simpler than the original, and left out Minus, but otherwise it's the same.
I quickly found out that values constructed using e.g. "Const 4" were not printable with the above, as there was no show function applicable. I made Expr an instance of the Show type class, and provided a simple definition of show, taking operator precedence into account:
instance Show Expr where
show (Const n) = show n
show (Var n) = show n
show (Plus a b) = (show a) ++ "+" ++ (show b)
show (Mult a b) = "(" ++ (show a) ++ ") * (" ++ (show b) ++ ")"
Next up was the simplification task itself. As Glomek hints, there's an issue with trying to evaluate everything just using pattern matching in one function.
Specifically, for any given operation (all operations in the example are binary) you'd like to first simplify the left tree, then the right tree, and then simplify the current Expr based on what those subtrees evaluated to; e.g. if both simplified to Const, then you can replace the entire subtree with the evaluated operation. However, pattern matching forces you to choose what to do based on the immediate node's children, rather than what the subtrees return after being simplified themselves.
Thus, to get pattern-matching to do the job of deciding whether to evaluate the current node or not as a constant subexpression, it's important to simplify the subtrees, then dispatch based on the simplified whole.
I did this using a separate function I called eval, whose purpose is to pattern-match on things that can be reduced, assuming that subtrees have already been reduced. It also handles multiplication by 0 and 1, and addition of 0:
-- Tries to evaluate any constant expressions.
eval :: Expr -> Expr
eval (Mult (Const a) (Const b)) = Const (a * b)
eval (Mult (Const a) b)
| a == 0 = Const 0
| a == 1 = b
| otherwise = (Mult (Const a) b)
eval (Mult a (Const b))
| b == 0 = Const 0
| b == 1 = a
| otherwise = (Mult a (Const b))
eval (Plus (Const a) (Const b)) = Const (a + b)
eval (Plus (Const a) b)
| a == 0 = b
| otherwise = (Plus (Const a) b)
eval (Plus a (Const b))
| b == 0 = a
| otherwise = (Plus a (Const b))
eval e = e
Now that I have eval, and I know it's safe to call at the top level of an expression tree (i.e. it won't infinitely recurse), I can call it from simplify after I've simplified the subtrees:
-- Tries to match evaluation rules after simplifying subtrees.
simplify :: Expr -> Expr
simplify (Plus a b) = eval (Plus (simplify a) (simplify b))
simplify (Mult a b) = eval (Mult (simplify a) (simplify b))
simplify e = e
This version of simplify has many limitations: it won't distribute a multiplication over a non-Const subtree, it won't reorder the expression to bring constant expressions together (so the equivalent of 1+a+2 won't get simplified to a+3), etc. However, it gets the basic jobs done.

The recursion comes in when you need to deal with nested expressions. For instance, how do you simply (Plus (Plus 2 3) (Plus 4 5))?
One approach is to break it into two functions. Move the one level logic (which you show above) into its own function. The main simplify function might have a rule similar to the following for Plus:
simplify (Plus x y) = simplify_one_level (Plus (simplify x) (simplify y))

Related

left associate an operation in haskell

I want to return the left association of an expression given (haskell), so if we have a + (b + c) the function has to return (a + b) + c, this also applies for the multiplication since these 2 operations are associative. taking onto consideration the other operations that are not associative therefor I have to put a condition to not left associate those expressions.
so the leftAssociate function turns every expression given into an equivalent left-associated one with the same constants
the function is defined as follow :
data Expr = Val Int | App Op Expr Expr
leftAssociate :: Expr -> Expr
leftAssociate (App Add (Val a) (App Add (Val b) (Val c))) = App Add (App Add (Val a) (Val b)) (Val c)
I have tried pattern matching but it's too overwhelming as there is a lot of possibilities and also I cannot specify the number of operations given as input as it's not limited.
You say
we consider it left-balances [sic] if it has no subexpressions of shape App Op x ( App Op y z) and that's only when the operation is Addition or Multiplication
I therefore propose that you structure your function for fixing this defect in the way you described:
leftAssociate (App Add x (App Add y z)) = -- ...
leftAssociate (App Mul x (App Mul y z)) = -- ...
leftAssociate (App op x y) = -- ...
leftAssociate (Val n) = -- ...
Presumably in the first three cases you will make recursive calls at some point to make sure that the x, y, and z subterms are also left-associated. This recursion will be the mechanism that allows you to handle arbitrarily large expressions.
I find it easiest to conceptualize this like so: for each subtree rooted at an App op _ _ node with an op you want to re-associate, you can collect all the terms at the top of the subtree being combined with that same App op into a flattened list, and then create a left associated tree with a foldl1 from that list. This gives the following solution:
data Expr = Val Int | App Op Expr Expr deriving (Show)
data Op = Add | Mul | Sub deriving (Show, Eq)
-- Identify which operators should be re-associated
isAssoc :: Op -> Bool
isAssoc Add = True
isAssoc Mul = True
isAssoc _ = False
leftAssociate :: Expr -> Expr
leftAssociate a#(App op _ _)
| isAssoc op = foldl1 (App op) $ opTerms a
where opTerms :: Expr -> [Expr]
opTerms (App op' x' y') | op' == op = opTerms x' ++ opTerms y'
opTerms e = [leftAssociate e]
leftAssociate (App op x y) = App op (leftAssociate x) (leftAssociate y)
leftAssociate e = e
You can technically get rid of the intermediate flattened list by constructing the left associated tree directly and defining a concatenation function for left associated trees, and I think that would give you the sort of direct recursive solution being discussed in the other answer, but I found this version easier to write.
Here's a test case:
mul = App Mul
add = App Add
sub = App Sub
ex1 = leftAssociate (add (Val 1) (sub (mul (Val 2) (mul (Val 3) (Val 4)))
(add (add (Val 5) (Val 6)) (add (Val 7) (Val 8)))))
main = print $ leftAssociate ex1
TL;DR:
instead of turning:
+
/ \
/ \
a +
/ \
/ \
b c
into
+
/ \
/ \
+ c
/ \
/ \
a b
I'd suggest to alter the tree to be non-binary:
+
/|\
/ | \
a b c
Longer Explanation
if we have a + (b + c) the function has to return (a + b) + c
I would not do that. I would choose a different representation than Expr = Val Int | App Op Expr Expr. Expr as binary tree is not associative. How about
data AssocExpr = AVal Int | AApp Op [Expr]
Lists are associative by design. You can keep both data structures around and convert to AssocExpr when you need the associativity. And if you really need it, you can still convert back and thereby achieve the initial goal.
To transform from Expr to AssocExpr, you can modify leftAssociate from K. A. Buhr's answer and eliminate the foldl1:
associate :: Expr -> AssocExpr
associate a#(App op _ _)
| isAssoc op = AApp op $ opTerms a
...
Related Codereview (from myself):
https://codereview.stackexchange.com/questions/254288/parametrize-by-type-constructor/254572#254572

Generic transformations on a set of a given datatype

If I have a datatype representing a subset of propositional logic such as
data Prop = Lit String
| Neg Prop
| And Prop Prop
| Or Prop Prop
Are there then easy ways to do generic transformations on [[Prop]]? E.g.
replace [[And a b, c]] with [[a, b, c]]
replace [[Or a b, c]] with [[a], [b], [c]], or
removing occurrences of sublists containing both Neg a and a, e.g. turning [[Neg a, x, a], [b]] into [[b]]
This feels like something close to what e.g. uniplate does, but “two levels up”.
I assume that your second rule is wrong, and you really meant to say either:
replace [[Or a b],[c]] with [[a],[b],[c]]
or else:
replace [[Or a b, c]] with [[a,c],[b,c]]
In other words, I assume you're trying to convert a Prop into an alternate representation [[Prop]] where the first-level list is an "or" and the second-level lists are "and"s, with all terms being either literals or Neg-literals. So, you're trying to imagine how you could apply a bunch of generic structural rules to make transformations like:
[[And a (Or b c)]]
[[a, Or b c]] -- apply "And" rule
[[a,b],[a,c]] -- apply some kind of "Or" distribution rule
If so, having generic transformations isn't much use. With your current datatype, you can only apply these transformations to top-level expressions anyway. For example, there's no obvious way to apply an Or rule here:
[[And a (And b (Or c d))]]
without first applying And rules a couple of times. If you change your data type to add, say, an L2 [[Prop]] constructor, so you can transform the above expression to:
[[And a (And b (L2 [[c],[d]]))]] -- apply "Or" rule
it's not clear what that buys you.
Ultimately, I don't think this is the right approach...
You have a perfectly adequate representation of your prepositional logic in the Prop data type; and you have a desired final representation. Instead of trying to translate your Prop representation into the final representation using piecemeal generic transformations, transform your Prop representation using standard recursive Prop-to-Prop transformations into a canonical Prop form, and do the translation as the final step.
Here, a reasonable canonical form is:
Or e1 (Or e2 (... (Or e3 e4)))
where each ek is of form:
And t1 (And t2 (... (And t3 t4)))
and each tk is either a Lit _ or a Neg (Lit _). Obviously, this canonical form can be translated pretty easily into the desired final representation as a [[Prop]].
I've included a possible solution below. I don't see that much opportunity for simplifying things via generic transformations. Most of the pattern matching seems to be doing non-trivial work.
Possible Solution
After a bit of preamble:
import Data.List
data Prop = Lit String
| Neg Prop
| And Prop Prop
| Or Prop Prop
deriving (Eq)
then one way to translate an arbitrary Prop into this canonical form is to first push all the Negs down to the literal terms:
pushNeg :: Prop -> Prop
pushNeg = push False
where
-- de Morgan's laws
push neg (And x y) = (if neg then Or else And) (push neg x) (push neg y)
push neg (Or x y) = (if neg then And else Or) (push neg x) (push neg y)
-- handle Neg and Lit
push neg (Neg y) = push (not neg) y
push neg (Lit l) = if neg then Neg (Lit l) else Lit l
then push all the Ands down on top of them. This is tougher to get right, but I think the following is correct, even though it does a bit of unnecessary work in some cases:
pushAnd :: Prop -> Prop
pushAnd (Or x y) = Or (pushAnd x) (pushAnd y)
pushAnd (And x y)
= let x' = pushAnd x
in case x' of
Or u v -> Or (pushAnd (And u y)) (pushAnd (And v y))
_ -> let y' = pushAnd y
in case y' of
Or u v -> Or (pushAnd (And x' u)) (pushAnd (And x' v))
_ -> And x' y'
pushAnd x = x
and then recursively make all the And and Or clauses right-associative:
rassoc :: Prop -> Prop
rassoc (Or (Or x y) z) = rassoc (Or x (Or y z))
rassoc (Or x z) = Or (rassoc x) (rassoc z)
rassoc (And (And x y) z) = rassoc (And x (And y z))
rassoc (And x z) = And x (rassoc z)
rassoc x = x
and finally convert the canonical form to its final representation (dropping the inconsistent clauses and duplicate terms while we're at it):
translate :: Prop -> [[Prop]]
translate = nub . map nub . filter consistent . doOr
where
doOr x = case x of
Or x y -> doAnd x : doOr y
x -> doAnd x : []
doAnd x = case x of
And x y -> x : doAnd y
x -> x : []
consistent lits =
let (falses, trues) = partition isNeg lits
falses' = map (\(Neg (Lit l)) -> l) falses
trues' = map (\ (Lit l) -> l) trues
in null (intersect falses' trues')
isNeg (Neg x) = True
isNeg _ = False
The whole pipeline is:
final :: Prop -> [[Prop]]
final = translate . rassoc . pushAnd . pushNeg
and here's some test code:
a = Lit "a"
b = Lit "b"
c = Lit "c"
d = Lit "d"
e = Lit "e"
-- Show instance, but only for `final` forms
instance Show Prop where
show (Lit x) = x
show (Neg (Lit x)) = '~':x
main :: IO ()
main = do print $ final (Neg a)
print $ final (Or a b)
print $ final (Or a a)
print $ final (And a b)
print $ final (And (Or (And (Or a b) c) d) e)
print $ final (And (Or (Or a b) c) (Neg (And a (Or b d))))
which outputs:
[[~a]]
[[a],[b]]
[[a]]
[[a,b]]
[[a,c,e],[b,c,e],[d,e]]
[[a,~b,~d],[b,~a],[c,~a],[c,~b,~d]]
There's still some opportunity for further simplification, as:
final (And a (Or a b))
gives final form [[a],[a,b]] instead of just [[a]].

Genetic Programming in Haskell

There is GenProg (http://hackage.haskell.org/package/genprog) for example, but that only deals with numerical optimization, in this case finding an equation that describes the data.
But I require for loops, if statements, when statements, Boolean checks etc. I need to be able to generate imperative structures. Any thought on this? My best options so far seem to be husk-scheme where I can run Scheme code as a DSL in Haskell. Surely there must be better ways?
If you're looking for something akin to S-expressions, this is fairly easily modeled in Haskell. Say, for example, we want to represent simple algebraic equations with variables, such as
x + 5 / (y * 2 - z)
This can be represented by a simple AST in Haskell, in particular we can implement it as
data Expr
= Lit Double -- Literal numbers
| Var Char -- Variables have single letter names
| Add Expr Expr -- We can add things together
| Sub Expr Expr -- And subtract them
| Mul Expr Expr -- Why not multiply, too?
| Div Expr Expr -- And divide
deriving (Eq)
This would let us express the equation above as
Add (Var 'x') (Div (Lit 5) (Sub (Mul (Var 'y') (Lit 2)) (Var 'z')))
But this is rather clunky to write and difficult to read. Let's start by working some Show magic so that it gets pretty printed:
instance Show Expr where
showsPrec n (Lit x) = showParen (n > 10) $ showsPrec 11 x
showsPrec n (Var x) = showParen (n > 10) $ showChar x
showsPrec n (Add x y) = showParen (n > 6) $ showsPrec 7 x . showString " + " . showsPrec 7 y
showsPrec n (Sub x y) = showParen (n > 6) $ showsPrec 7 x . showString " - " . showsPrec 7 y
showsPrec n (Mul x y) = showParen (n > 7) $ showsPrec 8 x . showString " * " . showsPrec 8 y
showsPrec n (Div x y) = showParen (n > 7) $ showsPrec 8 x . showString " / " . showsPrec 8 y
If you don't understand everything going on here, that's ok, it's a lot of complication made easy by some built in functions for efficiently building strings with parentheses in them properly and all that fun stuff. It's pretty much copied out of the docs in Text.Show. Now if we print out our expression from above, it'll look like
x + 5.0 / (y * 2.0 - z)
Now for simplifying building these expressions. Since they're pretty much numeric, we can implement Num (except for abs and signum) and Fractional:
instance Num Expr where
fromInteger = Lit . fromInteger
(+) = Add
(-) = Sub
(*) = Mul
abs = undefined
signum = undefined
instance Fractional Expr where
(/) = Div
fromRational = Lit . fromRational
Now we can input out expression from above as
Var 'x' + 5 / (Var 'y' * 2 - Var 'z')
This is at least much easier to visually parse, even if we have to specify the variables manually.
Now that we have pretty input and output, let's focus on evaluating these expressions. Since we have variables in here, we'll need some sort of environment that associates a variable with a value
import Data.Map (Map)
import qualified Data.Map as M
type Env = Map Char Double
And now it's just basic pattern matching (along with a helper function)
import Control.Applicative
binOp :: (Double -> Double -> Double) -> Expr -> Expr -> Env -> Maybe Double
binOp op x y vars = op <$> evalExpr x vars <*> evalExpr y vars
evalExpr :: Expr -> Env -> Maybe Double
evalExpr (Lit x) = const $ Just x
evalExpr (Var x) = M.lookup x
evalExpr (Add x y) = binOp (+) x y
evalExpr (Sub x y) = binOp (-) x y
evalExpr (Mul x y) = binOp (*) x y
evalExpr (Div x y) = binOp (/) x y
Now we can use evalExpr to evaluate an expression in our mini-language with variable substitution. All the error handling if there's an undefined variable is done by the Maybe monad, and we were even able to cut down on repetition by making the environment argument implicit. This is all pretty standard for a simple expression DSL.
So for the fun bit, generating random expressions and (eventually) mutations. For this, we'll need System.Random. We want to be able to generate expressions of varying complexity, so we'll express it in rough depth. Since it's random, there is a chance that we'll get shorter or deeper trees than specified. This will probably be something that you'll want to tweak and tune to get your desired results. First, because I have the foresight of having written this code already, let's define two helpers for generating a random literal and a random variable:
randomLit, randomVar :: IO Expr
randomLit = Lit <$> randomRIO (-100, 100)
randomVar = Var <$> randomRIO ('x', 'z')
Nothing exciting here, we get doubles between -100 and 100, and up to 3 variables. Now we can generate large expression trees.
generateExpr :: Int -> IO Expr
-- When the depth is 1, return a literal or a variable randomly
generateExpr 1 = do
isLit <- randomIO
if isLit
then randomLit
else randomVar
-- Otherwise, generate a tree using helper
generateExpr n = randomRIO (0, 100) >>= helper
where
helper :: Int -> IO Expr
helper prob
-- 20% chance that it's a literal
| prob < 20 = randomLit
-- 10% chance that it's a variable
| prob < 30 = randomVar
-- 15% chance of Add
| prob < 45 = (+) <$> generateExpr (n - 1) <*> generateExpr (n - 1)
-- 15% chance of Sub
| prob < 60 = (-) <$> generateExpr (n - 1) <*> generateExpr (n - 1)
-- 15% chance of Mul
| prob < 75 = (*) <$> generateExpr (n - 1) <*> generateExpr (n - 1)
-- 15% chance of Div
| prob < 90 = (/) <$> generateExpr (n - 1) <*> generateExpr (n - 1)
-- 10% chance that we generate a possibly taller tree
| otherwise = generateExpr (n + 1)
The bulk of this function is just specifying the probabilities that a given node will be generated, and then generating the left and right nodes for each operator. We even got to use the normal arithmetic operators since we overloaded Num, how handy!
Now, remember that we can still pattern match on the constructors of this Expr type for other operations, such as replacing nodes, swapping them, or measuring the depth. For this, you just have to treat it as any other binary tree type in Haskell, except it has 2 leaf constructors and 4 node constructors. As for mutations, you'll have to write code that traverses this structure and chooses when to swap out nodes and what to swap them out with. It'll live within the IO monad since you'll be generating random values, but it shouldn't be too difficult. This structure should be pretty easy to extend as need be, such as if you wanted to add trig functions and exponentiation, you'd just need more constructors, more expressions in evalExpr, and the appropriate clauses in helper, along with some probability adjustments.
You can get the full code for this example here. Hope this helps you see how to formulate something like S-expressions in Haskell.

Neighborhood of a mathematical expression using Haskell

I'm trying to implement with Haskell an algorithm to manipulate mathematical expressions.
I have this data type :
data Exp = Var String | IVal Int | Add Exp Exp
This will be enough for my question.
Given a set of expression transformations, for example :
(Add a b) => (Add b a)
(Add (Add a b) c) => (Add a (Add b c))
And an expression, for example : x = (Add (Add x y) (Add z t)), I want to find all expressions in the neighborhood of x. Given that neighborhood of x is defined as: y in Neighborhood(x) if y can be reached from x within a single transformation.
I am new to Haskell. I am not even sure Haskell is the right tool for this job.
The final goal is to get a function : equivalent x which returns a set of all expressions that are equivalent to x. In other words, the set of all expressions that are in the closure of the neighborhood of x (given a set of transformations).
Right now, I have the following :
import Data.List(nub)
import Data.Set
data Exp = IVal Int
| Scalar String
| Add Exp Exp
deriving (Show, Eq, Ord)
commu (Add a b) = (Add b a)
commu x = x
assoc (Add (Add a b) c) = (Add a (Add b c))
assoc (Add a (Add b c)) = (Add (Add a b) c)
assoc x = x
neighbors x = [commu x, assoc x]
equiv :: [Exp] -> [Exp]
equiv closure
| closure == closureUntilNow = closure
| otherwise = equiv closureUntilNow
where closureUntilNow = nub $ closure ++ concat [neighbors x|x<-closure]
But It's probably slower than needed (nub is O(n^2)) and some terms are missing.
For example, if you have f = (x+y)+z, then, you will not get (x+z)+y, and some others.
Imports, etc. below. I'll be using the multiset package.
import Control.Monad
import Data.MultiSet as M
data Exp = Var String | IVal Int | Add Exp Exp deriving (Eq, Ord, Show, Read)
A bit of paper-and-pencil work shows the following fact: expressions e1 and e2 are in the congruence closure of your relation iff the multiset of leaves are equal. By leaves, I mean the Var and IVal values, e.g. the output of the following function:
leaves :: Exp -> MultiSet Exp
leaves (Add a b) = leaves a `union` leaves b
leaves e = singleton e
So this suggests a nice clean way to generate all the elements in a particular value's neighborhood (without attempting to generate any duplicates in the first place). First, generate the multiset of leaves; then nondeterministically choose a partition of the multiset and recurse. The code to generate partitions might look like this:
partitions :: Ord k => MultiSet k -> [(MultiSet k, MultiSet k)]
partitions = go . toOccurList where
go [] = [(empty, empty)]
go ((k, n):bag) = do
n' <- [0..n]
(left, right) <- go bag
return (insertMany k n' left, insertMany k (n-n') right)
Actually, we only want partitions where both the left and right part are non-empty. But we'll check that after we've generated them all; it's cheap, as there's only two that aren't like that per invocation of partitions. So now we can generate the whole neighborhood in one fell swoop:
neighborhood :: Exp -> [Exp]
neighborhood = go . leaves where
full = guard . not . M.null
go m
| size m == 1 = toList m
| otherwise = do
(leftBag, rightBag) <- partitions m
full leftBag
full rightBag
left <- go leftBag
right <- go rightBag
return (Add left right)
By the way, the reason you're not getting all the terms is because you're generating the reflexive, transitive closure but not the congruence closure: you need to apply your rewrite rules deep in the term, not just at the top level.

How to handle expressions in Haskell?

Let's say I have :
f :: Double -> Double
f x = 3*x^2 + 5*x + 9
I would like to compute the derivative of this function and write
derivate f
so that
derivate f == \x -> 6*x + 5
but how to define derivate?
derivate :: (a -> a) -> (a -> a)
derivate f = f' -- how to compute f'?
I'm aware there is no native way to do this, but is there a library that can?
Do we have to rely on "meta"-datatypes to achieve this?
data Computation = Add Exp Expr | Mult Expr Expr | Power Expr Expr -- etc
Then, is it not a pain to make a corresponding constructor for each function ? However, datatypes should not represent functions (except for parsers).
Is Pure a good alternative because of its term-rewriting feature? Doesn't it have its drawbacks as well?
Are lists affordable?
f :: [Double]
f = [3, 5, 9]
derivate :: (a -> [a])
derivate f = (*) <$> f <*> (getNs f)
compute f x = sum $
((*) . (^) x) <$> (getNs f) <*> f
getNs f = (reverse (iterate (length f) [0..]))
Haskell now looks like it depends on LISP with a less appropriate syntax. Function and arguments waiting to be used together are quite stored in datatypes.
Plus, it's not very natural.
They don't seem to be "flexible" enough to be able my derivate function other than polynomials, such as homographic functions.
Right now, for example, I would like to use derivatives for a game. The character runs on a floor made using a function, and I would like him to slide if the floor is steep enough.
I also need to solve equations for various purposes. Some examples:
I'm a spaceship and I want to take a nap. During my sleep, if I don't place myself carefully, I might crash on a planet because of gravity. I don't have enough gas to go far away from celestial objects and I don't have a map either.
So I must place myself between the objects in this area so that the sum of their gravitationnal influence on me is canceled.
x and y are my coordinates. gravity is a function that takes two objects and return the vector of the gravitationnal force between them.
If there are two objects, say the Earth and the Moon, besides me, all I need to do to find where to go is to solve:
gravity earth spaceship + gravity moon spaceship == (0, 0)
It's much simpler and faster, etc., than to create a new function from scratch equigravityPoint :: Object -> Object -> Object -> Point.
If there are 3 objects besides me, it's still simple.
gravity earth spaceship + gravity moon spaceship + gravity sun spaceship == (0, 0)
Same for 4, and n. Handling a list of objects is much simpler this way than with equigravityPoint.
Other example.
I want to code an ennemy bot that shoots me.
If he just shoots targeting my current position, he will get me if I run towards me, but he'll miss me if I jump and fall on him.
A smarter bot thinks like that: "Well, he jumped from a wall. If I shoot targeting where he is now the bullet won't get him, because he will have moved until then. So I'm gonna anticipate where he'll be in a few seconds and shoot there so that the bullet and him reach this point at the same time".
Basically, I need the ability to compute trajectories. For example, for this case, I need the solution to trajectoryBullet == trajectoryCharacter, which gives a point where the line and the parabola meet.
A similar and simpler example not involving speed.
I'm a fireman bot and there's a building in fire. Another team of firemen is fighting the fire with their water guns. I am and there are people jumping from . While my friends are shooting water, I hold the trampoline.
I need to go where the people will fall before they do. So I need trajectories and equation-solving.
One way of doing this is to do automatic differentiation instead of symbolic differentiation; this is an approach where you simultaneously compute both f(x) and f′(x) in one computation. There's a really cool way of doing this using dual numbers that I learned about from Dan "sigfpe" Piponi's excellent blog post on automatic differentiation. You should probably just go read that, but here's the basic idea. Instead of working with the real numbers (or Double, our favorite (?) facsimile of them), you define a new set, which I'm going to call D, by adjoining a new element ε to ℝ such that ε2 = 0. This is much like the way we define the complex numbers ℂ by adjoining a new element i to ℝ such that i2 = -1. (If you like algebra, this is the same as saying D = ℝ[x]/⟨x2⟩.) Thus, every element of D is of the form a + bε, where a and b are real. Arithmetic over the dual numbers works like you expect:
(a + bε) ± (c + dε) = (a + c) ± (b + d)ε; and
(a + bε)(c + dε) = ac + bcε + adε + bdε2 = ac + (bc + ad)ε.
(Since ε2 = 0, division is more complicated, although the multiply-by-the-conjugate trick you use with the complex numbers still works; see Wikipedia's explanation for more.)
Now, why are these useful? Intuitively, the ε acts like an infinitesimal, allowing you to compute derivatives with it. Indeed, if we rewrite the rule for multiplication using different names, it becomes
(f + f′ε)(g + g′ε) = fg + (f′g + fg′)ε
And the coefficient of ε there looks a lot like the product rule for differentiating products of functions!
So, then, let's work out what happens for one large class of functions. Since we've ignored division above, suppose we have some function f : ℝ → ℝ defined by a power series (possibly finite, so any polynomial is OK, as are things like sin(x), cos(x), and ex). Then we can define a new function fD : D → D in the obvious way: instead of adding real numbers, we add dual numbers, etc., etc. Then I claim that fD(x + ε) = f(x) + f′(x)ε. First, we can show by induction that for any natural number i, it's the case that (x + ε)i = xi + ixi-1ε; this will establish our derivative result for the case where f(x) = xk. In the base case, this equality clearly holds when i = 0. Then supposing it holds for i, we have
(x + ε)i+1 = (x + ε)(x + ε)i by factoring out one copy of (x + ε)
= (x + ε)(xi + ixi-1ε) by the inductive hypothesis
= xi+1 + (xi + x(ixi-1))ε by the definition of dual-number multiplication
= xi+1 + (i+1)xiε by simple algebra.
And indeed, this is what we wanted. Now, considering our power series f, we know that
f(x) = a0 + a1x + a2x2 + … + aixi + …
Then we have
fD(x + ε) = a0 + a1(x + ε) + a2(x + ε)2 + … + ai(x + ε)i + …
= a0 + (a1x + a1ε) + (a2x2 + 2a2xε) + … + (aixi + iaixi-1ε) + … by the above lemma
= (a0 + a1x + a2x2 + … + aixi + …) + (a1ε + 2a2xε + … + iaixi-1ε + …) by commutativity
= (a0 + a1x + a2x2 + … + aixi + …) + (a1 + 2a2x + … + iaixi-1 + …)ε by factoring out the ε
= f(x) + f′(x)ε by definition.
Great! So dual numbers (at least for this case, but the result is generally true) can do differentiation for us. All we have to do is apply our original function to, not the real number x, but the dual number x + ε, and then extract the resulting coefficient of ε. And I bet you can see how one could implement this in Haskell:
data Dual a = !a :+? !a deriving (Eq, Read, Show)
infix 6 :+?
instance Num a => Num (Dual a) where
(a :+? b) + (c :+? d) = (a+c) :+? (b+d)
(a :+? b) - (c :+? d) = (a-c) :+? (b-d)
(a :+? b) * (c :+? d) = (a*c) :+? (b*c + a*d)
negate (a :+? b) = (-a) :+? (-b)
fromInteger n = fromInteger n :+? 0
-- abs and signum might actually exist, but I'm not sure what they are.
abs _ = error "No abs for dual numbers."
signum _ = error "No signum for dual numbers."
-- Instances for Fractional, Floating, etc., are all possible too.
differentiate :: Num a => (Dual a -> Dual a) -> (a -> a)
differentiate f x = case f (x :+? 1) of _ :+? f'x -> f'x
-- Your original f, but with a more general type signature. This polymorphism is
-- essential! Otherwise, we can't pass f to differentiate.
f :: Num a => a -> a
f x = 3*x^2 + 5*x + 9
f' :: Num a => a -> a
f' = differentiate f
And then, lo and behold:
*Main> f 42
5511
*Main> f' 42
257
Which, as Wolfram Alpha can confirm, is exactly the right answer.
More information about this stuff is definitely available. I'm not any kind of expert on this; I just think the idea is really cool, so I'm taking this chance to parrot what I've read and work out a simple proof or two. Dan Piponi has written more about dual numbers/automatic differentiation, including a post where, among other things, he shows a more general construction which allows for partial derivatives. Conal Elliott has a post where he shows how to compute derivative towers (f(x), f′(x), f″(x), …) in an analogous way. The Wikipedia article on automatic differentiation linked above goes into some more detail, including some other approaches. (This is apparently a form of "forward mode automatic differentiation", but "reverse mode" also exists, and can apparently be faster.)
Finally, there's a Haskell wiki page on automatic differentiation, which links to some articles—and, importantly, some Hackage packages! I've never used these, but it appears that the ad package, by Edward Kmett is the most complete, handling multiple different ways of doing automatic differentiation—and it turns out that he uploaded that package after writing a package to properly answer another Stack Overflow question.
I do want to add one other thing. You say "However, datatypes should not represent functions (except for parsers)." I'd have to disagree there—reifying your functions into data types is great for all sorts of things in this vein. (And what makes parsers special, anyway?) Any time you have a function you want to introspect, reifying it as a data type can be a great option. For instance, here's an encoding of symbolic differentiation, much like the encoding of automatic differentiation above:
data Symbolic a = Const a
| Var String
| Symbolic a :+: Symbolic a
| Symbolic a :-: Symbolic a
| Symbolic a :*: Symbolic a
deriving (Eq, Read, Show)
infixl 6 :+:
infixl 6 :-:
infixl 7 :*:
eval :: Num a => (String -> a) -> Symbolic a -> a
eval env = go
where go (Const a) = a
go (Var x) = env x
go (e :+: f) = go e + go f
go (e :-: f) = go e - go f
go (e :*: f) = go e * go f
instance Num a => Num (Symbolic a) where
(+) = (:+:)
(-) = (:-:)
(*) = (:*:)
negate = (0 -)
fromInteger = Const . fromInteger
-- Ignoring abs and signum again
abs = error "No abs for symbolic numbers."
signum = error "No signum for symbolic numbers."
-- Instances for Fractional, Floating, etc., are all possible too.
differentiate :: Num a => Symbolic a -> String -> Symbolic a
differentiate f x = go f
where go (Const a) = 0
go (Var y) | x == y = 1
| otherwise = 0
go (e :+: f) = go e + go f
go (e :-: f) = go e - go f
go (e :*: f) = go e * f + e * go f
f :: Num a => a -> a
f x = 3*x^2 + 5*x + 9
f' :: Num a => a -> a
f' x = eval (const x) $ differentiate (f $ Var "x") "x"
And once again:
*Main> f 42
5511
*Main> f' 42
257
The beauty of both of these solutions (or one piece of it, anyway) is that as long as your original f is polymorphic (of type Num a => a -> a or similar), you never have to modify f! The only place you need to put derivative-related code is in the definition of your new data type and in your differentiation function; you get the derivatives of your existing functions for free.
Numerical derivative can be done easily:
derive f x = (f (x + dx) - f (x - dx)) / (2 * dx) where dx = 0.00001
However, for symbolic derivatives, you need to create an AST, then implement the derivation rules through matching and rewriting the AST.
I don't understand your problem with using a custom data type
data Expr = Plus Expr Expr
| Times Expr Expr
| Negate Expr
| Exp Expr Expr
| Abs Expr
| Signum Expr
| FromInteger Integer
| Var
instance Num Expr where
fromInteger = FromInteger
(+) = Plus
(*) = Times
negate = Negate
abs = Abs
signum = Signum
toNumF :: Num a => Expr -> a -> a
toNumF e x = go e where
go Var = x
go (FromInteger i) = fromInteger i
go (Plus a b) = (go a) + (go b)
...
you can then use this just like you would Int or Double and all will just work! You can define a function
deriveExpr :: Expr -> Expr
which would then let you define the following (RankN) function
derivate :: Num b => (forall a. Num a => a -> a) -> b -> b
derivate f = toNumF $ deriveExpr (f Var)
you can extend this to work with other parts of the numerical hierarchy.

Resources