Click here to Skip to main content
15,880,503 members
Articles / Programming Languages / F#

Symbolic Calculation in F#

Rate me:
Please Sign up or sign in to vote.
4.96/5 (24 votes)
11 Jun 2010CPOL7 min read 47.3K   30   13
The article describes how to perform symbolic math calculations using F#

Introduction

One of the best areas to use a functional language is to apply it to symbolic calculations. Like transforming algebraic expressions or evaluating function derivatives. I remember how I was impressed many years ago when I looked at a program in Prolog that occupied not more than one computer screen but could tell me that derivative of sin(x) was cos(x). So I wanted to do the same in F#.

If you ask a developer who is only using procedural languages to write a program that calculates derivatives in a symbolic form, chances are pretty good that he will start with parsing input strings. That’s the nature of procedural languages: you solve a task by building a sequence of steps that it takes to convert input to output. A developer focusing on a higher level abstraction might start with building classes for expression trees, so he can implement derivative calculation on the top of them. But what derivative calculation has with creating classes to store tree nodes? Why should we care?

In procedural languages, we need to care as Niklaus Wirth stated in his book title, "Algorithms + Data Structures = Programs". So we express our imperative programs in algorithms and apply them to data structures.

With F#, it’s completely different. You simply describe your domain, your rules. And things just happen.

This article describes how to apply F# to the following tasks:

  • Symbolic calculations of derivatives
  • Simplifying algebraic expressions
  • Formatting algebraic expression
  • Parsing algebraic expressions

All these tasks can be chained for the benefit of a composite operation: evaluation of derivatives in a symbolic form right with input and output being just plain text, as we prefer it to see. So if we run our program on input “sin(x ^ 2)”, we will get output “2 * x * cos(x ^ 2)”.

1. Calculating Derivatives

First we need to define the scope of our calculations, our symbols. Note that Expression type doesn’t define a data structure – it’s just a collection of symbols that we will be using to form functional expressions.

F#
type Expression =
    | X
    | Const of float
    | Neg of Expression
    | Add of Expression * Expression
    | Sub of Expression * Expression
    | Mul of Expression * Expression
    | Div of Expression * Expression
    | Pow of Expression * Expression
    | Exp of Expression
    | Log of Expression
    | Sin of Expression
    | Cos of Expression

What we just declared is called in F# discriminated union. I won’t be spending time on F# syntax details, I am learning F# from two great books: "Programming F#" and "Real World Functional Programming". (I started with the second one but had to switch to the first one that in my opinion provides a better transition to a functional programming and F# style).

As you can see, we made some restrictions to expression syntax: we assume that numeric constants are of type float, and we only support four functions: exponent, natural logarithm, sine and cosine. But this should be sufficient for a purpose of language demo. In addition, there is only one variable symbol (X).

Before we proceed with derivative definition, there are a couple of helper constructions I’d like to define. We may need to have a common match for binary operators (Add, Sub, Mul, Div) and supported functions (Exp, Log, Sin, Cos). So we’ll define so called active patterns that can be used to match such constructs:

F#
let (|Op|_|) (x : Expression) =
    match x with
    | Add(e1, e2) -> Some(Add, e1, e2)
    | Sub(e1, e2) -> Some(Sub, e1, e2)
    | Mul(e1, e2) -> Some(Mul, e1, e2)
    | Div(e1, e2) -> Some(Div, e1, e2)
    | Pow(e1, e2) -> Some(Pow, e1, e2)
    | _ -> None

let (|Func|_|) (x : Expression) =
    match x with
    | Exp(e) -> Some(Exp, e)
    | Log(e) -> Some(Log, e)
    | Sin(e) -> Some(Sin, e)
    | Cos(e) -> Some(Cos, e)
    | _ -> None

Again, I am afraid I can’t use this post to define the meaning of active patterns, banana clips (“(|” and “|)”), and options syntax (“Some” and “None”), there is a lot of information online, but you can think about the definitions above as something similar to regular expression matching: an expression “Add(e1, e2)” will be matched as “Op” (Add, e1, e2), and an expression “Exp(e)” is matched as “Func (Exp, e)”. We will see in a moment how this can become useful.

