Rash thoughts about .NET, C#, F# and Dynamics NAV.


"Every solution will only lead to new problems."

Tuesday, 9. December 2008


Dynamics NAV Hilfe erstmals auf MSDN verfügbar

Filed under: Dynamics NAV 2009 — Steffen Forkmann at 11:12 Uhr

Die Dynamics NAV 2009 Entwickler-Hilfe ist ab heute auf MSDN verfügbar. Damit ist es in Kürze auch möglich über Suchmaschinen in der Hilfe zu suchen. Laut dem Microsoft Dynamics NAV Team Blog wird die Hilfe dort auch ständig aktualisiert, so dass NAV 2009-Entwickler und -Administratoren ab heute wohl die Onlinevariante bevorzugen sollten.

Unter anderem werden auch folgende Themen beschrieben:

Tags: ,

Monday, 8. December 2008


Project Euler in F# – Problem 53 – Memoization

Filed under: F#,Theoretische — Steffen Forkmann at 17:16 Uhr

Last time I showed how one can solve the Euler Project – problem 53 with the help of Dynamic Programming and a two-dimensional array. This time I will use another technique called (automatic) memoization.

First of all I need a memoization-function. There are two different approaches, one with a System.Collections.Generic.Dictionary and one with an immutable Map. You can read Don Syme’s blog posting to get more information about the differences.

let memoizeWithMap f =
  let cache = ref Map.empty
  fun x ->
    match (!cache).TryFind(x) with
      | Some res -> res
      | None ->
           let res = f x
           cache := (!cache).Add(x,res)
           res
open System.Collections.Generic

let memoizeWithDictionary f =
  let cache = Dictionary<_, _>()
  fun x ->
    let (found,result) = cache.TryGetValue(x)
    if found then
      result
    else
      let res = f x
      cache.[x] <- res
      res

With the help of one of this generic memoization-functions I can create a recursive function for the binomial coefficients, which memoizes intermediate data:

let rec binomial =
  let f (n,k) =
    if k = 0I || n = k then
      1I
    else
      binomial(n - 1I,k) + binomial(n - 1I,k - 1I)
  f |> memoizeWithDictionary

let answer =
      seq { for n in 2I .. 100I do
              for k in 2I .. n -> n,k }
       |> Seq.filter (fun (a,b) -> binomial (a,b) > 1000000I )
       |> Seq.length

answer |> printf "Answer: %A"

It turns out that memoizeWithDictionary is much faster for this problem. But with 160ms it is still slower than the comparable version with a two-dimensional array (45ms).

https://hrvatskafarmacija24.com
Tags: , , ,

Project Euler in F# – Problem 53 – Dynamic Programming

Filed under: English posts,F#,Theoretische — Steffen Forkmann at 12:23 Uhr

Claudio Cherubino (from fsharp.it/) posted his solution to Euler Project – problem 53. As I dealed a lot with Dynamic Programming in the recent time, I tried to solve the problem with a dynamic program in F#.

Project Euler – Problem 53:

How many values of C(n,k), for 1 ≤ n ≤ 100, exceed one-million?

Remark: C(n,k) are the binomial coefficients.

As it turned out, this is not that complicated if one knows the recursive function for the binomial coefficients (see Wikipedia):

Recursive definition for the Binomial coefficient with Recursive definition for the Binomial coefficient

This is easily transformed into a F# program:

let binomials = Array2.create 101 101 1I
let answer = ref 0
for n in [1..100] do
  for k in [1..n - 1] do
    binomials.[n, k] <- binomials.[n - 1,k] + binomials.[n - 1,k - 1]
    if binomials.[n, k] > 1000000I then
      answer := !answer + 1

!answer |> printf "Answer: %A"

Claudio’s program took 1315ms on my computer. The dynamic program needs only 63ms. But we can still do better if we use the symmetry of Pascal’s triangle.

Symmetry of Pascal's triangle

This leads to an algorithm, which calculates only half of the binomial coefficients.

