jsaddle-0.9.9.0: Interface for JavaScript that works with GHCJS and GHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Javascript.JSaddle.Types

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

Instances details
MonadFail JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

fail :: String -> JSM a #

MonadFix JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

MonadIO JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftIO :: IO a -> 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 #

Functor JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

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

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 #

MonadCatch JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

MonadMask JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

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

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

MonadThrow JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

throwM :: (HasCallStack, Exception e) => e -> JSM a #

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 JSCallAsFunction Source # 
Instance details

Defined in Language.Javascript.JSaddle.Object

MonadJSM JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

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 #

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 () #

MonadUnliftIO JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

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

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

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 function 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 #

type Ref JSM Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Ref JSM = Ref IO

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

Nothing

Methods

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

default liftJSM' :: (MonadJSM m', MonadTrans t, m ~ t m') => JSM a -> m a Source #

Instances

Instances details
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 (ExceptT e m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ExceptT e 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 (ReaderT r m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ReaderT r 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 #

(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.

Pure GHCJS functions

newtype GHCJSPure a Source #

Type we can give to functions that are pure when using ghcjs, but live in JSM when using jsaddle.

Some functions that can be pure in GHCJS cannot be implemented in a pure way in JSaddle (because we need to know the JSContextRef). Instead we implement versions of these functions in that return `GHCJSPure a` instead of a. To call them in a way that will work when compiling with GHCJS use ghcjsPure.

Constructors

GHCJSPure (JSM a) 

ghcjsPure :: GHCJSPure a -> JSM a Source #

Used when you want to call a functions that is pure in GHCJS, but lives in the JSM in jsaddle.

ghcjsPureMap :: (a -> b) -> GHCJSPure a -> GHCJSPure b Source #

JavaScript Value Types

newtype JSVal Source #

Constructors

JSVal (IORef JSValueRef) 

Instances

Instances details
NFData JSVal Source # 
Instance details

Defined in GHCJS.Prim.Internal

Methods

rnf :: JSVal -> () #

FromJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal

PFromJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal.Pure

PToJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal.Pure

Methods

pToJSVal :: JSVal -> JSVal Source #

ToJSVal JSVal Source #

If we already have a JSVal we are fine

Instance details

Defined in Language.Javascript.JSaddle.Value

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 JSVal Source #

A single JSVal can be used as the argument list

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs JSCallAsFunction Source # 
Instance details

Defined in Language.Javascript.JSaddle.Object

MakeObject JSVal Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

class IsJSVal a where Source #

Minimal complete definition

Nothing

Methods

jsval_ :: a -> GHCJSPure JSVal Source #

newtype SomeJSArray (m :: MutabilityType s) Source #

Constructors

SomeJSArray JSVal 

Instances

Instances details
IsJSVal (SomeJSArray m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

newtype Object Source #

See Object

Constructors

Object JSVal 

Instances

Instances details
ToJSVal Object Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

MakeObject Object Source #

If we already have a Object we are fine

Instance details

Defined in Language.Javascript.JSaddle.Classes.Internal

newtype JSString Source #

A wrapper around a JavaScript string

Constructors

JSString Text 

Instances

Instances details
FromJSON JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

ToJSON JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Data JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Methods

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

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

toConstr :: JSString -> Constr #

dataTypeOf :: JSString -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Monoid JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Semigroup JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

IsList JSString Source # 
Instance details

Defined in Data.JSString

Associated Types

type Item JSString #

Read JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Show JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

NFData JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Methods

rnf :: JSString -> () #

Eq JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

Ord JSString Source # 
Instance details

Defined in Data.JSString.Internal.Type

FromJSVal JSString Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSString Source #

Makes a JavaScript string

Instance details

Defined in Language.Javascript.JSaddle.Value

FromJSString JSString Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSString JSString Source #

If we already have a JSString we are fine

Instance details

Defined in Language.Javascript.JSaddle.Value

IsJSVal JSString Source # 
Instance details

Defined in GHCJS.Internal.Types

type Item JSString Source # 
Instance details

Defined in Data.JSString

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.

Debugging

type JSadddleHasCallStack = () :: Constraint Source #

Like HasCallStack, but only when jsaddle cabal flag check-unchecked is set

Sync JSM

syncPoint :: JSM () Source #

Forces execution of pending asyncronous code

syncAfter :: JSM a -> JSM a Source #

Forces execution of pending asyncronous code after performing f

JavaScript Context Commands

data MutabilityType s Source #

Constructors

Mutable_ s 
Immutable_ s 
STMutable s 

newtype JSValueForSend Source #

Wrapper used when sending a JSVal to the JavaScript context

Instances

Instances details
FromJSON JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep JSValueForSend :: Type -> Type #

Show JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

NFData JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSValueForSend -> () #

type Rep JSValueForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep JSValueForSend = D1 ('MetaData "JSValueForSend" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'True) (C1 ('MetaCons "JSValueForSend" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueRef)))

newtype JSStringForSend Source #

Wrapper used when sending a JString to the JavaScript context

Constructors

JSStringForSend Text 

Instances

Instances details
FromJSON JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep JSStringForSend :: Type -> Type #

Show JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

NFData JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSStringForSend -> () #

type Rep JSStringForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep JSStringForSend = D1 ('MetaData "JSStringForSend" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'True) (C1 ('MetaCons "JSStringForSend" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype JSObjectForSend Source #

Wrapper used when sending a Object to the JavaScript context

Instances

Instances details
FromJSON JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep JSObjectForSend :: Type -> Type #

Show JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

NFData JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSObjectForSend -> () #

type Rep JSObjectForSend Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep JSObjectForSend = D1 ('MetaData "JSObjectForSend" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'True) (C1 ('MetaCons "JSObjectForSend" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)))

data AsyncCommand Source #

Command sent to a JavaScript context for execution asynchronously

Instances

Instances details
FromJSON AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep AsyncCommand :: Type -> Type #

Show AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

NFData AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: AsyncCommand -> () #

type Rep AsyncCommand Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep AsyncCommand = D1 ('MetaData "AsyncCommand" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'False) ((((C1 ('MetaCons "FreeRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "FreeRefs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "SetPropertyByName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: (C1 ('MetaCons "SetPropertyAtIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: C1 ('MetaCons "StringToValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))))) :+: ((C1 ('MetaCons "NumberToValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "JSONValueToValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: (C1 ('MetaCons "GetPropertyByName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: (C1 ('MetaCons "GetPropertyAtIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: C1 ('MetaCons "CallAsFunction" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JSValueForSend]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))))))) :+: (((C1 ('MetaCons "CallAsConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JSValueForSend]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: C1 ('MetaCons "NewEmptyObject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: (C1 ('MetaCons "NewAsyncCallback" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: (C1 ('MetaCons "NewSyncCallback" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "FreeCallback" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))))) :+: ((C1 ('MetaCons "NewArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JSValueForSend]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "EvaluateScript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))) :+: (C1 ('MetaCons "SyncWithAnimationFrame" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: (C1 ('MetaCons "StartSyncBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndSyncBlock" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Command Source #

Command sent to a JavaScript context for execution synchronously

Instances

Instances details
FromJSON Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep Command :: Type -> Type #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Show Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

NFData Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: Command -> () #

type Rep Command Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep Command = D1 ('MetaData "Command" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'False) (((C1 ('MetaCons "DeRefVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: (C1 ('MetaCons "ValueToBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "ValueToNumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)))) :+: (C1 ('MetaCons "ValueToString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: (C1 ('MetaCons "ValueToJSON" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "ValueToJSONValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend))))) :+: ((C1 ('MetaCons "IsNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: (C1 ('MetaCons "IsUndefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)) :+: C1 ('MetaCons "StrictEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend)))) :+: (C1 ('MetaCons "InstanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueForSend) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend)) :+: (C1 ('MetaCons "PropertyNames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSObjectForSend)) :+: C1 ('MetaCons "Sync" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Batch Source #

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

Instances

Instances details
FromJSON Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep Batch :: Type -> Type #

Methods

from :: Batch -> Rep Batch x #

to :: Rep Batch x -> Batch #

Show Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

showsPrec :: Int -> Batch -> ShowS #

show :: Batch -> String #

showList :: [Batch] -> ShowS #

NFData Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: Batch -> () #

type Rep Batch Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

data Result Source #

Result of a Command returned from the JavaScript context

Instances

Instances details
FromJSON Result Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON Result Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic Result Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep Result :: Type -> Type #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

Show Result Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep Result Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep Result = D1 ('MetaData "Result" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'False) (((C1 ('MetaCons "DeRefValResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "ValueToBoolResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "ValueToNumberResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :+: (C1 ('MetaCons "ValueToStringResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringReceived)) :+: (C1 ('MetaCons "ValueToJSONResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSStringReceived)) :+: C1 ('MetaCons "ValueToJSONValueResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) :+: ((C1 ('MetaCons "IsNullResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "IsUndefinedResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "StrictEqualResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: ((C1 ('MetaCons "InstanceOfResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "PropertyNamesResult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JSStringReceived]))) :+: (C1 ('MetaCons "ThrowJSValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueReceived)) :+: C1 ('MetaCons "SyncResult" 'PrefixI 'False) (U1 :: Type -> Type)))))

data BatchResults Source #

Instances

Instances details
FromJSON BatchResults Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON BatchResults Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic BatchResults Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep BatchResults :: Type -> Type #

Show BatchResults Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep BatchResults Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

data Results Source #

Instances

Instances details
FromJSON Results Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

ToJSON Results Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Generic Results Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

Associated Types

type Rep Results :: Type -> Type #

Methods

from :: Results -> Rep Results x #

to :: Rep Results x -> Results #

Show Results Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep Results Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

type Rep Results = D1 ('MetaData "Results" "Language.Javascript.JSaddle.Types" "jsaddle-0.9.9.0-1RwLwsU7nUs2azdmgbzhIa" 'False) ((C1 ('MetaCons "BatchResults" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BatchResults)) :+: C1 ('MetaCons "Duplicate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "Callback" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BatchResults) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueReceived))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueReceived) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JSValueReceived) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [JSValueReceived])))) :+: C1 ('MetaCons "ProtocolError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))