view test/ParRead.hs @ 20:97d1e67aef15

add STM in Jungle map
author Daichi TOMA <toma@cr.ie.u-ryukyu.ac.jp>
date Fri, 24 Jan 2014 06:06:30 +0900
parents a30ec665df9d
children 451bf8dcdc9c
line wrap: on
line source

{-# LANGUAGE OverloadedStrings #-}

import Control.Parallel
import Control.Parallel.Strategies
import Text.Printf
import Jungle
import Data.Maybe
import Data.List
import Data.Time.Clock
import qualified Data.ByteString.Lazy.Char8 as B
import Control.Exception
import System.Environment


main = do
  jungle <- createJungle
  createTree jungle "test_tree"
  node <- getRootNode jungle "test_tree"
  let
    x = testTree node 8
  putStrLn $ show $ size x
  updateRootNode jungle "test_tree" x
  node2 <- getRootNode jungle "test_tree"
  t0 <- getCurrentTime
  printTimeSince t0
  r <- evaluate (runEval $ test node2)
  print r
  printTimeSince t0


test node = do
    a <- rpar (func node)
    b <- rpar (func node)
    c <- rpar (func node)
    d <- rpar (func node)
    e <- rpar (func node)
    f <- rpar (func node)
    g <- rpar (func node)
    h <- rpar (func node)
    i <- rpar (func node)
    j <- rpar (func node)
    k <- rpar (func node)
    l <- rpar (func node)
    return (a,b,c,d,e,f,g,h,i,j,k,l)

func :: Node -> Int
func node = size node


-- ある程度の大きさの木を作れる
-- size $ testTree y 2 = 10
-- size $ testTree y 6 = 11742
-- size $ testTree y 8 = 876808
testTree node h = foldl' (add (h-1)) node (concatMap permutations . subsequences $ [1..h])
  where
    add x node h = addc x node h

-- x回addNewChildAtする
addc 0 node h = addNewChildAt node h
addc x node h = addNewChildAt (addc (x-1) node h) h
  
printTimeSince t0 = do
  t1 <- getCurrentTime
  printf "time: %.2fs\n" (realToFrac (diffUTCTime t1 t0) :: Double)