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

Safe HaskellNone
LanguageHaskell2010

GHCJS.Foreign.Callback

Contents

Synopsis

Documentation

data Callback a Source #

Instances
IsJSVal (Callback a) Source # 
Instance details

Defined in GHCJS.Foreign.Callback.Internal

Methods

jsval_ :: Callback a -> JSVal

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

releaseCallback :: Callback a -> IO () Source #

When you create a callback, the Haskell runtime stores a reference to the exported IO action or function. This means that all data referenced by the exported value stays in memory, even if nothing outside the Haskell runtime holds a reference to to callback.

Use releaseCallback to free the reference. Subsequent calls from JavaScript to the callback will result in an exception.

asynchronous callbacks

asyncCallback Source #

Arguments

:: IO ()

the action that the callback runs

-> IO (Callback (IO ()))

the callback

Make a callback (JavaScript function) that runs the supplied IO action in an asynchronous thread when called.

Call releaseCallback when done with the callback, freeing data referenced by the IO action.

asyncCallback1 Source #

Arguments

:: (JSVal -> IO ())

the function that the callback calls

-> IO (Callback (JSVal -> IO ()))

the calback

asyncCallback2 Source #

Arguments

:: (JSVal -> JSVal -> IO ())

the Haskell function that the callback calls

-> IO (Callback (JSVal -> JSVal -> IO ()))

the callback

asyncCallback3 Source #

Arguments

:: (JSVal -> JSVal -> JSVal -> IO ())

the Haskell function that the callback calls

-> IO (Callback (JSVal -> JSVal -> JSVal -> IO ()))

the callback

synchronous callbacks

syncCallback Source #

Arguments

:: OnBlocked

what to do when the thread blocks

-> IO ()

the Haskell action

-> IO (Callback (IO ()))

the callback

Make a callback (JavaScript function) that runs the supplied IO action in a synchronous thread when called.

Call releaseCallback when done with the callback, freeing memory referenced by the IO action.

syncCallback1 Source #

Arguments

:: OnBlocked

what to do when the thread blocks

-> (JSVal -> IO ())

the Haskell function

-> IO (Callback (JSVal -> IO ()))

the callback

Make a callback (JavaScript function) that runs the supplied IO function in a synchronous thread when called. The callback takes one argument that it passes as a JSVal value to the Haskell function.

Call releaseCallback when done with the callback, freeing data referenced by the function.

syncCallback2 Source #

Arguments

:: OnBlocked

what to do when the thread blocks

-> (JSVal -> JSVal -> IO ())

the Haskell function

-> IO (Callback (JSVal -> JSVal -> IO ()))

the callback

Make a callback (JavaScript function) that runs the supplied IO function in a synchronous thread when called. The callback takes two arguments that it passes as JSVal values to the Haskell function.

Call releaseCallback when done with the callback, freeing data referenced by the function.

syncCallback3 Source #

Arguments

:: OnBlocked

what to do when the thread blocks

-> (JSVal -> JSVal -> JSVal -> IO ())

the Haskell function

-> IO (Callback (JSVal -> JSVal -> JSVal -> IO ()))

the callback

Make a callback (JavaScript function) that runs the supplied IO function in a synchronous thread when called. The callback takes three arguments that it passes as JSVal values to the Haskell function.

Call releaseCallback when done with the callback, freeing data referenced by the function.

synchronous callbacks that return a value

syncCallback' :: IO JSVal -> IO (Callback (IO JSVal)) Source #

Make a callback (JavaScript function) that runs the supplied IO action in a synchronous thread when called.

Call releaseCallback when done with the callback, freeing memory referenced by the IO action.