jsaddle-0.9.7.0: Interface for JavaScript that works with GHCJS and GHC

Safe HaskellNone
LanguageHaskell2010

Language.Javascript.JSaddle.Monad

Contents

Description

JSM monad keeps track of the JavaScript context

Synopsis

Types

newtype JSM a Source #

The JSM monad keeps track of the JavaScript execution context.

When using GHCJS it is IO.

Given a JSM function and a JSContextRef you can run the function like this...

runJSM jsmFunction javaScriptContext

Constructors

JSM 
Instances
Monad JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

(>>=) :: JSM a -> (a -> JSM b) -> JSM b #

(>>) :: JSM a -> JSM b -> JSM b #

return :: a -> JSM a #

fail :: String -> JSM a #

Functor JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

fmap :: (a -> b) -> JSM a -> JSM b #

(<$) :: a -> JSM b -> JSM a #

MonadFix JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

mfix :: (a -> JSM a) -> JSM a #

MonadFail JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

fail :: String -> JSM a #

Applicative JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

pure :: a -> JSM a #

(<*>) :: JSM (a -> b) -> JSM a -> JSM b #

liftA2 :: (a -> b -> c) -> JSM a -> JSM b -> JSM c #

(*>) :: JSM a -> JSM b -> JSM b #

(<*) :: JSM a -> JSM b -> JSM a #

MonadIO JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftIO :: IO a -> JSM a #

MonadThrow JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

throwM :: Exception e => e -> JSM a #

MonadCatch JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

catch :: Exception e => JSM a -> (e -> JSM a) -> JSM a #

MonadMask JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

mask :: ((forall a. JSM a -> JSM a) -> JSM b) -> JSM b #

uninterruptibleMask :: ((forall a. JSM a -> JSM a) -> JSM b) -> JSM b #

generalBracket :: JSM a -> (a -> ExitCase b -> JSM c) -> (a -> JSM b) -> JSM (b, c) #

MonadRef JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Ref JSM :: Type -> Type #

Methods

newRef :: a -> JSM (Ref JSM a) #

readRef :: Ref JSM a -> JSM a #

writeRef :: Ref JSM a -> a -> JSM () #

modifyRef :: Ref JSM a -> (a -> a) -> JSM () #

modifyRef' :: Ref JSM a -> (a -> a) -> JSM () #

MonadAtomicRef JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

atomicModifyRef :: Ref JSM a -> (a -> (a, b)) -> JSM b #

atomicModifyRef' :: Ref JSM a -> (a -> (a, b)) -> JSM b #

MonadUnliftIO JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

askUnliftIO :: JSM (UnliftIO JSM) #

withRunInIO :: ((forall a. JSM a -> IO a) -> IO b) -> JSM b #

MonadJSM JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> JSM a Source #

MakeArgs JSCallAsFunction Source # 
Instance details

Defined in Language.Javascript.JSaddle.Object

ToJSVal JSCallAsFunction Source #

A callback to Haskell can be used as a JavaScript value. This will create an anonymous JavaScript function object. Use function to create one with a name.

Instance details

Defined in Language.Javascript.JSaddle.Object

MakeArgs arg => MakeArgs (JSM arg) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Classes.Internal

Methods

makeArgs :: JSM arg -> JSM [JSVal] Source #

MakeObject v => MakeObject (JSM v) Source #

Object can be made by evaluating a fnction in JSM as long as it returns something we can make into a Object.

Instance details

Defined in Language.Javascript.JSaddle.Object

Methods

makeObject :: JSM v -> JSM Object Source #

ToJSVal v => ToJSVal (JSM v) Source #

JSVal can be made by evaluating a function in JSM as long as it returns something we can make into a JSVal.

Instance details

Defined in Language.Javascript.JSaddle.Value

type Ref JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Ref JSM = Ref IO

data JSContextRef Source #

Identifies a JavaScript execution context. When using GHCJS this is just '()' since their is only one context. When using GHC it includes the functions JSaddle needs to communicate with the JavaScript context.

class (Applicative m, MonadIO m) => MonadJSM m Source #

The MonadJSM is to JSM what MonadIO is to IO. When using GHCJS it is MonadIO.

Instances
MonadJSM JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> JSM a Source #

MonadJSM m => MonadJSM (MaybeT m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> MaybeT m a Source #

MonadJSM m => MonadJSM (ListT m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ListT m a Source #

MonadJSM m => MonadJSM (IdentityT m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> IdentityT m a Source #

MonadJSM m => MonadJSM (ExceptT e m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ExceptT e m a Source #

(Error e, MonadJSM m) => MonadJSM (ErrorT e m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ErrorT e m a Source #

MonadJSM m => MonadJSM (StateT s m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a Source #

MonadJSM m => MonadJSM (StateT s m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a Source #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a Source #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a Source #

MonadJSM m => MonadJSM (ContT r m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ContT r m a Source #

MonadJSM m => MonadJSM (ReaderT r m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ReaderT r m a Source #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a Source #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a Source #

liftJSM :: MonadJSM m => JSM a -> m a Source #

The liftJSM is to JSM what liftIO is to IO. When using GHCJS it is liftIO.

Running JavaScript in a JavaScript context

askJSM :: MonadJSM m => m JSContextRef Source #

Gets the JavaScript context from the monad

runJSM :: MonadIO m => JSM a -> JSContextRef -> m a Source #

Runs a JSM JavaScript function in a given JavaScript context.

runJSaddle :: MonadIO m => JSContextRef -> JSM a -> m a Source #

Alternative version of runJSM

Syncronizing with the JavaScript context

syncPoint :: JSM () Source #

Forces execution of pending asyncronous code

syncAfter :: JSM a -> JSM a Source #

Forces execution of pending asyncronous code after performing f

waitForAnimationFrame :: JSM Double Source #

On GHCJS this is waitForAnimationFrame. On GHC it will delay the execution of the current batch of asynchronous command when they are sent to JavaScript. It will not delay the Haskell code execution. The time returned will be based on the Haskell clock (not the JavaScript clock).

nextAnimationFrame :: (Double -> JSM a) -> JSM a Source #

Tries to executes the given code in the next animation frame callback. Avoid synchronous opperations where possible.

Exception Handling

catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a #

Provide a handler for exceptions thrown during execution of the first action. Note that type of the type of the argument to the handler will constrain which exceptions are caught. See Control.Exception's catch.

bracket :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b #

Generalized abstracted pattern of safe resource acquisition and release in the face of errors. The first action "acquires" some value, which is "released" by the second action at the end. The third action "uses" the value and its result is the result of the bracket.

If an error is thrown during the use, the release still happens before the error is rethrown.

Note that this is essentially a type-specialized version of generalBracket. This function has a more common signature (matching the signature from Control.Exception), and is often more convenient to use. By contrast, generalBracket is more expressive, allowing us to implement other functions like bracketOnError.