Skip to content

Commit

Permalink
add a test for setNumCapabilities
Browse files Browse the repository at this point in the history
  • Loading branch information
simonmar committed Dec 19, 2011
1 parent 94ebbb0 commit 8556be4
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 0 deletions.
4 changes: 4 additions & 0 deletions tests/concurrent/should_run/all.T
Expand Up @@ -210,3 +210,7 @@ test('conc067', ignore_output, compile_and_run, [''])
# than one CPU.
test('conc068', [ omit_ways('threaded2'), exit_code(1) ], compile_and_run, [''])

test('setnumcapabilities001',
[ only_ways(['threaded1','threaded2']),
extra_run_opts('4 12 2000') ],
compile_and_run, [''])
34 changes: 34 additions & 0 deletions tests/concurrent/should_run/setnumcapabilities001.hs
@@ -0,0 +1,34 @@
import GHC.Conc
import Control.Parallel
import Control.Parallel.Strategies
import System.Environment
import System.IO
import Control.Monad
import Text.Printf
import Data.Time.Clock

main = do
[n,q,t] <- fmap (fmap read) getArgs
forkIO $ do
forM_ (cycle ([n,n-1..1] ++ [2..n-1])) $ \m -> do
setNumCapabilities m
threadDelay t
printf "%d" (nqueens q)

nqueens :: Int -> Int
nqueens nq = length (pargen 0 [])
where
safe :: Int -> Int -> [Int] -> Bool
safe x d [] = True
safe x d (q:l) = x /= q && x /= q+d && x /= q-d && safe x (d+1) l

gen :: [[Int]] -> [[Int]]
gen bs = [ (q:b) | b <- bs, q <- [1..nq], safe q 1 b ]

pargen :: Int -> [Int] -> [[Int]]
pargen n b
| n >= threshold = iterate gen [b] !! (nq - n)
| otherwise = concat bs
where bs = map (pargen (n+1)) (gen [b]) `using` parList rdeepseq

threshold = 3
1 change: 1 addition & 0 deletions tests/concurrent/should_run/setnumcapabilities001.stdout
@@ -0,0 +1 @@
14200

0 comments on commit 8556be4

Please sign in to comment.