{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Control.Monad.IOSim.InternalTypes
( ThreadControl (..)
, ControlStack (..)
, IsLocked (..)
, unsafeUnregisterTimeout
) where
import Control.Concurrent.Class.MonadSTM
import Control.Exception (Exception)
import Control.Monad.Class.MonadThrow (MaskingState (..))
import Control.Monad.IOSim.Types (IOSim (..), IOSimThreadId, SimA (..),
TimeoutId)
import GHC.Exts (oneShot)
data ThreadControl s a where
ThreadControl :: SimA s b
-> !(ControlStack s b a)
-> ThreadControl s a
instance Show (ThreadControl s a) where
show :: ThreadControl s a -> String
show ThreadControl s a
_ = String
"..."
data ControlStack s b a where
MainFrame :: ControlStack s a a
ForkFrame :: ControlStack s () a
MaskFrame :: (b -> SimA s c)
-> MaskingState
-> !(ControlStack s c a)
-> ControlStack s b a
CatchFrame :: Exception e
=> (e -> SimA s b)
-> (b -> SimA s c)
-> !(ControlStack s c a)
-> ControlStack s b a
TimeoutFrame :: TimeoutId
-> TMVar (IOSim s) IOSimThreadId
-> (Maybe b -> SimA s c)
-> !(ControlStack s c a)
-> ControlStack s b a
DelayFrame :: TimeoutId
-> SimA s c
-> ControlStack s c a
-> ControlStack s b a
instance Show (ControlStack s b a) where
show :: ControlStack s b a -> String
show = ControlStackDash -> String
forall a. Show a => a -> String
show (ControlStackDash -> String)
-> (ControlStack s b a -> ControlStackDash)
-> ControlStack s b a
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ControlStack s b a -> ControlStackDash
forall b'. ControlStack s b' a -> ControlStackDash
dash
where
dash :: ControlStack s b' a -> ControlStackDash
dash :: forall b'. ControlStack s b' a -> ControlStackDash
dash ControlStack s b' a
MainFrame = ControlStackDash
MainFrame'
dash ControlStack s b' a
ForkFrame = ControlStackDash
ForkFrame'
dash (MaskFrame b' -> SimA s c
_ MaskingState
m ControlStack s c a
cs) = MaskingState -> ControlStackDash -> ControlStackDash
MaskFrame' MaskingState
m (ControlStack s c a -> ControlStackDash
forall b'. ControlStack s b' a -> ControlStackDash
dash ControlStack s c a
cs)
dash (CatchFrame e -> SimA s b'
_ b' -> SimA s c
_ ControlStack s c a
cs) = ControlStackDash -> ControlStackDash
CatchFrame' (ControlStack s c a -> ControlStackDash
forall b'. ControlStack s b' a -> ControlStackDash
dash ControlStack s c a
cs)
dash (TimeoutFrame TimeoutId
tmid TMVar (IOSim s) IOSimThreadId
_ Maybe b' -> SimA s c
_ ControlStack s c a
cs) = TimeoutId -> ControlStackDash -> ControlStackDash
TimeoutFrame' TimeoutId
tmid (ControlStack s c a -> ControlStackDash
forall b'. ControlStack s b' a -> ControlStackDash
dash ControlStack s c a
cs)
dash (DelayFrame TimeoutId
tmid SimA s c
_ ControlStack s c a
cs) = TimeoutId -> ControlStackDash -> ControlStackDash
DelayFrame' TimeoutId
tmid (ControlStack s c a -> ControlStackDash
forall b'. ControlStack s b' a -> ControlStackDash
dash ControlStack s c a
cs)
data ControlStackDash =
MainFrame'
| ForkFrame'
| MaskFrame' MaskingState ControlStackDash
| CatchFrame' ControlStackDash
| TimeoutFrame' TimeoutId ControlStackDash
| ThreadDelayFrame' TimeoutId ControlStackDash
| DelayFrame' TimeoutId ControlStackDash
deriving Int -> ControlStackDash -> ShowS
[ControlStackDash] -> ShowS
ControlStackDash -> String
(Int -> ControlStackDash -> ShowS)
-> (ControlStackDash -> String)
-> ([ControlStackDash] -> ShowS)
-> Show ControlStackDash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ControlStackDash -> ShowS
showsPrec :: Int -> ControlStackDash -> ShowS
$cshow :: ControlStackDash -> String
show :: ControlStackDash -> String
$cshowList :: [ControlStackDash] -> ShowS
showList :: [ControlStackDash] -> ShowS
Show
data IsLocked = NotLocked | Locked !IOSimThreadId
deriving (IsLocked -> IsLocked -> Bool
(IsLocked -> IsLocked -> Bool)
-> (IsLocked -> IsLocked -> Bool) -> Eq IsLocked
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IsLocked -> IsLocked -> Bool
== :: IsLocked -> IsLocked -> Bool
$c/= :: IsLocked -> IsLocked -> Bool
/= :: IsLocked -> IsLocked -> Bool
Eq, Int -> IsLocked -> ShowS
[IsLocked] -> ShowS
IsLocked -> String
(Int -> IsLocked -> ShowS)
-> (IsLocked -> String) -> ([IsLocked] -> ShowS) -> Show IsLocked
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IsLocked -> ShowS
showsPrec :: Int -> IsLocked -> ShowS
$cshow :: IsLocked -> String
show :: IsLocked -> String
$cshowList :: [IsLocked] -> ShowS
showList :: [IsLocked] -> ShowS
Show)
unsafeUnregisterTimeout :: TimeoutId -> IOSim s ()
unsafeUnregisterTimeout :: forall s. TimeoutId -> IOSim s ()
unsafeUnregisterTimeout TimeoutId
tmid = (forall r. (() -> SimA s r) -> SimA s r) -> IOSim s ()
forall s a. (forall r. (a -> SimA s r) -> SimA s r) -> IOSim s a
IOSim ((forall r. (() -> SimA s r) -> SimA s r) -> IOSim s ())
-> (forall r. (() -> SimA s r) -> SimA s r) -> IOSim s ()
forall a b. (a -> b) -> a -> b
$ ((() -> SimA s r) -> SimA s r) -> (() -> SimA s r) -> SimA s r
forall a b. (a -> b) -> a -> b
oneShot (((() -> SimA s r) -> SimA s r) -> (() -> SimA s r) -> SimA s r)
-> ((() -> SimA s r) -> SimA s r) -> (() -> SimA s r) -> SimA s r
forall a b. (a -> b) -> a -> b
$ \() -> SimA s r
k -> TimeoutId -> SimA s r -> SimA s r
forall s a. TimeoutId -> SimA s a -> SimA s a
UnregisterTimeout TimeoutId
tmid (() -> SimA s r
k ())