2015-12-01 07:27:58 +03:00
|
|
|
-- An implementation of the Dining Philosophers. This is interesting
|
|
|
|
-- as it show-cases testing a non-terminating program.
|
2016-03-31 20:16:09 +03:00
|
|
|
module Examples.Philosophers where
|
2015-12-01 07:27:58 +03:00
|
|
|
|
|
|
|
import Control.Monad (replicateM, forever)
|
|
|
|
import Control.Monad.Conc.Class
|
|
|
|
import Data.Functor (void)
|
|
|
|
import Test.DejaFu
|
|
|
|
import Test.Framework (Test)
|
|
|
|
import Test.Framework.Providers.HUnit (hUnitTestToTests)
|
|
|
|
import Test.HUnit (test)
|
|
|
|
import Test.HUnit.DejaFu
|
2017-02-20 06:23:46 +03:00
|
|
|
import System.Random (StdGen)
|
2015-12-01 07:27:58 +03:00
|
|
|
|
|
|
|
tests :: [Test]
|
|
|
|
tests = hUnitTestToTests $ test
|
2017-02-20 06:23:46 +03:00
|
|
|
[ testDejafuWay way defaultMemType (philosophers 3) "deadlocks" deadlocksSometimes
|
|
|
|
, testDejafuWay way defaultMemType (philosophers 3) "loops" abortsSometimes
|
2015-12-01 07:27:58 +03:00
|
|
|
]
|
|
|
|
|
|
|
|
-- | Shorter execution length bound
|
2017-02-26 05:51:36 +03:00
|
|
|
way :: Way
|
2017-02-20 06:23:46 +03:00
|
|
|
way = Systematically defaultBounds { boundLength = Just 30 }
|
2015-12-01 07:27:58 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Run the Dining Philosophers. Result is irrelevant, we just care
|
|
|
|
-- about deadlocks.
|
|
|
|
philosophers :: MonadConc m => Int -> m ()
|
|
|
|
philosophers n = do
|
2016-03-23 06:36:07 +03:00
|
|
|
forks <- replicateM n newEmptyMVar
|
2015-12-01 07:27:58 +03:00
|
|
|
let phils = map (\(i,p) -> p i forks) $ zip [0..] $ replicate n philosopher
|
|
|
|
cvars <- mapM spawn phils
|
2016-03-23 06:36:07 +03:00
|
|
|
mapM_ takeMVar cvars
|
2015-12-01 07:27:58 +03:00
|
|
|
|
|
|
|
where
|
|
|
|
philosopher ident forks = forever $ do
|
|
|
|
let leftId = ident
|
|
|
|
let rightId = (ident + 1) `mod` length forks
|
2016-04-03 08:29:54 +03:00
|
|
|
putMVar (forks !! leftId) ()
|
|
|
|
putMVar (forks !! rightId) ()
|
2015-12-01 07:27:58 +03:00
|
|
|
-- In the traditional approach, we'd wait for a random time
|
|
|
|
-- here, but we want the only source of (important)
|
|
|
|
-- nondeterminism to come from the scheduler, which it does, as
|
|
|
|
-- pre-emption is effectively a delay.
|
2016-04-03 08:29:54 +03:00
|
|
|
takeMVar $ forks !! leftId
|
|
|
|
takeMVar $ forks !! rightId
|