let binomials = Array2.create 101 101 1I
let answer = ref 0
for n in [1..100] do
  for k in [1..n/2] do
    let b = binomials.[n - 1,k] + binomials.[n - 1,k - 1]
    binomials.[n, k] <- b
    binomials.[n, n - k] <- b
    if b > 1000000I then
      if k = n-k then
        answer := !answer + 1
      else
        answer := !answer + 2
!answer |> printf "Answer: %A"

This version needs only 45ms – but we are not ready. I mentioned Pascal’s triangle and its symmetry. But we can use another property. We don’t have to calculate the complete row, if we exceed 100000. All values behind this threshold have to be greater.

let binomials = Array2.create 101 101 1I
let answer = ref 0
for n in [1..100] do
  let threshold_reached = ref false
  let c = ref 0
  for k in [1..n/2] do
    if not !threshold_reached then
      let b = binomials.[n - 1,k] + binomials.[n - 1,k - 1]
      binomials.[n, k] <- b
      binomials.[n, n - k] <- b
      if b > 1000000I then
        threshold_reached := true
      else
        c := !c + 1

  if !threshold_reached then
    answer := !answer + (n - 1) - (2 * !c)
!answer |> printf "Answer: %A"

This final version took only 29 ms.

In the next posting I will show a version using memoization.

Tags: , , , ,

Sunday, 7. December 2008


SubsetSum in O(nS)

Filed under: English posts,F#,Informatik — Steffen Forkmann at 13:17 Uhr

The “Subset Sum”-problem is given as the following:

SUBSET SUM
Input: Numbers a1, a2, . . . , an, S ∈ N.
Question: Is there a subset I ⊆ {1,…,n} with ∑ ai = S?

Finding a solution for this decision problem is a very easy task in F#.

let hasSubsetSum_Naive (numbers: int list) S =
  let rec hasSubsetSum (a: int list) lastSum =
    match a with 
      | [] -> false
      | x::rest -> 
        if lastSum + x = S then
          true
        elif lastSum + x > S then
          false
        else
          hasSubsetSum rest lastSum || hasSubsetSum rest (lastSum+x)
  
  hasSubsetSum numbers 0

let numbers = [ 5;4;3;6;7;12 ]
let searchedSum = 33  
hasSubsetSum_Naive numbers searchedSum

Of course this small program can be easily adjusted to give the subset I back. Unfortunately this naïve approach leads to a running time of O(2^n).

But if S is small we can build a dynamic program and decide the problem in O(n*S) time.

 

This can be easily transformed into F# code.

let hasSubsetSum (numbers: int array) S =
   if numbers |> Array.exists (fun x -> x = S) then
     true
   else
     let a = numbers |> Array.filter (fun x -> x < S)      
     let n = a.Length
     if n = 0 then
       false
     else
       let v = Array2.create n (S+1) 0
       let u = Array2.create n (S+1) false
       let t = Array2.create n (S+1) 0
       
       for j in [1..S] do
         for i in [0..n-1] do                           
           if j - a.[i] >= 0 && not u.[i,j - a.[i]] then
             v.[i,j] <- t.[i,j - a.[i]] + a.[i]
           if ((i = 0) || (i > 0 && t.[i-1,j] <> j)) && v.[i,j] = j then
             u.[i,j] <- true
           if v.[i,j] = j then
             t.[i,j] <- j
           else
             if i > 0 then
               t.[i,j] <- max t.[i-1,j] t.[i,j-1]
             else
               t.[i,j] <- t.[0,j-1]
               
       t.[n-1,S] = S
https://kopapilleronline.com
Tags: , , ,

Friday, 5. December 2008


The distance of two cities on the surface of the earth in F#

Filed under: English posts,F#,Informatik — Steffen Forkmann at 12:19 Uhr

