Hi,

continuing the above discussion "Parallel Haskell, 2 year project", here
is what i want to do:

- put an (almost) trivial program here that is a dynamic programming
  program but requires no other knowledge (like Bioinformatics or
  whatever). This one is attached.

- write the same program but using one array for each diagonal so that
  it could be parallelized; using the vector package.

- finally, lets see if something like that works in dph.

- hint: we are typically interested in both, a final result and the
  table(s) for backtracking!



+ other topic: publish Haskell libraries for RNA-folding so that there
is a benchmark against a C program, mainly for Roman and the 2-3 other
people out there using Haskell for bioinformatics ;-)

+ other topic: if I start benchmarking in earnest, should I use HEAD
because of the inliner bugs?

Gruss,
Christian


PS:
Dynamic Programming on a very high level, to see what kind of stuff I
would like to be able to do (in parallel ;-)
http://bibiserv.techfak.uni-bielefeld.de/adp/
-- | example Dynamic Programming (DP) program.

module Main where

import Data.Array.IArray
import System.Environment (getArgs)


run n = arr where
  arr :: Array (Int,Int) Int
  arr = array ((1,1),(n,n)) [ ((i,j),f (i,j)) | i <- [1..n], j <- [1..n]]
  f (i,j)
    | i >  j = n -- "undefined lower triangular part"
    | i == j = i -- initialize the main diagonal
    -- a calculation that does some work
    | otherwise = minimum $ n : [ arr ! (i+1,k) + arr ! (k+1,j-1) | k <- [i+1..j-2]]


main = do
  (a:_) <- getArgs
  let n = read a
  print $ run n ! (1,n)

Attachment: pgp8gxXWUCqBO.pgp
Description: PGP signature

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to