Now what’s left is just a definition of a derivative. Here it is:

F#
let rec Derivative x : Expression =
    match x with
    | X -> Const(1.)
    | Const(n) -> Const(0.)
    | Neg(e) -> Neg(Derivative(e))
    | Add(e1, e2) -> Add(Derivative(e1), Derivative(e2))
    | Sub(e1, e2) -> Sub(Derivative(e1), Derivative(e2))
    | Mul(e1, e2) -> Add(Mul(Derivative(e1), e2), Mul(e1, Derivative(e2)))
    | Pow(e, Const(n)) -> Mul(Const(n), Pow(e, Const(n-1.)))
    | Pow(Const(n), e) -> Mul(Mul(Log(Const(n)), Pow(Const(n), e)), Derivative(e))
    | Exp(X) -> Exp(X)
    | Log(X) -> Div(Const(1.), X)
    | Sin(X) -> Cos(X)
    | Cos(X) -> Neg(Sin(X))
    | Div(Const(1.), e) -> Div(Derivative(e), Pow(e, Const(2.)))
    | Func(g, f) ->
        let dg = Derivative(g(X))
        let df = Derivative(f)
        match dg with
        | Func(dgf, dge) -> Mul(dgf(f), df)
        | Op (op, e1, e2) -> Mul(op(e1, e2), df)
        | _ -> failwith(sprintf "Unable to match compound function [%A]" dg)
    | _ -> failwith(sprintf "Unable to match expression [%A]" x)

As you can see, it’s not an algorithm – it’s a description of what  derivative is. You can also why we needed to introduce “Op” and “Func” active patterns: they are used in declaration of complex function derivative evaluation. Without these patterns, we would need to list all supported operators and functions.

To test how this works, we can open a F# interactive window (FSI) and type a function to test:

> let d = Derivative(Sin(X));;
val d : Expression = Cos X
> let d = Derivative(Exp(Pow(X,Const(2.))));;
val d : Expression = Mul (Exp (Pow (X,Const 2.0)),Mul (Const 2.0,X))

That’s it! But while we are on symbolic calculations, we can improve the presentation part of it. Right now, if there is no attempt to simplify resulting expressions, so if we calculate a derivative of an expression corresponding to “5 * x + 3”, we will get a correct but silly looking answer:

> let d = Derivative(Add(Mul(Const(5.), X), Const(3.)));;
 val d : Expression = Add (Add (Mul (Const 0.0,X),Mul (Const 5.0,Const 1.0)),Const 0.0)

But if it was so simple to calculate derivatives in F#, it should not be difficult to write a function to simplify algebraic expressions. That will be in the next section.

2. Simplifying Algebraic Expressions 

So now we want to improve the aesthetics of expressions, in other words, present them in a simplest possible form. To achieve this goal, we define a recursive function Simplify that converts an input of Expression type to an output of the same type attempting to rewrite an expression in a shorter form. Like with Derivative function, the definition is a list of rules rather than a sequential algorithm:

F#
let rec Simplify x : Expression =
    match x with
    | Add(Const(n1), Const(n2)) -> Const(n1 + n2)
    | Sub(Const(n1), Const(n2)) -> Const(n1 - n2)
    | Mul(Const(n1), Const(n2)) -> Const(n1 * n2)
    | Div(Const(n1), Const(n2)) -> Const(n1 / n2)
    | Neg(Const(0.)) -> Const(0.)
    | Neg(Neg(e)) -> e |> Simplify
    | Add(e, Const(0.)) -> e |> Simplify
    | Add(Const(0.), e) -> e |> Simplify
    | Add(Const(n), e) -> Add(e, Const(n)) |> Simplify
    | Add(e1, Neg(e2)) -> Sub(e1, e2) |> Simplify
    | Add(Neg(e1), e2) -> Sub(e2, e1) |> Simplify
    | Sub(e, Const(0.)) -> e |> Simplify
    | Sub(Const(0.), e) -> Neg(e) |> Simplify
    | Mul(e, Const(1.)) -> e |> Simplify
    | Mul(Const(1.), e) -> e |> Simplify
    | Mul(e, Const(0.)) -> Const(0.)
    | Mul(Const(0.), e) -> Const(0.)
    | Mul(e, Const(n)) -> Mul(Const(n), e) |> Simplify
    | Mul(Div(Const(n), e1), e2) -> Mul(Const(n), Div(e2, e1)) |> Simplify
    | Mul(e1, Div(Const(n), e2)) -> Mul(Const(n), Div(e1, e2)) |> Simplify
    | Mul(Neg(e1), e2) -> Neg(Mul(e1, e2)) |> Simplify
    | Mul(e1, Neg(e2)) -> Neg(Mul(e1, e2)) |> Simplify
    | Div(Const(0.), e) -> Const(0.)
    | Div(e, Const(1.)) -> e |> Simplify
    | Div(Neg(e1), e2) -> Neg(Div(e1, e2)) |> Simplify
    | Div(e1, Neg(e2)) -> Neg(Div(e1, e2)) |> Simplify
    | Pow(Const(0.), e) -> Const(0.)
    | Pow(Const(1.), e) -> Const(1.)
    | Pow(e, Const(0.)) -> Const(1.)
    | Pow(e, Const(1.)) -> e |> Simplify
    | Op (op, e1, e2)
        ->
        let e1s = Simplify e1
        let e2s = Simplify e2
        if e1s <> e1 || e2s <> e2 then
            op(Simplify e1, Simplify e2) |> Simplify
        else
            op(e1, e2)
    | _ -> x

The set of rules is not complete. For example, there is no rule to rewrite “2 * (3 + X)” as “6 + 2*X”, but it should be enough to eliminate most obvious redundancies, such as multiplication by one and zero addition. So if we can fire F# interactive window, we can test how it works:

> let s = Simplify(Add(Mul(Const 0., X), Mul(Const 5., Const 1.)));;
val s : Expression = Const 5.0

What we can do now is extend the Derivative function written in the previous post, so it can take advantage of our new Simplify function:

F#
let rec Derivative x : Expression =
   let y =
       match x with
       | X -> Const(1.)
       | Const(n) -> Const(0.)
       | Neg(e) -> Neg(Derivative(e))
       | Add(e1, e2) -> Add(Derivative(e1), Derivative(e2))
       | Sub(e1, e2) -> Sub(Derivative(e1), Derivative(e2))
       | Mul(e1, e2) -> Add(Mul(Derivative(e1), e2), Mul(e1, Derivative(e2)))
       | Pow(e, Const(n)) -> Mul(Const(n), Pow(e, Const(n-1.)))
       | Pow(Const(n), e) -> Mul(Mul(Log(Const(n)), Pow(Const(n), e)), Derivative(e))
       | Exp(X) -> Exp(X)
       | Log(X) -> Div(Const(1.), X)
       | Sin(X) -> Cos(X)
       | Cos(X) -> Neg(Sin(X))
       | Div(Const(1.), e) -> Div(Derivative(e), Pow(e, Const(2.)))
       | Func(g, f) ->
           let dg = Derivative(g(X))
           let df = Derivative(f)
           match dg with
           | Func(dgf, dge) -> Mul(dgf(f), df)
           | Op (op, e1, e2) -> Mul(op(e1, e2), df)
           | _ -> failwith(sprintf "Unable to match compound function [%A]" dg)
       | _ -> failwith(sprintf "Unable to match expression [%A]" x)
   Simplify y

Now let's test what we have by calculating the derivative for various functions:

> let d1 = Derivative(Add(Mul(Const(5.), X), Const(3.)))
	let d2 = Derivative(Add(Pow(X, Const(3.)), Const(3.)))
	let d3 = Derivative(Sin(Mul(Const(2.), X)))
	let d4 = Derivative(Log(Mul(Const(2.), X)))
	let d5 = Derivative(Exp(Mul(Const(2.), X)))
	let d6 = Derivative(Exp(Pow(X, Const(2.))))
	let d7 = Derivative(Log(Sin(X)))
	let d8 = Derivative(Log(Cos(X)));;