If we want to calculate the distance between two objects, we need some sort of distance function. I recently showed how we can compute the “edit distance” between two strings (see Damerau-Levenshtein-Distance in F# – part I, part II and part III). This time I will consider the distance between two points in the plane and on the surface of the earth.

First of all we need some sort of location type, which stores information about the coordinates (I used this type before). I will use the “Units of Measure”-feature in F# to distinct between <degree> vs. <radian> and <m> vs. <km>. If you are not familiar with this concept see Andrew Kennedy’s excellent blog series about Units of Measures in F#.

open Microsoft.FSharp.Math.SI
  
[<Measure>]
type degree

[<Measure>]
type radian =
  static member per_degree = Math.PI/180.0<degree/radian>
  
[<Measure>]
type km =  
  static member per_meter = 1000.<m/km>
type Location =
  {Latitude:float<degree>; 
   Longitude:float<degree> }
    
  member x.YPos = x.Longitude
  member x.XPos = x.Latitude        
  member x.Longitude_radian = x.Longitude * radian.per_degree  
  member x.Latitude_radian = x.Latitude * radian.per_degree   
  member x.Coordinates = (x.Longitude,x.Latitude)  
  
  static member CreateLocation(latitude, longitude) = 
    {new Location with
      Latitude = latitude and
      Longitude = longitude}

Now we can easily compute the Euclidean distance for two points in the plane.

let sq x = x * x
let CalcEuclideanDistance (s:Location) (t:Location) =

let d1 = (t.Longitude - s.Longitude) / 1.<degree> let d2 = (t.Latitude - s.Latitude) / 1.<degree> ((sq d1 + sq d2) |> Math.Sqrt) * 1.<m>

If we want to approximate the distance of two cities on the surface of earth, we can use the “Great circle distance“.

“The great-circle distance is the shortest distance between any two points on the surface of a sphere measured along a path on the surface of the sphere (as opposed to going through the sphere’s interior)” – Wikipedia

let kmFactor = 6372.795<km>
let sin_rad x = Math.Sin(x / 1.<radian>)
let cos_rad x = Math.Cos(x / 1.<radian>)

/// Great Circle Distance 
let CalcGreatCircleDistance (s:Location) (t:Location)=
  if s = t then
    0.<m>
  else
    let factor = kmFactor * km.per_meter
    let b =
         sin_rad s.Latitude_radian * sin_rad t.Latitude_radian +
         cos_rad s.Latitude_radian * cos_rad t.Latitude_radian *
           cos_rad (t.Longitude_radian - s.Longitude_radian) 
    Math.Acos(b) * factor
https://apotheekpillen.nl
Tags: , , ,

Tuesday, 2. December 2008


Calculate the intersection point of two lines in F# (2 dimensions)

Filed under: English posts,F#,Informatik — Steffen Forkmann at 11:58 Uhr

In one of my next postings I will show a algorithm, that calculates line segment intersections. As a prerequisite we need an algorithm, which calculates the intersection of two lines. In this post I will consider the following intersection of two lines in the euclidean plan:

Intersection of two lines

We can write this as an equation system with two variables and two equations:

  • Ax + r (Bx – Ax) = Cx + s (Dx – Cx)
  • Ay + r (By – Ay) = Cy + s (Dy – Cy)

After solving this system we can calculate the intersection:

  • Px = Ax + r (Bx – Ax)
  • Py = Ay + r (By – Ay)

Putting this all together we can derive the following F#-code:

let calcIntersection (A:Location, B:Location, C:Location, D:Location) =
  let (Ax,Ay,Bx,By,Cx,Cy,Dx,Dy) =
     (A.XPos, A.YPos, B.XPos, B.YPos, C.XPos, C.YPos, D.XPos, D.YPos)
  let d = (Bx-Ax)*(Dy-Cy)-(By-Ay)*(Dx-Cx)  

  if  d = 0 then
    // parallel lines ==> no intersection in euclidean plane
    None
  else
let q = (Ay-Cy)*(Dx-Cx)-(Ax-Cx)*(Dy-Cy) let r = q / d let p = (Ay-Cy)*(Bx-Ax)-(Ax-Cx)*(By-Ay) let s = p / d if r < 0. or r > 1. or s < 0. or s > 1. then None // intersection is not within the line segments else Some( (Ax+r*(Bx-Ax)), // Px (Ay+r*(By-Ay))) // Py


Remarks:

  1. If one given line degenerates into a point, then the algorithm gives no intersection.
  2. If the given lines are parallel, then the algorithm gives no intersection, even if the lines have an overlap.
Tags: , , ,