ghcjs-base-stub-0.3.0.1: Allow GHCJS projects to compile under GHC and develop using intero.

Safe HaskellNone
LanguageHaskell2010

GHCJS.Concurrent

Description

GHCJS has two types of threads. Regular, asynchronous threads are started with `h$run`, are managed by the scheduler and run in the background. `h$run` returns immediately.

Synchronous threads are started with `h$runSync`, which returns when the thread has run to completion. When a synchronous thread does an operation that would block, like accessing an MVar or an asynchronous FFI call, it cannot continue synchronously.

There are two ways this can be resolved, depending on the second argument of the `h$runSync` call:

  • The action is aborted and the thread receives a WouldBlockException
  • The thread continues asynchronously, `h$runSync` returns

Note: when a synchronous thread encounters a black hole from another thread, it tries to steal the work from that thread to avoid blocking. In some cases that might not be possible, for example when the data accessed is produced by a lazy IO operation. This is resolved the same way as blocking on an IO action would be.

Synopsis

Documentation

isThreadSynchronous :: ThreadId -> IO Bool Source #

Returns whether the ThreadId is a synchronous thread

isThreadContinueAsync :: ThreadId -> IO Bool Source #

Returns whether the ThreadId will continue running async. Always returns True when the thread is not synchronous.

data OnBlocked Source #

The runtime tries to run synchronous threads to completion. Sometimes it's not possible to continue running a thread, for example when the thread tries to take an empty MVar. The runtime can then either throw a WouldBlockException, aborting the blocking action, or continue the thread asynchronously.

Constructors

ContinueAsync

continue the thread asynchronously if blocked

ThrowWouldBlock

throw WouldBlockException if blocked

Instances
Enum OnBlocked Source # 
Instance details

Defined in GHCJS.Concurrent

Eq OnBlocked Source # 
Instance details

Defined in GHCJS.Concurrent

Data OnBlocked Source # 
Instance details

Defined in GHCJS.Concurrent

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OnBlocked -> c OnBlocked #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OnBlocked #

toConstr :: OnBlocked -> Constr #

dataTypeOf :: OnBlocked -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OnBlocked) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OnBlocked) #

gmapT :: (forall b. Data b => b -> b) -> OnBlocked -> OnBlocked #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OnBlocked -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OnBlocked -> r #

gmapQ :: (forall d. Data d => d -> u) -> OnBlocked -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OnBlocked -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OnBlocked -> m OnBlocked #

Ord OnBlocked Source # 
Instance details

Defined in GHCJS.Concurrent

Show OnBlocked Source # 
Instance details

Defined in GHCJS.Concurrent

data WouldBlockException Source #

If a synchronous thread tries to do something that can only be done asynchronously, and the thread is set up to not continue asynchronously, it receives this exception.

Constructors

WouldBlockException 

withoutPreemption :: IO a -> IO a Source #

Run the action without the scheduler preempting the thread. When a blocking action is encountered, the thread is still suspended and will continue without preemption when it's woken up again.

When the thread encounters a black hole from another thread, the scheduler will attempt to clear it by temporarily switching to that thread.

synchronously :: IO a -> IO a Source #

Run the action synchronously, which means that the thread will not be preempted by the scheduler. If the thread encounters a blocking operation, the runtime throws a WouldBlock exception.

When the thread encounters a black hole from another thread, the scheduler will attempt to clear it by temporarily switching to that thread.