Safe Haskell | None |
---|---|
Language | GHC2021 |
Effects.Concurrent.Thread
Description
Provides the MonadThread
typeclass.
Since: 0.1
Synopsis
- class Monad m => MonadThread (m :: Type -> Type) where
- threadDelay :: Int -> m ()
- throwTo :: (Exception e, HasCallStack) => ThreadId -> e -> m ()
- getNumCapabilities :: m Int
- setNumCapabilities :: Int -> m ()
- threadCapability :: ThreadId -> m (Int, Bool)
- myThreadId :: m ThreadId
- labelThread :: ThreadId -> String -> m ()
- threadLabel :: ThreadId -> m (Maybe String)
- microsleep :: (HasCallStack, MonadThread m) => Natural -> m ()
- sleep :: (HasCallStack, MonadThread m) => Natural -> m ()
- data Natural
- data ThreadId
- class Monad m => MonadQSem (m :: Type -> Type) where
- class Monad m => MonadQSemN (m :: Type -> Type) where
- data QSem
- data QSemN
Thread Effect
class Monad m => MonadThread (m :: Type -> Type) where Source #
Represents thread effects.
Since: 0.1
Methods
threadDelay :: Int -> m () Source #
Lifted threadDelay
.
Since: 0.1
throwTo :: (Exception e, HasCallStack) => ThreadId -> e -> m () Source #
Lifted throwTo
.
Since: 0.1
getNumCapabilities :: m Int Source #
Lifted getNumCapabilities
.
Since: 0.1
setNumCapabilities :: Int -> m () Source #
Lifted setNumCapabilities
.
Since: 0.1
threadCapability :: ThreadId -> m (Int, Bool) Source #
Lifted threadCapability
.
Since: 0.1
myThreadId :: m ThreadId Source #
Lifted myThreadId
.
Since: 0.1
labelThread :: ThreadId -> String -> m () Source #
Lifted labelThread
.
Since: 0.1
threadLabel :: ThreadId -> m (Maybe String) Source #
Lifted threadLabel
.
Since: 0.1
Instances
MonadThread IO Source # | Since: 0.1 |
Defined in Effects.Concurrent.Thread Methods threadDelay :: Int -> IO () Source # throwTo :: (Exception e, HasCallStack) => ThreadId -> e -> IO () Source # getNumCapabilities :: IO Int Source # setNumCapabilities :: Int -> IO () Source # threadCapability :: ThreadId -> IO (Int, Bool) Source # myThreadId :: IO ThreadId Source # | |
MonadThread m => MonadThread (ReaderT e m) Source # | Since: 0.1 |
Defined in Effects.Concurrent.Thread Methods threadDelay :: Int -> ReaderT e m () Source # throwTo :: (Exception e0, HasCallStack) => ThreadId -> e0 -> ReaderT e m () Source # getNumCapabilities :: ReaderT e m Int Source # setNumCapabilities :: Int -> ReaderT e m () Source # threadCapability :: ThreadId -> ReaderT e m (Int, Bool) Source # myThreadId :: ReaderT e m ThreadId Source # labelThread :: ThreadId -> String -> ReaderT e m () Source # threadLabel :: ThreadId -> ReaderT e m (Maybe String) Source # |
microsleep :: (HasCallStack, MonadThread m) => Natural -> m () Source #
threadDelay
in terms of unbounded Natural
rather than Int
i.e.
runs sleep in the current thread for the specified number of microseconds.
Since: 0.1
sleep :: (HasCallStack, MonadThread m) => Natural -> m () Source #
Runs sleep in the current thread for the specified number of seconds.
Since: 0.1
Reexports
Natural number
Invariant: numbers <= 0xffffffffffffffff use the NS
constructor
Instances
Data Natural | Since: base-4.8.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural # toConstr :: Natural -> Constr # dataTypeOf :: Natural -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) # gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r # gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural # | |
Bits Natural | Since: base-4.8.0 |
Defined in GHC.Bits Methods (.&.) :: Natural -> Natural -> Natural # (.|.) :: Natural -> Natural -> Natural # xor :: Natural -> Natural -> Natural # complement :: Natural -> Natural # shift :: Natural -> Int -> Natural # rotate :: Natural -> Int -> Natural # setBit :: Natural -> Int -> Natural # clearBit :: Natural -> Int -> Natural # complementBit :: Natural -> Int -> Natural # testBit :: Natural -> Int -> Bool # bitSizeMaybe :: Natural -> Maybe Int # shiftL :: Natural -> Int -> Natural # unsafeShiftL :: Natural -> Int -> Natural # shiftR :: Natural -> Int -> Natural # unsafeShiftR :: Natural -> Int -> Natural # rotateL :: Natural -> Int -> Natural # | |
Enum Natural | Since: base-4.8.0.0 |
Ix Natural | Since: base-4.8.0.0 |
Defined in GHC.Ix | |
Num Natural | Note that Since: base-4.8.0.0 |
Read Natural | Since: base-4.8.0.0 |
Integral Natural | Since: base-4.8.0.0 |
Defined in GHC.Real | |
Real Natural | Since: base-4.8.0.0 |
Defined in GHC.Real Methods toRational :: Natural -> Rational # | |
Show Natural | Since: base-4.8.0.0 |
PrintfArg Natural | Since: base-4.8.0.0 |
Defined in Text.Printf | |
Eq Natural | |
Ord Natural | |
KnownNat n => HasResolution (n :: Nat) | For example, |
Defined in Data.Fixed Methods resolution :: p n -> Integer # | |
TestCoercion SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
TestEquality SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
type Compare (a :: Natural) (b :: Natural) | |
Defined in Data.Type.Ord |
A ThreadId
is an abstract type representing a handle to a thread.
ThreadId
is an instance of Eq
, Ord
and Show
, where
the Ord
instance implements an arbitrary total ordering over
ThreadId
s. The Show
instance lets you convert an arbitrary-valued
ThreadId
to string form; showing a ThreadId
value is occasionally
useful when debugging or diagnosing the behaviour of a concurrent
program.
Note: in GHC, if you have a ThreadId
, you essentially have
a pointer to the thread itself. This means the thread itself can't be
garbage collected until you drop the ThreadId
. This misfeature would
be difficult to correct while continuing to support threadStatus
.
QSem Effect
class Monad m => MonadQSem (m :: Type -> Type) where Source #
Effect for QSem
semaphore.
Since: 0.1
Methods
newQSem :: Int -> m QSem Source #
Lifted newQSem
.
Since: 0.1
waitQSem :: QSem -> m () Source #
Lifted waitQSem
.
Since: 0.1
signalQSem :: QSem -> m () Source #
Lifted signalQSem
.
Since: 0.1
class Monad m => MonadQSemN (m :: Type -> Type) where Source #
Effect for QSemN
semaphore.
Since: 0.1
Methods
newQSemN :: Int -> m QSemN Source #
Lifted newQSemN
.
Since: 0.1
waitQSemN :: QSemN -> Int -> m () Source #
Lifted waitQSemN
.
Since: 0.1
signalQSemN :: QSemN -> Int -> m () Source #
Lifted signalQSemN
.
Since: 0.1
Instances
MonadQSemN IO Source # | Since: 0.1 |
MonadQSemN m => MonadQSemN (ReaderT e m) Source # | Since: 0.1 |