>
	val d1 : Expression = Const 5.0
	val d2 : Expression = Mul (Const 3.0,Pow (X,Const 2.0))
	val d3 : Expression = Mul (Const 2.0,Cos (Mul (Const 2.0,X)))
	val d4 : Expression = Div (Const 2.0,X)
	val d5 : Expression = Mul (Const 2.0,Exp (Mul (Const 2.0,X)))
	val d6 : Expression = Mul (Exp (Pow (X,Const 2.0)),Mul (Const 2.0,X))
	val d7 : Expression = Div (Cos X,X)
	val d8 : Expression = Neg (Div (Sin X,X))

Can we improve anything? Well, maybe… Since it’s getting so easy, why not set an ultimate goal: present input and output as a plain text, not as Expression items. So we can pass “log(cos(x))” and get back “-sin(x)/x”. I guess this will be slightly more work to achieve, but should be fun once we get there. In the next section.

3. Formatting Expressions  

First we define a couple of helper functions to format operators and function names:

F#
 let OpName (e: Expression) : string =
    match e with
    | Add(e1, e2) -> "+"
    | Sub(e1, e2) -> "-"
    | Mul(e1, e2) -> "*"
    | Div(e1, e2) -> "/"
    | Pow(e1, e2) -> "^"
    | _ -> failwith(sprintf "Unrecognized operator [%A]" e)

let FuncName (e: Expression) (a : string) : string =
    match e with
    | Exp(x) -> sprintf "e^(%s)" a
    | Log(x) -> sprintf "log(%s)" a
    | Sin(x) -> sprintf "sin(%s)" a
    | Cos(x) -> sprintf "cos(%s)" a
    | _ -> failwith(sprintf "Unrecognized function [%A]" e)

Then the rough implementation of the expression formatter does not take many lines of code:

F#
let rec FormatExpression (inner : Expression) : string =
    match inner with
    | X -> "x";
    | Const(n) -> sprintf "%f" n
    | Neg x -> sprintf "-%s" (FormatExpression(x))
    | Op(op, e1, e2) -> "(" + FormatExpression(e1) + " " +
	OpName(inner) + " " + FormatExpression(e2) + ")"
    | Func(f, e) -> FuncName(inner) (FormatExpression(e))

There is only one problem with this code: it always surrounds algebraic operations with parenthesis, and this is only necessary in case the expression is contained in an outer expression. This is an example of redundant parenthesis:

FormatExpression(Mul(Mul(Const(2.), X), Const(3.)))
>
val it : string = "((2.000000 * x) * 3.000000)"

It’s not complicated however to modify the original code, so it does not embrace top-level expressions with parenthesis:

F#
let FormatExpression x =
    let rec FormatSubExpression (outer : Expression option,
		inner : Expression) : string =
        match inner with
        | X -> "x"
        | Const(n) -> sprintf "%f" n
        | Neg x -> sprintf "-%s" (FormatSubExpression(Some(inner), x))
        | Op(op, e1, e2) ->
            let s = FormatSubExpression(Some(inner), e1) + " " +
		OpName(inner) + " " + FormatSubExpression(Some(inner), e2)
            match outer with
            | None -> s
            | _ -> "(" + s + ")"
        | Func(f, e) -> FuncName(inner) (FormatSubExpression(None, e))
    FormatSubExpression(None, x)

Now we’re getting nice-looking output:

let t1 = FormatExpression(Mul(Const(2.), X))
let t2 = FormatExpression(Mul(Const(3.), Mul(Const(2.), X)))
let t3 = FormatExpression(Mul(Mul(Const(2.), X), Const(3.)))
let t4 = FormatExpression(Mul(Add(X, Const(2.)), Const(3.)))
let t5 = FormatExpression(Neg(Mul(Const(2.), X)))
let t6 = FormatExpression(Sin(X))
>
val t1 : string = "2.000000 * x"
val t2 : string = "3.000000 * (2.000000 * x)"
val t3 : string = "(2.000000 * x) * 3.000000"
val t4 : string = "(x + 2.000000) * 3.000000"
val t5 : string = "-(2.000000 * x)"
val t6 : string = "sin(x)"

4. Parsing Expressions  

Satisfied with expression formatting, we can now proceed with expression parsing which appeared to be a more challenging tasks. First we need a tokenizer that would convert an input string into a list of tokens – atoms that will be building blocks of the resulting expression. Here is a simple tokenizer:

