jsaddle-0.9.2.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 # 

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 # 

Methods

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

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

MonadFix JSM Source # 

Methods

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

Applicative JSM Source # 

Methods

pure :: a -> JSM a #

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

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

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

MonadIO JSM Source # 

Methods

liftIO :: IO a -> JSM a #

MonadRef JSM Source # 

Associated Types

type Ref (JSM :: * -> *) :: * -> * #

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 # 

Methods

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

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

MonadJSM JSM Source # 

Methods

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

MakeArgs arg => MakeArgs (JSM arg) Source # 

Methods

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

type Ref JSM Source # 
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 # 

Methods

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

MonadJSM m => MonadJSM (ListT m) Source # 

Methods

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

MonadJSM m => MonadJSM (MaybeT m) Source # 

Methods

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

MonadJSM m => MonadJSM (IdentityT * m) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

MonadJSM m => MonadJSM (ContT * r m) Source # 

Methods

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

MonadJSM m => MonadJSM (ReaderT * r m) Source # 

Methods

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

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

Methods

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

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

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 :: Exception e => JSM b -> (e -> JSM b) -> JSM b Source #

Wrapped version of catch that runs in a MonadIO that works a bit better with JSM

bracket :: JSM a -> (a -> JSM b) -> (a -> JSM c) -> JSM c Source #

Wrapped version of bracket that runs in a MonadIO that works a bit better with JSM