view test/ParRead.hs @ 9:947c5cfa4149

Change function related to Tree, Tree is not visiable from outside.
author Daichi TOMA <toma@cr.ie.u-ryukyu.ac.jp>
date Tue, 21 Jan 2014 13:17:02 +0900
parents f03876c8236a
children a30ec665df9d
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
  let
    jungle = createJungle
  new_jungle <- createTree jungle "test_tree"
  node <- getRootNode new_jungle "test_tree"
  let
    x = testTree node 7
  putStrLn $ show $ size x
  updateRootNode new_jungle "test_tree" x
  node2 <- getRootNode new_jungle "test_tree"
  t0 <- getCurrentTime
  printTimeSince t0
  r <- evaluate (runEval $ test node2)
  print r
  printTimeSince t0


test node = do
    x <- rpar (func node)
    y <- rseq (func2 node)
    rseq x
    return (x,y)

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

func2 :: Node -> Int
func2 node = size node2
  where
    node2 = addNewChildAt node [0,0] 0


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

addc node h w = foldl' (add h) node [0..w] 
  where
    add h node pos = addNewChildAt node h pos
  
printTimeSince t0 = do
  t1 <- getCurrentTime
  printf "time: %.2fs\n" (realToFrac (diffUTCTime t1 t0) :: Double)