F#
let Tokenize (value : System.String) =
    let value = value.Replace(" ", "")
    let value = value.Replace("e^(", "e(")
    let value = value.Replace("(", " ( ")
    let value = value.Replace(")", " ) ")
    let value = value.Replace("+", " + ")
    let value = value.Replace("-", " - ")
    let value = value.Replace("*", " * ")
    let value = value.Replace("/", " / ")
    let value = value.Replace("^", " ^ ")
    value.Trim().Split([|' '|]) |> Seq.toList |> List.filter (fun e -> e.Length > 0)
> Tokenize "(x * 4) * sin(x) * (30 + 40)"
>
val it : string list = ["(";"x"; "*"; "4"; ")"; "*";
	"sin"; "("; "x"; ")"; "*"; "("; "30"; "+"; "40"; ")"]

The tokenizer includes one rule that is specific for processing exponential functions (e ^ x). Unlike other functions (log, sin, cos), the exponent uses power operator notation, so adding proper support for it would devote a large part of the post series just to this specific case. So I made a light constraint on use of exponent: its argument is always enclosed in parenthesis (so the input string should look like "e ^ (x)", not "e ^ x", and during the tokenization process the expression is converted into notation similar to other functions: e(x). So when proceeding with expression parsing, we won’t need to handle exponential functions in a special way.

The next step is to eleminate parenthesis and divide tokens into groups, each group representing a trivial expression construct. For example, an expression "(2 + x) * (5 - x)" can be split into groups containing expressions "2 + x", "5 – x" and the operator "*" binding them together. We achive this in a few steps: first by assigning each token a level (incremented with each opening parentheses and decremeneted with a closing parentheses), and then by putting contiguous tokens with the same level in a list. Here is the code that handles these operations and an example of its use:

F#
let rec LevelTokens (lst : string list) (level : int) : (string * int) list =
    match lst with
    | [] -> []
    | "(" :: tail -> LevelTokens tail (level+1)
    | ")" :: tail -> LevelTokens tail (level-1)
    | x :: tail when IsOperator(x) -> (x, level) :: LevelTokens tail level
    | head :: tail -> (head, level) :: LevelTokens tail level

let GroupTokens (item : (string * int))
	(acc : (string list * int) list) : (string list * int) list =
    match acc, item with
    | [], (s, l) -> [([s], l)]
    | (s1, l1) :: tail, (s, l) when l = l1 -> (s :: s1, l) :: tail
    | head :: tail, (s, l) -> ([s], l) :: head :: tail
let lst = "(x * 4) * sin(x) * (30 + 40)"
(Tokenize lst |> LevelTokens)  0
let items = List.foldBack GroupTokens
	((Tokenize lst |> LevelTokens) 0) [] |> List.map(fun (x, y) -> x)
>

val lst : string = "(x * 4) * sin(x) * (30 + 40)"
val items : string list list =  [["x"; "*"; "4"]; ["*"; "sin"];
	["x"]; ["*"]; ["30"; "+"; "40"]]

We will also need some auxilliary functions: to test if a string represents an operator or a function, a couple of active pattern definitions to match numeric constants and variables, and methods to apply parsed operators or functions to expressions that they bind:

F#
 let IsOperator (x : string) =
    match x with
    | "+" | "-" | "*" | "/" | "^" -> true
    | _ -> false

let IsFunction (x : string) =
    match x with
    | "e" | "log" | "sin" | "cos" -> true
    | _ -> false

let (|ToVar|_|) s =
    if s = "x" then
        Some(X)
    else
        None

let ApplyOperator (op : string, e1 : Expression, e2 : Expression) : Expression =
    match op with
    | "+" -> Add(e1, e2)
    | "-" -> Sub(e1, e2)
    | "*" -> Mul(e1, e2)
    | "/" -> Div(e1, e2)
    | "^" -> Pow(e1, e2)
    | _ -> failwith(sprintf "Unrecognized operator [%s]" op)

let ApplyFunction (func : string, e : Expression) : Expression =
    match func with
    | "e" -> Exp(e)
    | "log" -> Log(e)
    | "sin" -> Sin(e)
    | "cos" -> Cos(e)
    | _ -> failwith(sprintf "Unrecognized function [%s]" func)

let (|ToConst|_|) s =
    let success, result = Double.TryParse(s)
    if success then
        Some(Const(result))
    else
        None

let ParseItem (s : string) : Expression =
    match s with
    | ToVar e -> e
    | ToConst e -> e

With supporting stuff in place, here’s the code that converts text input into expression trees:

F#
let rec ParseExpression (s : string) : Expression =

    let rec LevelTokens (lst : string list) (level : int) : (string * int) list =
        match lst with
        | [] -> []
        | "(" :: tail -> LevelTokens tail (level+1)
        | ")" :: tail -> LevelTokens tail (level-1)
        | x :: tail when IsOperator(x) -> (x, level) :: LevelTokens tail level
        | head :: tail -> (head, level) :: LevelTokens tail level

    let GroupTokens (item : (string * int))
	(acc : (string list * int) list) : (string list * int) list =
        match acc, item with
        | [], (s, l) -> [([s], l)]
        | (s1, l1) :: tail, (s, l) when l = l1 -> (s :: s1, l) :: tail
        | head :: tail, (s, l) -> ([s], l) :: head :: tail

    let rec MergeTokensWithExpressions
	(e : Expression, items : (string list) list) : Expression =
        match items with
        | [] -> e
        | [[func]] when IsFunction(func) -> ApplyFunction(func, e)
        | [op; x] :: tail when IsOperator(op) ->
	MergeTokensWithExpressions(ApplyOperator(op, e, ParseItem(x)), tail)
        | [x; op] :: tail when IsOperator(op) ->
	MergeTokensWithExpressions(ApplyOperator(op, ParseItem(x), e), tail)
        | (op::x::rest) :: tail when IsOperator(op) ->
	MergeTokensWithExpressions(ApplyOperator(op, e,
	ParseFlatExpression(x::rest)), tail)
        | (x::op::y::rest) :: tail when IsOperator(op) ->
	ApplyOperator(op, ParseItem(x), MergeTokensWithExpressions(e, (y::rest)::tail))
        | _ -> failwith(sprintf "Unable to build expression from [%A]" items)

    let rec MergeExpressions (e : Expression, items : string list) : Expression =
        match items with
        | [] -> e
        | op :: x :: tail when IsOperator(op) ->
	MergeExpressions(ApplyOperator(op, e, ParseItem(x)), tail)
        | x :: op :: tail when IsOperator(op) ->
	MergeExpressions(ApplyOperator(op, ParseItem(x), e), tail)
        | _ -> failwith(sprintf "Unable to build expression from [%A]" items)

    let ParseFlatExpression (tokens : string list) : Expression =
        match tokens with
        | [] -> failwith("Expression string is empty")
        | "-" :: x :: tail -> MergeExpressions(Neg(ParseItem(x)), tail)
        | x :: tail -> MergeExpressions(ParseItem(x), tail)

    let rec ParseTokenGroups (lst : (string list) list) : Expression =
        match lst with
        | [ls] -> ParseFlatExpression(ls)
        | ls :: [op] :: tail when IsOperator(op) ->
	ApplyOperator(op, ParseFlatExpression(ls), ParseTokenGroups(tail))
        | ls :: [op :: optail] when IsOperator(op) ->
	MergeTokensWithExpressions(ParseFlatExpression(ls), [op :: optail])
        | ls :: (op :: optail) :: tail when IsOperator(op) ->
	ApplyOperator(op, ParseFlatExpression(ls),
	MergeTokensWithExpressions(ParseTokenGroups(tail), [optail]))
        | ls :: tail -> MergeTokensWithExpressions(ParseTokenGroups(tail), [ls])

    let leveledTokens = (Tokenize s |> LevelTokens) 0
    let tokenGroups =
	List.foldBack GroupTokens leveledTokens [] |> List.map(fun (x, y) -> x)

    ParseTokenGroups(tokenGroups)

Now it’s just to test how this all works:

let f1 = ParseExpression "5*x + 3" |> Derivative |> FormatExpression
let f2 = ParseExpression "x^3 +3" |> Derivative |> FormatExpression
let f3 = ParseExpression "sin(2*x)" |> Derivative |> FormatExpression
let f4 = ParseExpression "log(2*x)" |> Derivative |> FormatExpression
let f5 = ParseExpression "e ^(2*x)" |> Derivative |> FormatExpression
let f6 = ParseExpression "e ^(x^2)" |> Derivative |> FormatExpression
let f7 = ParseExpression "log(sin(x))" |> Derivative |> FormatExpression
let f8 = ParseExpression "log(cos(x))" |> Derivative |> FormatExpression
let f9 = ParseExpression "1 / x"  |> Derivative |> FormatExpression
let f10 = ParseExpression "2 ^ x"  |> Derivative |> FormatExpression

>
val f1 : string = "5.000000"
val f2 : string = "3.000000 * (x ^ 2.000000)"
val f3 : string = "2.000000 * cos(2.000000 * x)"
val f4 : string = "2.000000 / x"
val f5 : string = "2.000000 * e^(2.000000 * x)"
val f6 : string = "e^(x ^ 2.000000) * (2.000000 * x)"
val f7 : string = "cos(x) / x"
val f8 : string = "-(sin(x) / x)"
val f9 : string = "1.000000 / (x ^ 2.000000)"
val f10 : string = "log(2.000000) * (2.000000 ^ x)"

So we’re done: we can now enter math expressions in plain text and obtain results of symbolic derivative calculation also in plain text. All in F#!

References

  1. Chris Smith - Programming F#
  2. Tomas Petricek, Jon Skeet - Real World Functional Programming: With Examples in F# and C#

History

  • 11th June, 2010: Initial post

License

This article, along with any associated source code and files, is licensed under The Code Project Open License (CPOL)


Written By
Architect Miles AS
Norway Norway
Vagif Abilov is a Russian/Norwegian software developer and architect working for Miles. He has more than twenty years of programming experience that includes various programming languages, currently using mostly C# and F#.

Vagif writes articles and speaks at user group sessions and conferences. He is a contributor and maintainer of several open source projects, including Simple.Data OData adapter, Simple.OData.Client and MongOData.

Comments and Discussions

 
BugBug - Derivitive of 1/x Pin
MrDesperados17-Jan-19 10:17
MrDesperados17-Jan-19 10:17 
QuestionPrecedence Pin
Member 1168291025-May-16 7:36
Member 1168291025-May-16 7:36 
AnswerRe: Precedence Pin
Orilion31-May-16 3:43
Orilion31-May-16 3:43 
GeneralMy vote of 5 Pin
debiprasadghosh11-Dec-10 18:24
debiprasadghosh11-Dec-10 18:24 
GeneralWhere is the code Pin
Pascal Ganaye20-Jun-10 22:46
Pascal Ganaye20-Jun-10 22:46 
GeneralRe: Where is the code Pin
Vagif Abilov21-Jun-10 11:48
professionalVagif Abilov21-Jun-10 11:48 
Generalgreat! Pin
Julian Ott20-Jun-10 16:56
Julian Ott20-Jun-10 16:56 
GeneralBug Pin
fatho120-Jun-10 7:33
fatho120-Jun-10 7:33 
GeneralRe: Bug Pin
Vagif Abilov21-Jun-10 11:47
professionalVagif Abilov21-Jun-10 11:47 
GeneralReally impressing Pin
fatho119-Jun-10 23:59
fatho119-Jun-10 23:59 
GeneralRe: Really impressing Pin
Vagif Abilov21-Jun-10 11:48
professionalVagif Abilov21-Jun-10 11:48 
GeneralJust.... Pin
David Grenier12-Jun-10 1:45
David Grenier12-Jun-10 1:45 
GeneralRe: Just.... Pin
Vagif Abilov21-Jun-10 11:49
professionalVagif Abilov21-Jun-10 11:49 

General General    News News    Suggestion Suggestion    Question Question    Bug Bug    Answer Answer    Joke Joke    Praise Praise    Rant Rant    Admin Admin   

Use Ctrl+Left/Right to switch messages, Ctrl+Up/Down to switch threads, Ctrl+Shift+Left/Right to switch pages.