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

Safe HaskellNone
LanguageHaskell2010

Language.Javascript.JSaddle.Types

Contents

Description

 

Synopsis

JavaScript Context

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.

The JSM Monad

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 #

MonadJSM JSM Source # 

Methods

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

MakeArgs arg => MakeArgs (JSM arg) Source # 

Methods

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

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

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

Minimal complete definition

liftJSM'

Methods

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

Instances

MonadJSM JSM Source # 

Methods

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

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

Methods

liftJSM' :: JSM a -> ReaderT * e 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.

JavaScript Value Types

newtype Nullable a Source #

Constructors

Nullable a 

type JSCallAsFunction Source #

Arguments

 = JSVal

Function object

-> JSVal

this

-> [JSVal]

Function arguments

-> JSM ()

Only () (aka JSUndefined) can be returned because the function may need to be executed in a different thread. If you need to get a value out pass in a continuation function as an argument and invoke it from haskell.

Type used for Haskell functions called from JavaScript.

JavaScript Context Commands

data AsyncCommand Source #

Command sent to a JavaScript context for execution asynchronously

Instances

Show AsyncCommand Source # 
Generic AsyncCommand Source # 

Associated Types

type Rep AsyncCommand :: * -> * #

ToJSON AsyncCommand Source # 
FromJSON AsyncCommand Source # 
type Rep AsyncCommand Source # 
type Rep AsyncCommand = D1 (MetaData "AsyncCommand" "Language.Javascript.JSaddle.Types" "jsaddle-0.5.1.0-9MWZA7Wz8qdIZLURWC6nfM" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FreeRef" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) ((:+:) (C1 (MetaCons "SetPropertyByName" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSStringForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) (C1 (MetaCons "SetPropertyAtIndex" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))))) ((:+:) ((:+:) (C1 (MetaCons "StringToValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSStringForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))) (C1 (MetaCons "NumberToValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) ((:+:) (C1 (MetaCons "GetPropertyByName" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSStringForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) (C1 (MetaCons "GetPropertyAtIndex" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))))))) ((:+:) ((:+:) (C1 (MetaCons "CallAsFunction" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [JSValueForSend])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) ((:+:) (C1 (MetaCons "CallAsConstructor" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [JSValueForSend])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) (C1 (MetaCons "NewEmptyObject" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) ((:+:) ((:+:) (C1 (MetaCons "NewCallback" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) (C1 (MetaCons "NewArray" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [JSValueForSend])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))))) ((:+:) (C1 (MetaCons "EvaluateScript" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSStringForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))) (C1 (MetaCons "SyncWithAnimationFrame" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))))))

data Command Source #

Command sent to a JavaScript context for execution synchronously

Instances

Show Command Source # 
Generic Command Source # 

Associated Types

type Rep Command :: * -> * #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

ToJSON Command Source # 
FromJSON Command Source # 
type Rep Command Source # 
type Rep Command = D1 (MetaData "Command" "Language.Javascript.JSaddle.Types" "jsaddle-0.5.1.0-9MWZA7Wz8qdIZLURWC6nfM" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DeRefVal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) (C1 (MetaCons "ValueToBool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))) ((:+:) (C1 (MetaCons "ValueToNumber" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) ((:+:) (C1 (MetaCons "ValueToString" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) (C1 (MetaCons "ValueToJSON" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))))) ((:+:) ((:+:) (C1 (MetaCons "IsNull" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) ((:+:) (C1 (MetaCons "IsUndefined" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend))) (C1 (MetaCons "StrictEqual" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)))))) ((:+:) (C1 (MetaCons "InstanceOf" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSValueForSend)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend)))) ((:+:) (C1 (MetaCons "PropertyNames" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSObjectForSend))) (C1 (MetaCons "Sync" PrefixI False) U1)))))

data Batch Source #

Batch of commands that can be sent together to the JavaScript context

Constructors

Batch [AsyncCommand] Command Bool