{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
module Test.DejaFu.Internal where
import Control.DeepSeq (NFData(..))
import Control.Exception (MaskingState(..))
import Data.List.NonEmpty (NonEmpty(..))
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe (fromMaybe)
import Data.Set (Set)
import qualified Data.Set as S
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack, withFrozenCallStack)
import System.Random (RandomGen)
import Test.DejaFu.Types
data Settings n a = Settings
{ forall (n :: * -> *) a. Settings n a -> Way
_way :: Way
, forall (n :: * -> *) a. Settings n a -> Maybe LengthBound
_lengthBound :: Maybe LengthBound
, forall (n :: * -> *) a. Settings n a -> MemType
_memtype :: MemType
, forall (n :: * -> *) a.
Settings n a -> Maybe (Either Condition a -> Maybe Discard)
_discard :: Maybe (Either Condition a -> Maybe Discard)
, forall (n :: * -> *) a. Settings n a -> Maybe (a -> String)
_debugShow :: Maybe (a -> String)
, forall (n :: * -> *) a. Settings n a -> Maybe (String -> n ())
_debugPrint :: Maybe (String -> n ())
, forall (n :: * -> *) a. Settings n a -> Bool
_debugFatal :: Bool
, forall (n :: * -> *) a.
Settings n a -> Maybe (Either Condition a -> Bool)
_earlyExit :: Maybe (Either Condition a -> Bool)
, forall (n :: * -> *) a. Settings n a -> Maybe (a -> a -> Bool)
_equality :: Maybe (a -> a -> Bool)
, forall (n :: * -> *) a. Settings n a -> Bool
_simplify :: Bool
, forall (n :: * -> *) a. Settings n a -> Bool
_safeIO :: Bool
, forall (n :: * -> *) a. Settings n a -> Bool
_showAborts :: Bool
}
data Way where
Systematic :: Bounds -> Way
Randomly :: RandomGen g => (g -> (Int, g)) -> g -> Int -> Way
instance Show Way where
show :: Way -> String
show (Systematic Bounds
bs) = String
"Systematic (" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Bounds
bs forall a. [a] -> [a] -> [a]
++ String
")"
show (Randomly g -> (Int, g)
_ g
_ Int
n) = String
"Randomly <f> <gen> " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
data IdSource = IdSource
{ IdSource -> (Int, [String])
_iorids :: (Int, [String])
, IdSource -> (Int, [String])
_mvids :: (Int, [String])
, IdSource -> (Int, [String])
_tvids :: (Int, [String])
, IdSource -> (Int, [String])
_tids :: (Int, [String])
} deriving (IdSource -> IdSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdSource -> IdSource -> Bool
$c/= :: IdSource -> IdSource -> Bool
== :: IdSource -> IdSource -> Bool
$c== :: IdSource -> IdSource -> Bool
Eq, Eq IdSource
IdSource -> IdSource -> Bool
IdSource -> IdSource -> Ordering
IdSource -> IdSource -> IdSource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IdSource -> IdSource -> IdSource
$cmin :: IdSource -> IdSource -> IdSource
max :: IdSource -> IdSource -> IdSource
$cmax :: IdSource -> IdSource -> IdSource
>= :: IdSource -> IdSource -> Bool
$c>= :: IdSource -> IdSource -> Bool
> :: IdSource -> IdSource -> Bool
$c> :: IdSource -> IdSource -> Bool
<= :: IdSource -> IdSource -> Bool
$c<= :: IdSource -> IdSource -> Bool
< :: IdSource -> IdSource -> Bool
$c< :: IdSource -> IdSource -> Bool
compare :: IdSource -> IdSource -> Ordering
$ccompare :: IdSource -> IdSource -> Ordering
Ord, Int -> IdSource -> ShowS
[IdSource] -> ShowS
IdSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdSource] -> ShowS
$cshowList :: [IdSource] -> ShowS
show :: IdSource -> String
$cshow :: IdSource -> String
showsPrec :: Int -> IdSource -> ShowS
$cshowsPrec :: Int -> IdSource -> ShowS
Show, forall x. Rep IdSource x -> IdSource
forall x. IdSource -> Rep IdSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IdSource x -> IdSource
$cfrom :: forall x. IdSource -> Rep IdSource x
Generic, IdSource -> ()
forall a. (a -> ()) -> NFData a
rnf :: IdSource -> ()
$crnf :: IdSource -> ()
NFData)
nextIORId :: String -> IdSource -> (IdSource, IORefId)
nextIORId :: String -> IdSource -> (IdSource, IORefId)
nextIORId String
name IdSource
idsource =
let (Id
iorid, (Int, [String])
iorids') = String -> (Int, [String]) -> (Id, (Int, [String]))
nextId String
name (IdSource -> (Int, [String])
_iorids IdSource
idsource)
in (IdSource
idsource { _iorids :: (Int, [String])
_iorids = (Int, [String])
iorids' }, Id -> IORefId
IORefId Id
iorid)
nextMVId :: String -> IdSource -> (IdSource, MVarId)
nextMVId :: String -> IdSource -> (IdSource, MVarId)
nextMVId String
name IdSource
idsource =
let (Id
mvid, (Int, [String])
mvids') = String -> (Int, [String]) -> (Id, (Int, [String]))
nextId String
name (IdSource -> (Int, [String])
_mvids IdSource
idsource)
in (IdSource
idsource { _mvids :: (Int, [String])
_mvids = (Int, [String])
mvids' }, Id -> MVarId
MVarId Id
mvid)
nextTVId :: String -> IdSource -> (IdSource, TVarId)
nextTVId :: String -> IdSource -> (IdSource, TVarId)
nextTVId String
name IdSource
idsource =
let (Id
tvid, (Int, [String])
tvids') = String -> (Int, [String]) -> (Id, (Int, [String]))
nextId String
name (IdSource -> (Int, [String])
_tvids IdSource
idsource)
in (IdSource
idsource { _tvids :: (Int, [String])
_tvids = (Int, [String])
tvids' }, Id -> TVarId
TVarId Id
tvid)
nextTId :: String -> IdSource -> (IdSource, ThreadId)
nextTId :: String -> IdSource -> (IdSource, ThreadId)
nextTId String
name IdSource
idsource =
let (Id
tid, (Int, [String])
tids') = String -> (Int, [String]) -> (Id, (Int, [String]))
nextId String
name (IdSource -> (Int, [String])
_tids IdSource
idsource)
in (IdSource
idsource { _tids :: (Int, [String])
_tids = (Int, [String])
tids' }, Id -> ThreadId
ThreadId Id
tid)
nextId :: String -> (Int, [String]) -> (Id, (Int, [String]))
nextId :: String -> (Int, [String]) -> (Id, (Int, [String]))
nextId String
name (Int
num, [String]
used) = (Maybe String -> Int -> Id
Id Maybe String
newName (Int
numforall a. Num a => a -> a -> a
+Int
1), (Int
numforall a. Num a => a -> a -> a
+Int
1, [String]
newUsed)) where
newName :: Maybe String
newName
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
name = forall a. Maybe a
Nothing
| Int
occurrences forall a. Ord a => a -> a -> Bool
> Int
0 = forall a. a -> Maybe a
Just (String
name forall a. [a] -> [a] -> [a]
++ String
"-" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
occurrences)
| Bool
otherwise = forall a. a -> Maybe a
Just String
name
newUsed :: [String]
newUsed
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
name = [String]
used
| Bool
otherwise = String
name forall a. a -> [a] -> [a]
: [String]
used
occurrences :: Int
occurrences = forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
==String
name) [String]
used)
initialIdSource :: IdSource
initialIdSource :: IdSource
initialIdSource = (Int, [String])
-> (Int, [String])
-> (Int, [String])
-> (Int, [String])
-> IdSource
IdSource (Int
0, []) (Int
0, []) (Int
0, []) (Int
0, [])
isBlock :: ThreadAction -> Bool
isBlock :: ThreadAction -> Bool
isBlock (BlockedThrowTo ThreadId
_) = Bool
True
isBlock (BlockedTakeMVar MVarId
_) = Bool
True
isBlock (BlockedReadMVar MVarId
_) = Bool
True
isBlock (BlockedPutMVar MVarId
_) = Bool
True
isBlock (BlockedSTM [TAction]
_) = Bool
True
isBlock ThreadAction
_ = Bool
False
tvarsOf :: ThreadAction -> Set TVarId
tvarsOf :: ThreadAction -> Set TVarId
tvarsOf ThreadAction
act = ThreadAction -> Set TVarId
tvarsRead ThreadAction
act forall a. Ord a => Set a -> Set a -> Set a
`S.union` ThreadAction -> Set TVarId
tvarsWritten ThreadAction
act
tvarsWritten :: ThreadAction -> Set TVarId
tvarsWritten :: ThreadAction -> Set TVarId
tvarsWritten ThreadAction
act = forall a. Ord a => [a] -> Set a
S.fromList forall a b. (a -> b) -> a -> b
$ case ThreadAction
act of
STM [TAction]
trc [ThreadId]
_ -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
ThrownSTM [TAction]
trc Maybe MaskingState
_ -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
BlockedSTM [TAction]
trc -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
ThreadAction
_ -> []
where
tvarsOf' :: TAction -> [TVarId]
tvarsOf' (TNew TVarId
tv) = [TVarId
tv]
tvarsOf' (TWrite TVarId
tv) = [TVarId
tv]
tvarsOf' (TOrElse [TAction]
ta Maybe [TAction]
tb) = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' ([TAction]
ta forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe [] Maybe [TAction]
tb)
tvarsOf' (TCatch [TAction]
ta Maybe [TAction]
tb) = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' ([TAction]
ta forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe [] Maybe [TAction]
tb)
tvarsOf' TAction
_ = []
tvarsRead :: ThreadAction -> Set TVarId
tvarsRead :: ThreadAction -> Set TVarId
tvarsRead ThreadAction
act = forall a. Ord a => [a] -> Set a
S.fromList forall a b. (a -> b) -> a -> b
$ case ThreadAction
act of
STM [TAction]
trc [ThreadId]
_ -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
ThrownSTM [TAction]
trc Maybe MaskingState
_ -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
BlockedSTM [TAction]
trc -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' [TAction]
trc
ThreadAction
_ -> []
where
tvarsOf' :: TAction -> [TVarId]
tvarsOf' (TRead TVarId
tv) = [TVarId
tv]
tvarsOf' (TOrElse [TAction]
ta Maybe [TAction]
tb) = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' ([TAction]
ta forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe [] Maybe [TAction]
tb)
tvarsOf' (TCatch [TAction]
ta Maybe [TAction]
tb) = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TAction -> [TVarId]
tvarsOf' ([TAction]
ta forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe [] Maybe [TAction]
tb)
tvarsOf' TAction
_ = []
rewind :: ThreadAction -> Lookahead
rewind :: ThreadAction -> Lookahead
rewind (Fork ThreadId
_) = Lookahead
WillFork
rewind (ForkOS ThreadId
_) = Lookahead
WillForkOS
rewind (SupportsBoundThreads Bool
_) = Lookahead
WillSupportsBoundThreads
rewind (IsCurrentThreadBound Bool
_) = Lookahead
WillIsCurrentThreadBound
rewind ThreadAction
MyThreadId = Lookahead
WillMyThreadId
rewind (GetNumCapabilities Int
_) = Lookahead
WillGetNumCapabilities
rewind (SetNumCapabilities Int
i) = Int -> Lookahead
WillSetNumCapabilities Int
i
rewind ThreadAction
Yield = Lookahead
WillYield
rewind (ThreadDelay Int
n) = Int -> Lookahead
WillThreadDelay Int
n
rewind (NewMVar MVarId
_) = Lookahead
WillNewMVar
rewind (PutMVar MVarId
c [ThreadId]
_) = MVarId -> Lookahead
WillPutMVar MVarId
c
rewind (BlockedPutMVar MVarId
c) = MVarId -> Lookahead
WillPutMVar MVarId
c
rewind (TryPutMVar MVarId
c Bool
_ [ThreadId]
_) = MVarId -> Lookahead
WillTryPutMVar MVarId
c
rewind (ReadMVar MVarId
c) = MVarId -> Lookahead
WillReadMVar MVarId
c
rewind (BlockedReadMVar MVarId
c) = MVarId -> Lookahead
WillReadMVar MVarId
c
rewind (TryReadMVar MVarId
c Bool
_) = MVarId -> Lookahead
WillTryReadMVar MVarId
c
rewind (TakeMVar MVarId
c [ThreadId]
_) = MVarId -> Lookahead
WillTakeMVar MVarId
c
rewind (BlockedTakeMVar MVarId
c) = MVarId -> Lookahead
WillTakeMVar MVarId
c
rewind (TryTakeMVar MVarId
c Bool
_ [ThreadId]
_) = MVarId -> Lookahead
WillTryTakeMVar MVarId
c
rewind (NewIORef IORefId
_) = Lookahead
WillNewIORef
rewind (ReadIORef IORefId
c) = IORefId -> Lookahead
WillReadIORef IORefId
c
rewind (ReadIORefCas IORefId
c) = IORefId -> Lookahead
WillReadIORefCas IORefId
c
rewind (ModIORef IORefId
c) = IORefId -> Lookahead
WillModIORef IORefId
c
rewind (ModIORefCas IORefId
c) = IORefId -> Lookahead
WillModIORefCas IORefId
c
rewind (WriteIORef IORefId
c) = IORefId -> Lookahead
WillWriteIORef IORefId
c
rewind (CasIORef IORefId
c Bool
_) = IORefId -> Lookahead
WillCasIORef IORefId
c
rewind (CommitIORef ThreadId
t IORefId
c) = ThreadId -> IORefId -> Lookahead
WillCommitIORef ThreadId
t IORefId
c
rewind (STM [TAction]
_ [ThreadId]
_) = Lookahead
WillSTM
rewind (ThrownSTM [TAction]
_ Maybe MaskingState
_) = Lookahead
WillSTM
rewind (BlockedSTM [TAction]
_) = Lookahead
WillSTM
rewind ThreadAction
Catching = Lookahead
WillCatching
rewind ThreadAction
PopCatching = Lookahead
WillPopCatching
rewind (Throw Maybe MaskingState
_) = Lookahead
WillThrow
rewind (ThrowTo ThreadId
t Maybe MaskingState
_) = ThreadId -> Lookahead
WillThrowTo ThreadId
t
rewind (BlockedThrowTo ThreadId
t) = ThreadId -> Lookahead
WillThrowTo ThreadId
t
rewind (SetMasking Bool
b MaskingState
m) = Bool -> MaskingState -> Lookahead
WillSetMasking Bool
b MaskingState
m
rewind (ResetMasking Bool
b MaskingState
m) = Bool -> MaskingState -> Lookahead
WillResetMasking Bool
b MaskingState
m
rewind (GetMaskingState MaskingState
_) = Lookahead
WillGetMaskingState
rewind ThreadAction
LiftIO = Lookahead
WillLiftIO
rewind ThreadAction
Return = Lookahead
WillReturn
rewind ThreadAction
Stop = Lookahead
WillStop
rewind ThreadAction
RegisterInvariant = Lookahead
WillRegisterInvariant
willRelease :: Lookahead -> Bool
willRelease :: Lookahead -> Bool
willRelease Lookahead
WillFork = Bool
True
willRelease Lookahead
WillForkOS = Bool
True
willRelease Lookahead
WillYield = Bool
True
willRelease (WillThreadDelay Int
_) = Bool
True
willRelease (WillPutMVar MVarId
_) = Bool
True
willRelease (WillTryPutMVar MVarId
_) = Bool
True
willRelease (WillReadMVar MVarId
_) = Bool
True
willRelease (WillTakeMVar MVarId
_) = Bool
True
willRelease (WillTryTakeMVar MVarId
_) = Bool
True
willRelease Lookahead
WillSTM = Bool
True
willRelease Lookahead
WillThrow = Bool
True
willRelease (WillSetMasking Bool
_ MaskingState
_) = Bool
True
willRelease (WillResetMasking Bool
_ MaskingState
_) = Bool
True
willRelease Lookahead
WillStop = Bool
True
willRelease Lookahead
_ = Bool
False
data ActionType =
UnsynchronisedRead IORefId
| UnsynchronisedWrite IORefId
| UnsynchronisedOther
| PartiallySynchronisedCommit IORefId
| PartiallySynchronisedWrite IORefId
| PartiallySynchronisedModify IORefId
| SynchronisedModify IORefId
| SynchronisedRead MVarId
| SynchronisedWrite MVarId
| SynchronisedOther
deriving (ActionType -> ActionType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionType -> ActionType -> Bool
$c/= :: ActionType -> ActionType -> Bool
== :: ActionType -> ActionType -> Bool
$c== :: ActionType -> ActionType -> Bool
Eq, Int -> ActionType -> ShowS
[ActionType] -> ShowS
ActionType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionType] -> ShowS
$cshowList :: [ActionType] -> ShowS
show :: ActionType -> String
$cshow :: ActionType -> String
showsPrec :: Int -> ActionType -> ShowS
$cshowsPrec :: Int -> ActionType -> ShowS
Show, forall x. Rep ActionType x -> ActionType
forall x. ActionType -> Rep ActionType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActionType x -> ActionType
$cfrom :: forall x. ActionType -> Rep ActionType x
Generic, ActionType -> ()
forall a. (a -> ()) -> NFData a
rnf :: ActionType -> ()
$crnf :: ActionType -> ()
NFData)
isBarrier :: ActionType -> Bool
isBarrier :: ActionType -> Bool
isBarrier (SynchronisedModify IORefId
_) = Bool
True
isBarrier (SynchronisedRead MVarId
_) = Bool
True
isBarrier (SynchronisedWrite MVarId
_) = Bool
True
isBarrier ActionType
SynchronisedOther = Bool
True
isBarrier ActionType
_ = Bool
False
isCommit :: ActionType -> IORefId -> Bool
isCommit :: ActionType -> IORefId -> Bool
isCommit (PartiallySynchronisedCommit IORefId
c) IORefId
r = IORefId
c forall a. Eq a => a -> a -> Bool
== IORefId
r
isCommit (PartiallySynchronisedWrite IORefId
c) IORefId
r = IORefId
c forall a. Eq a => a -> a -> Bool
== IORefId
r
isCommit (PartiallySynchronisedModify IORefId
c) IORefId
r = IORefId
c forall a. Eq a => a -> a -> Bool
== IORefId
r
isCommit ActionType
_ IORefId
_ = Bool
False
synchronises :: ActionType -> IORefId -> Bool
synchronises :: ActionType -> IORefId -> Bool
synchronises ActionType
a IORefId
r = ActionType -> IORefId -> Bool
isCommit ActionType
a IORefId
r Bool -> Bool -> Bool
|| ActionType -> Bool
isBarrier ActionType
a
iorefOf :: ActionType -> Maybe IORefId
iorefOf :: ActionType -> Maybe IORefId
iorefOf (UnsynchronisedRead IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf (UnsynchronisedWrite IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf (SynchronisedModify IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf (PartiallySynchronisedCommit IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf (PartiallySynchronisedWrite IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf (PartiallySynchronisedModify IORefId
r) = forall a. a -> Maybe a
Just IORefId
r
iorefOf ActionType
_ = forall a. Maybe a
Nothing
mvarOf :: ActionType -> Maybe MVarId
mvarOf :: ActionType -> Maybe MVarId
mvarOf (SynchronisedRead MVarId
c) = forall a. a -> Maybe a
Just MVarId
c
mvarOf (SynchronisedWrite MVarId
c) = forall a. a -> Maybe a
Just MVarId
c
mvarOf ActionType
_ = forall a. Maybe a
Nothing
tidsOf :: ThreadAction -> Set ThreadId
tidsOf :: ThreadAction -> Set ThreadId
tidsOf (Fork ThreadId
tid) = forall a. a -> Set a
S.singleton ThreadId
tid
tidsOf (ForkOS ThreadId
tid) = forall a. a -> Set a
S.singleton ThreadId
tid
tidsOf (PutMVar MVarId
_ [ThreadId]
tids) = forall a. Ord a => [a] -> Set a
S.fromList [ThreadId]
tids
tidsOf (TryPutMVar MVarId
_ Bool
_ [ThreadId]
tids) = forall a. Ord a => [a] -> Set a
S.fromList [ThreadId]
tids
tidsOf (TakeMVar MVarId
_ [ThreadId]
tids) = forall a. Ord a => [a] -> Set a
S.fromList [ThreadId]
tids
tidsOf (TryTakeMVar MVarId
_ Bool
_ [ThreadId]
tids) = forall a. Ord a => [a] -> Set a
S.fromList [ThreadId]
tids
tidsOf (CommitIORef ThreadId
tid IORefId
_) = forall a. a -> Set a
S.singleton ThreadId
tid
tidsOf (STM [TAction]
_ [ThreadId]
tids) = forall a. Ord a => [a] -> Set a
S.fromList [ThreadId]
tids
tidsOf (ThrowTo ThreadId
tid Maybe MaskingState
_) = forall a. a -> Set a
S.singleton ThreadId
tid
tidsOf (BlockedThrowTo ThreadId
tid) = forall a. a -> Set a
S.singleton ThreadId
tid
tidsOf ThreadAction
_ = forall a. Set a
S.empty
simplifyAction :: ThreadAction -> ActionType
simplifyAction :: ThreadAction -> ActionType
simplifyAction = Lookahead -> ActionType
simplifyLookahead forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreadAction -> Lookahead
rewind
simplifyLookahead :: Lookahead -> ActionType
simplifyLookahead :: Lookahead -> ActionType
simplifyLookahead (WillPutMVar MVarId
c) = MVarId -> ActionType
SynchronisedWrite MVarId
c
simplifyLookahead (WillTryPutMVar MVarId
c) = MVarId -> ActionType
SynchronisedWrite MVarId
c
simplifyLookahead (WillReadMVar MVarId
c) = MVarId -> ActionType
SynchronisedRead MVarId
c
simplifyLookahead (WillTryReadMVar MVarId
c) = MVarId -> ActionType
SynchronisedRead MVarId
c
simplifyLookahead (WillTakeMVar MVarId
c) = MVarId -> ActionType
SynchronisedRead MVarId
c
simplifyLookahead (WillTryTakeMVar MVarId
c) = MVarId -> ActionType
SynchronisedRead MVarId
c
simplifyLookahead (WillReadIORef IORefId
r) = IORefId -> ActionType
UnsynchronisedRead IORefId
r
simplifyLookahead (WillReadIORefCas IORefId
r) = IORefId -> ActionType
UnsynchronisedRead IORefId
r
simplifyLookahead (WillModIORef IORefId
r) = IORefId -> ActionType
SynchronisedModify IORefId
r
simplifyLookahead (WillModIORefCas IORefId
r) = IORefId -> ActionType
PartiallySynchronisedModify IORefId
r
simplifyLookahead (WillWriteIORef IORefId
r) = IORefId -> ActionType
UnsynchronisedWrite IORefId
r
simplifyLookahead (WillCasIORef IORefId
r) = IORefId -> ActionType
PartiallySynchronisedWrite IORefId
r
simplifyLookahead (WillCommitIORef ThreadId
_ IORefId
r) = IORefId -> ActionType
PartiallySynchronisedCommit IORefId
r
simplifyLookahead Lookahead
WillSTM = ActionType
SynchronisedOther
simplifyLookahead (WillThrowTo ThreadId
_) = ActionType
SynchronisedOther
simplifyLookahead Lookahead
_ = ActionType
UnsynchronisedOther
initialCState :: ConcurrencyState
initialCState :: ConcurrencyState
initialCState = Map IORefId Int
-> Set MVarId -> Map ThreadId MaskingState -> ConcurrencyState
ConcurrencyState forall k a. Map k a
M.empty forall a. Set a
S.empty forall k a. Map k a
M.empty
updateCState :: MemType -> ConcurrencyState -> ThreadId -> ThreadAction -> ConcurrencyState
updateCState :: MemType
-> ConcurrencyState -> ThreadId -> ThreadAction -> ConcurrencyState
updateCState MemType
memtype ConcurrencyState
cstate ThreadId
tid ThreadAction
act = ConcurrencyState
{ concIOState :: Map IORefId Int
concIOState = MemType -> ThreadAction -> Map IORefId Int -> Map IORefId Int
updateIOState MemType
memtype ThreadAction
act forall a b. (a -> b) -> a -> b
$ ConcurrencyState -> Map IORefId Int
concIOState ConcurrencyState
cstate
, concMVState :: Set MVarId
concMVState = ThreadAction -> Set MVarId -> Set MVarId
updateMVState ThreadAction
act forall a b. (a -> b) -> a -> b
$ ConcurrencyState -> Set MVarId
concMVState ConcurrencyState
cstate
, concMaskState :: Map ThreadId MaskingState
concMaskState = ThreadId
-> ThreadAction
-> Map ThreadId MaskingState
-> Map ThreadId MaskingState
updateMaskState ThreadId
tid ThreadAction
act forall a b. (a -> b) -> a -> b
$ ConcurrencyState -> Map ThreadId MaskingState
concMaskState ConcurrencyState
cstate
}
updateIOState :: MemType -> ThreadAction -> Map IORefId Int -> Map IORefId Int
updateIOState :: MemType -> ThreadAction -> Map IORefId Int -> Map IORefId Int
updateIOState MemType
SequentialConsistency ThreadAction
_ = forall a b. a -> b -> a
const forall k a. Map k a
M.empty
updateIOState MemType
_ (CommitIORef ThreadId
_ IORefId
r) = (forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
`M.alter` IORefId
r) forall a b. (a -> b) -> a -> b
$ \case
Just Int
1 -> forall a. Maybe a
Nothing
Just Int
n -> forall a. a -> Maybe a
Just (Int
nforall a. Num a => a -> a -> a
-Int
1)
Maybe Int
Nothing -> forall a. Maybe a
Nothing
updateIOState MemType
_ (WriteIORef IORefId
r) = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith forall a. Num a => a -> a -> a
(+) IORefId
r Int
1
updateIOState MemType
_ ThreadAction
ta
| ActionType -> Bool
isBarrier forall a b. (a -> b) -> a -> b
$ ThreadAction -> ActionType
simplifyAction ThreadAction
ta = forall a b. a -> b -> a
const forall k a. Map k a
M.empty
| Bool
otherwise = forall a. a -> a
id
updateMVState :: ThreadAction -> Set MVarId -> Set MVarId
updateMVState :: ThreadAction -> Set MVarId -> Set MVarId
updateMVState (PutMVar MVarId
mvid [ThreadId]
_) = forall a. Ord a => a -> Set a -> Set a
S.insert MVarId
mvid
updateMVState (TryPutMVar MVarId
mvid Bool
True [ThreadId]
_) = forall a. Ord a => a -> Set a -> Set a
S.insert MVarId
mvid
updateMVState (TakeMVar MVarId
mvid [ThreadId]
_) = forall a. Ord a => a -> Set a -> Set a
S.delete MVarId
mvid
updateMVState (TryTakeMVar MVarId
mvid Bool
True [ThreadId]
_) = forall a. Ord a => a -> Set a -> Set a
S.delete MVarId
mvid
updateMVState ThreadAction
_ = forall a. a -> a
id
updateMaskState :: ThreadId -> ThreadAction -> Map ThreadId MaskingState -> Map ThreadId MaskingState
updateMaskState :: ThreadId
-> ThreadAction
-> Map ThreadId MaskingState
-> Map ThreadId MaskingState
updateMaskState ThreadId
tid (Fork ThreadId
tid2) = \Map ThreadId MaskingState
masks -> case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ThreadId
tid Map ThreadId MaskingState
masks of
Just MaskingState
ms -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid2 MaskingState
ms Map ThreadId MaskingState
masks
Maybe MaskingState
Nothing -> Map ThreadId MaskingState
masks
updateMaskState ThreadId
tid (SetMasking Bool
_ MaskingState
ms) = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid MaskingState
ms
updateMaskState ThreadId
tid (ResetMasking Bool
_ MaskingState
ms) = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid MaskingState
ms
updateMaskState ThreadId
tid (Throw Maybe MaskingState
Nothing) = forall k a. Ord k => k -> Map k a -> Map k a
M.delete ThreadId
tid
updateMaskState ThreadId
tid (Throw (Just MaskingState
ms)) = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid MaskingState
ms
updateMaskState ThreadId
tid (ThrownSTM [TAction]
_ Maybe MaskingState
Nothing) = forall k a. Ord k => k -> Map k a -> Map k a
M.delete ThreadId
tid
updateMaskState ThreadId
tid (ThrownSTM [TAction]
_ (Just MaskingState
ms)) = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid MaskingState
ms
updateMaskState ThreadId
_ (ThrowTo ThreadId
tid Maybe MaskingState
Nothing) = forall k a. Ord k => k -> Map k a -> Map k a
M.delete ThreadId
tid
updateMaskState ThreadId
_ (ThrowTo ThreadId
tid (Just MaskingState
ms)) = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ThreadId
tid MaskingState
ms
updateMaskState ThreadId
tid ThreadAction
Stop = forall k a. Ord k => k -> Map k a -> Map k a
M.delete ThreadId
tid
updateMaskState ThreadId
_ ThreadAction
_ = forall a. a -> a
id
etail :: HasCallStack => [a] -> [a]
etail :: forall a. HasCallStack => [a] -> [a]
etail (a
_:[a]
xs) = [a]
xs
etail [a]
_ = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"tail: empty list"
eidx :: HasCallStack => [a] -> Int -> a
eidx :: forall a. HasCallStack => [a] -> Int -> a
eidx [a]
xs Int
i
| Int
i forall a. Ord a => a -> a -> Bool
< forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs = [a]
xs forall a. [a] -> Int -> a
!! Int
i
| Bool
otherwise = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"(!!): index too large"
efromJust :: HasCallStack => Maybe a -> a
efromJust :: forall a. HasCallStack => Maybe a -> a
efromJust (Just a
x) = a
x
efromJust Maybe a
_ = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"fromJust: Nothing"
efromList :: HasCallStack => [a] -> NonEmpty a
efromList :: forall a. HasCallStack => [a] -> NonEmpty a
efromList (a
x:[a]
xs) = a
xforall a. a -> [a] -> NonEmpty a
:|[a]
xs
efromList [a]
_ = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"fromList: empty list"
efromRight :: HasCallStack => Either a b -> b
efromRight :: forall a b. HasCallStack => Either a b -> b
efromRight (Right b
b) = b
b
efromRight Either a b
_ = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"fromRight: Left"
efromLeft :: HasCallStack => Either a b -> a
efromLeft :: forall a b. HasCallStack => Either a b -> a
efromLeft (Left a
a) = a
a
efromLeft Either a b
_ = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal String
"fromLeft: Right"
eadjust :: (Ord k, Show k, HasCallStack) => (v -> v) -> k -> M.Map k v -> M.Map k v
eadjust :: forall k v.
(Ord k, Show k, HasCallStack) =>
(v -> v) -> k -> Map k v -> Map k v
eadjust v -> v
f k
k Map k v
m = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k Map k v
m of
Just v
v -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k (v -> v
f v
v) Map k v
m
Maybe v
Nothing -> forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal (String
"adjust: key '" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show k
k forall a. [a] -> [a] -> [a]
++ String
"' not found")
einsert :: (Ord k, Show k, HasCallStack) => k -> v -> M.Map k v -> M.Map k v
einsert :: forall k v.
(Ord k, Show k, HasCallStack) =>
k -> v -> Map k v -> Map k v
einsert k
k v
v Map k v
m
| forall k a. Ord k => k -> Map k a -> Bool
M.member k
k Map k v
m = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal (String
"insert: key '" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show k
k forall a. [a] -> [a] -> [a]
++ String
"' already present")
| Bool
otherwise = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k v
v Map k v
m
elookup :: (Ord k, Show k, HasCallStack) => k -> M.Map k v -> v
elookup :: forall k v. (Ord k, Show k, HasCallStack) => k -> Map k v -> v
elookup k
k =
forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
fatal (String
"lookup: key '" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show k
k forall a. [a] -> [a] -> [a]
++ String
"' not found")) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k
fatal :: HasCallStack => String -> a
fatal :: forall a. HasCallStack => String -> a
fatal String
msg = forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
error (String
"(dejafu) " forall a. [a] -> [a] -> [a]
++ String
msg)
runRefCont :: MonadDejaFu n
=> (n () -> x)
-> (a -> Maybe b)
-> ((a -> x) -> x)
-> n (x, Ref n (Maybe b))
runRefCont :: forall (n :: * -> *) x a b.
MonadDejaFu n =>
(n () -> x)
-> (a -> Maybe b) -> ((a -> x) -> x) -> n (x, Ref n (Maybe b))
runRefCont n () -> x
act a -> Maybe b
f (a -> x) -> x
k = do
Ref n (Maybe b)
ref <- forall (m :: * -> *) a. MonadDejaFu m => a -> m (Ref m a)
newRef forall a. Maybe a
Nothing
let c :: x
c = (a -> x) -> x
k (n () -> x
act forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadDejaFu m => Ref m a -> a -> m ()
writeRef Ref n (Maybe b)
ref forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe b
f)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (x
c, Ref n (Maybe b)
ref)