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

Language.Javascript.JSaddle

Description

This package provides an EDSL for calling JavaScript that can be used both from GHCJS and GHC. When using GHC the application is run using Warp and WebSockets to drive a small JavaScript helper.

Synopsis

JSaddle EDSL

The JSM monad gives us the context for evaluation. In keeping with JavaScript the EDSL has

  • Weakish typing - type classes are used to convert to JSValueRef and Object types
  • Strict evaluation - function in the JSM monad can be passed in place of a value and will evaluated and converted to JSValueRef or Object and then passed on to JavaScript

JSaddle should be used to write wrappers for JavaScript libraries that provide more type safety.

Code Examples

The code examples in this documentation are executed with a runjs function that executes the example code in the JSM monad and converts the result to Text with valToText. It also catches unhandled exceptions with catch. The source code can be found in tests/TestJSaddle.hs

Where it makes sense code examples are given in two forms. One that uses eval to run a purely JavaScript version and one that uses more of the JSaddle EDSL feature being demonstrated.

Calling Haskell from JavaScript

You can call back into Haskell from JavaScript using fun to convert a Haskell function in the JSM monad into a javascript value.

GHCJS Support

When built with ghcjs the code works using JavaScript FFI by default.

GHC Support

When built with ghc the code runs a small Warp server that provides index.html and jsaddle.js files. When a browser is connected the code in jsaddle.js will open a WebSockets connection to the server and the server will run the Haskell code. The JSaddle parts will be executed by sending commands back to the browser.

Modules

newtype Function Source #

Constructors

Function 

Instances

Instances details
ToJSVal Function Source # 
Instance details

Defined in Language.Javascript.JSaddle.Object

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

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

class MakeArgs this where Source #

Anything that can be used to make a list of JavaScript value references for use as function arguments

Methods

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

Instances

Instances details
MakeArgs Value Source #

Makes an argument list with just a single JSON value

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

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

MakeArgs JSNull Source #

Makes an argument list with just a single null JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs JSValue Source #

Makes an argument list with just a single JavaScript value from a JSValue ADT.

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs Text Source #

Makes an argument list with just a single JavaScript string

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs () Source #

This allows us to pass no arguments easily (altenative would be to use []::[JSVal]).

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs Bool Source #

Makes an argument list with just a single JavaScript boolean value

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

MakeArgs Double Source #

Makes an argument list with just a single JavaScript number

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

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

Defined in Language.Javascript.JSaddle.Classes.Internal

Methods

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

ToJSVal arg => MakeArgs [arg] Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

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

(ToJSVal arg1, ToJSVal arg2) => MakeArgs (arg1, arg2) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

makeArgs :: (arg1, arg2) -> JSM [JSVal] Source #

(ToJSVal arg1, ToJSVal arg2, ToJSVal arg3) => MakeArgs (arg1, arg2, arg3) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

makeArgs :: (arg1, arg2, arg3) -> JSM [JSVal] Source #

(ToJSVal arg1, ToJSVal arg2, ToJSVal arg3, ToJSVal arg4) => MakeArgs (arg1, arg2, arg3, arg4) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

makeArgs :: (arg1, arg2, arg3, arg4) -> JSM [JSVal] Source #

(ToJSVal arg1, ToJSVal arg2, ToJSVal arg3, ToJSVal arg4, ToJSVal arg5) => MakeArgs (arg1, arg2, arg3, arg4, arg5) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

makeArgs :: (arg1, arg2, arg3, arg4, arg5) -> JSM [JSVal] Source #

(ToJSVal arg1, ToJSVal arg2, ToJSVal arg3, ToJSVal arg4, ToJSVal arg5, ToJSVal arg6) => MakeArgs (arg1, arg2, arg3, arg4, arg5, arg6) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Arguments

Methods

makeArgs :: (arg1, arg2, arg3, arg4, arg5, arg6) -> JSM [JSVal] Source #

class ToJSVal a where Source #

Minimal complete definition

Nothing

Methods

toJSVal :: a -> JSM JSVal Source #

default toJSVal :: (Generic a, GToJSVal (Rep a ())) => a -> JSM JSVal Source #

toJSValListOf :: [a] -> JSM JSVal Source #

Instances

Instances details
ToJSVal Value Source #

Makes a JSON value

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Int16 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Int32 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Int8 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Word16 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Word32 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Word8 Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSString Source #

Makes a JavaScript string

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSVal Source #

If we already have a JSVal we are fine

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Function 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

ToJSVal Object Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSNull Source #

Makes a null JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSUndefined Source #

Makes an undefined JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal JSValue Source #

Makes a JavaScript value from a JSValue ADT.

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Text Source #

Makes a JavaScript string

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Bool Source #

Make a JavaScript boolean value

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Char Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Double Source #

Makes a JavaScript number

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Float Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Int Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal Word Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

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

ToJSVal a => ToJSVal (Maybe a) Source #

Makes a JSVal or null JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSVal a => ToJSVal [a] Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

toJSVal :: [a] -> JSM JSVal Source #

toJSValListOf :: [[a]] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b) => ToJSVal (a, b) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b) -> JSM JSVal Source #

toJSValListOf :: [(a, b)] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b, ToJSVal c) => ToJSVal (a, b, c) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b, c) -> JSM JSVal Source #

toJSValListOf :: [(a, b, c)] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b, ToJSVal c, ToJSVal d) => ToJSVal (a, b, c, d) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b, c, d) -> JSM JSVal Source #

toJSValListOf :: [(a, b, c, d)] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b, ToJSVal c, ToJSVal d, ToJSVal e) => ToJSVal (a, b, c, d, e) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b, c, d, e) -> JSM JSVal Source #

toJSValListOf :: [(a, b, c, d, e)] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b, ToJSVal c, ToJSVal d, ToJSVal e, ToJSVal f) => ToJSVal (a, b, c, d, e, f) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b, c, d, e, f) -> JSM JSVal Source #

toJSValListOf :: [(a, b, c, d, e, f)] -> JSM JSVal Source #

(ToJSVal a, ToJSVal b, ToJSVal c, ToJSVal d, ToJSVal e, ToJSVal f, ToJSVal g) => ToJSVal (a, b, c, d, e, f, g) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

toJSVal :: (a, b, c, d, e, f, g) -> JSM JSVal Source #

toJSValListOf :: [(a, b, c, d, e, f, g)] -> JSM JSVal Source #

class PToJSVal a where Source #

Methods

pToJSVal :: a -> JSVal Source #

Instances

Instances details
PToJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal.Pure

Methods

pToJSVal :: JSVal -> JSVal Source #

PToJSVal MutableArrayBuffer Source # 
Instance details

Defined in JavaScript.TypedArray.ArrayBuffer.Internal

PToJSVal Bool Source # 
Instance details

Defined in GHCJS.Marshal.Pure

Methods

pToJSVal :: Bool -> JSVal Source #

class PFromJSVal a where Source #

Methods

pFromJSVal :: JSVal -> a Source #

Instances

Instances details
PFromJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal.Pure

PFromJSVal MutableArrayBuffer Source # 
Instance details

Defined in JavaScript.TypedArray.ArrayBuffer.Internal

PFromJSVal () Source # 
Instance details

Defined in GHCJS.Marshal.Pure

Methods

pFromJSVal :: JSVal -> () Source #

class FromJSVal a where Source #

Minimal complete definition

Nothing

Methods

fromJSVal :: JSVal -> JSM (Maybe a) Source #

default fromJSVal :: (Generic a, GFromJSVal (Rep a ())) => JSVal -> JSM (Maybe a) Source #

fromJSValUnchecked :: JSVal -> JSM a Source #

fromJSValListOf :: JSVal -> JSM (Maybe [a]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [a] Source #

Instances

Instances details
FromJSVal Value Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Int16 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Int32 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Int8 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Word16 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Word32 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Word8 Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal JSString Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

FromJSVal JSVal Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Text Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

FromJSVal () Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Bool Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Char Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

FromJSVal Double Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Float Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Int Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal Word Source # 
Instance details

Defined in GHCJS.Marshal

FromJSVal a => FromJSVal (Maybe a) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

FromJSVal a => FromJSVal [a] Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

(FromJSVal a, FromJSVal b) => FromJSVal (a, b) Source # 
Instance details

Defined in GHCJS.Marshal

(FromJSVal a, FromJSVal b, FromJSVal c) => FromJSVal (a, b, c) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c)] Source #

(FromJSVal a, FromJSVal b, FromJSVal c, FromJSVal d) => FromJSVal (a, b, c, d) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c, d)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c, d) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c, d)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c, d)] Source #

(FromJSVal a, FromJSVal b, FromJSVal c, FromJSVal d, FromJSVal e) => FromJSVal (a, b, c, d, e) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c, d, e)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c, d, e) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c, d, e)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c, d, e)] Source #

(FromJSVal a, FromJSVal b, FromJSVal c, FromJSVal d, FromJSVal e, FromJSVal f) => FromJSVal (a, b, c, d, e, f) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c, d, e, f)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c, d, e, f) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c, d, e, f)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c, d, e, f)] Source #

(FromJSVal a, FromJSVal b, FromJSVal c, FromJSVal d, FromJSVal e, FromJSVal f, FromJSVal g) => FromJSVal (a, b, c, d, e, f, g) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c, d, e, f, g)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c, d, e, f, g) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c, d, e, f, g)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c, d, e, f, g)] Source #

(FromJSVal a, FromJSVal b, FromJSVal c, FromJSVal d, FromJSVal e, FromJSVal f, FromJSVal g, FromJSVal h) => FromJSVal (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in GHCJS.Marshal

Methods

fromJSVal :: JSVal -> JSM (Maybe (a, b, c, d, e, f, g, h)) Source #

fromJSValUnchecked :: JSVal -> JSM (a, b, c, d, e, f, g, h) Source #

fromJSValListOf :: JSVal -> JSM (Maybe [(a, b, c, d, e, f, g, h)]) Source #

fromJSValUncheckedListOf :: JSVal -> JSM [(a, b, c, d, e, f, g, h)] Source #

class ToJSVal a => ToJSString a where Source #

Anything that can be used to make a JavaScript string

Methods

toJSString :: a -> JSString Source #

Instances

Instances details
ToJSString JSString Source #

If we already have a JSString we are fine

Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSString Text Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

ToJSString String Source # 
Instance details

Defined in Language.Javascript.JSaddle.Value

class FromJSVal a => FromJSString a where Source #

Anything that can be constructed from a JavaScript string

Methods

fromJSString :: JSString -> a Source #

class MakeObject this where Source #

Anything that can be used to make a JavaScript object reference

Methods

makeObject :: this -> JSM Object Source #

Instances

Instances details
MakeObject JSVal 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

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 #

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

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

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

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

type JSF = forall o. MakeObject o => IndexPreservingGetter o (JSM JSVal) Source #

Java script function applications have this type

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.

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

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

newtype SomeJSArray (m :: MutabilityType s) Source #

Constructors

SomeJSArray JSVal 

Instances

Instances details
IsJSVal (SomeJSArray m) Source # 
Instance details

Defined in Language.Javascript.JSaddle.Types

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

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

Constructors

JSNull

Type that represents a value that can only be null. Haskell of course has no null so we are adding this type.

Instances

Instances details
ToJSVal JSNull Source #

Makes a null JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

MakeArgs JSNull Source #

Makes an argument list with just a single null JavaScript value

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

type JSUndefined Source #

Arguments

 = ()

A type that can only be undefined in JavaScript. Using () because functions in JavaScript that have no return, impicitly return undefined. type JSBool = Bool -- ^ JavaScript boolean values map the Bool haskell type. type JSNumber = Double -- ^ A number in JavaScript maps nicely to Double. type JSString = Text -- ^ JavaScript strings can be represented with the Haskell Text type.

data JSValue Source #

An algebraic data type that can represent a JavaScript value. Any JavaScriptCore JSVal can be converted into this type.

Constructors

ValNull

null

ValUndefined

undefined

ValBool Bool

true or false

ValNumber Double

a number

ValString Text

a string

ValObject Object

an object

Instances

Instances details
ToJSVal JSValue Source #

Makes a JavaScript value from a JSValue ADT.

Instance details

Defined in Language.Javascript.JSaddle.Value

MakeArgs JSValue Source #

Makes an argument list with just a single JavaScript value from a JSValue ADT.

Instance details

Defined in Language.Javascript.JSaddle.Value

Methods

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

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) 

class IsJSVal a where Source #

Minimal complete definition

Nothing

Methods

jsval_ :: a -> GHCJSPure JSVal Source #

newtype Nullable a Source #

Constructors

Nullable a 

type JSadddleHasCallStack = () :: Constraint Source #

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

data MutabilityType s Source #

Constructors

Mutable_ s 
Immutable_ s 
STMutable s 

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

array :: MakeArgs args => args -> JSM Object Source #

Make an JavaScript array from a list of values

>>> testJSaddle $ eval "['Hello', 'World'][1]"
World
>>> testJSaddle $ array ["Hello", "World"] !! 1
World
>>> testJSaddle $ eval "['Hello', null, undefined, true, 1]"
Hello,,,true,1
>>> testJSaddle $ array ("Hello", JSNull, (), True, 1.0::Double)
Hello,,,true,1

function Source #

Arguments

:: JSCallAsFunction

Haskell function to call

-> JSM Function

Returns a JavaScript function object that will call the Haskell one when it is called

Make a JavaScript function object that wraps a Haskell function. Calls made to the function will be synchronous where possible (on GHCJS it uses on syncCallback2 with ContinueAsync).

(<##) infixr 1 Source #

Arguments

:: (MakeObject this, ToJSVal val) 
=> this

Object to set the property on

-> Int

Index of the property to set

-> val

Value to set it to

-> JSM () 

Set a JavaScript property

>>> testJSaddle $ eval "var j = {}; j[6] = 1; j[6]"
1
>>> testJSaddle $ do {j <- obj; (j <## 6) 1; j!!6}
1

(<#) infixr 1 Source #

Arguments

:: (MakeObject this, ToJSString name, ToJSVal val) 
=> this

Object to set the property on

-> name

Name of the property to set

-> val

Value to set it to

-> JSM () 

Set a JavaScript property

>>> testJSaddle $ eval "var j = {}; j.x = 1; j.x"
1
>>> testJSaddle $ do {j <- obj; (j <# "x") 1; j!"x"}
1

(!) Source #

Arguments

:: (MakeObject this, ToJSString name) 
=> this

Object to look on

-> name

Name of the property to find

-> JSM JSVal

Property reference

Lookup a property based on its name.

>>> testJSaddle $ eval "'Hello World'.length"
11
>>> testJSaddle $ val "Hello World" ! "length"
11

bracket :: (HasCallStack, 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.

new :: (MakeObject constructor, MakeArgs args) => constructor -> args -> JSM JSVal Source #

Use this to create a new JavaScript object

If you pass more than 7 arguments to a constructor for a built in JavaScript type (like Date) then this function will fail.

>>> testJSaddle $ new (jsg "Date") (2013, 1, 1)
Fri Feb 01 2013 00:00:00 GMT+... (...)

catch :: (MonadCatch m, HasCallStack, 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.

(!!) Source #

Arguments

:: MakeObject this 
=> this

Object to look on

-> Int

Index of the property to lookup

-> JSM JSVal

Property reference

Lookup a property based on its index.

>>> testJSaddle $ eval "'Hello World'[6]"
W
>>> testJSaddle $ val "Hello World" !! 6
W

create :: JSM Object Source #

create an empty object

(#) :: (MakeObject this, ToJSString name, MakeArgs args) => this -> name -> args -> JSM JSVal infixr 2 Source #

Call a JavaScript function

>>> testJSaddle $ eval "'Hello World'.indexOf('World')"
6
>>> testJSaddle $ val "Hello World" # "indexOf" $ ["World"]
6

eval Source #

Arguments

:: ToJSString script 
=> script

JavaScript to evaluate

-> JSM JSVal 

Evaluates a script (like eval in java script)

>>> testJSaddle $ eval "1+1"
2

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

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

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

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.

js Source #

Arguments

:: (MakeObject s, ToJSString name) 
=> name

Name of the property to find

-> IndexPreservingGetter s (JSM JSVal) 

Makes a getter for a particular property name.

js name = to (!name)
>>> testJSaddle $ eval "'Hello World'.length"
11
>>> testJSaddle $ val "Hello World" ^. js "length"
11

jss Source #

Arguments

:: (ToJSString name, ToJSVal val) 
=> name

Name of the property to find

-> val 
-> forall o. MakeObject o 
=> IndexPreservingGetter o (JSM ()) 

Makes a setter for a particular property name.

jss name = to (<#name)
>>> testJSaddle $ eval "'Hello World'.length = 12"
12
>>> testJSaddle $ val "Hello World" ^. jss "length" 12
undefined

jsf :: (ToJSString name, MakeArgs args) => name -> args -> JSF Source #

Handy way to call a function

jsf name = to (\o -> o # name $ args)
>>> testJSaddle $ val "Hello World" ^. jsf "indexOf" ["World"]
6

js0 :: ToJSString name => name -> JSF Source #

Handy way to call a function that expects no arguments

js0 name = jsf name ()
>>> testJSaddle $ val "Hello World" ^. js0 "toLowerCase"
hello world

js1 :: (ToJSString name, ToJSVal a0) => name -> a0 -> JSF Source #

Handy way to call a function that expects one argument

js1 name a0 = jsf name [a0]
>>> testJSaddle $ val "Hello World" ^. js1 "indexOf" "World"
6

js2 :: (ToJSString name, ToJSVal a0, ToJSVal a1) => name -> a0 -> a1 -> JSF Source #

Handy way to call a function that expects two arguments

js3 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2) => name -> a0 -> a1 -> a2 -> JSF Source #

Handy way to call a function that expects three arguments

js4 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3) => name -> a0 -> a1 -> a2 -> a3 -> JSF Source #

Handy way to call a function that expects four arguments

js5 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3, ToJSVal a4) => name -> a0 -> a1 -> a2 -> a3 -> a4 -> JSF Source #

Handy way to call a function that expects five arguments

jsg :: ToJSString a => a -> JSM JSVal Source #

Handy way to get and hold onto a reference top level javascript

>>> testJSaddle $ eval "w = console; w.log('Hello World')"
undefined
>>> testJSaddle $ do w <- jsg "console"; w ^. js1 "log" "Hello World"
undefined

jsgf :: (ToJSString name, MakeArgs args) => name -> args -> JSM JSVal Source #

Handy way to call a function

jsgf name = jsg name . to (# args)
>>> testJSaddle $ eval "globalFunc = function (x) {return x.length;}"
function (x) {return x.length;}
>>> testJSaddle $ jsgf "globalFunc" ["World"]
5

jsg0 :: ToJSString name => name -> JSM JSVal Source #

Handy way to call a function that expects no arguments

jsg0 name = jsgf name ()
>>> testJSaddle $ jsg0 "globalFunc" >>= valToText
A JavaScript exception was thrown! (may not reach Haskell code)
TypeError:...undefine...

jsg1 :: (ToJSString name, ToJSVal a0) => name -> a0 -> JSM JSVal Source #

Handy way to call a function that expects one argument

jsg1 name a0 = jsgf name [a0]
>>> testJSaddle $ jsg1 "globalFunc" "World"
5

jsg2 :: (ToJSString name, ToJSVal a0, ToJSVal a1) => name -> a0 -> a1 -> JSM JSVal Source #

Handy way to call a function that expects two arguments

jsg3 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2) => name -> a0 -> a1 -> a2 -> JSM JSVal Source #

Handy way to call a function that expects three arguments

jsg4 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3) => name -> a0 -> a1 -> a2 -> a3 -> JSM JSVal Source #

Handy way to call a function that expects four arguments

jsg5 :: (ToJSString name, ToJSVal a0, ToJSVal a1, ToJSVal a2, ToJSVal a3, ToJSVal a4) => name -> a0 -> a1 -> a2 -> a3 -> a4 -> JSM JSVal Source #

Handy way to call a function that expects five arguments

(##) :: (MakeObject this, MakeArgs args) => this -> Int -> args -> JSM JSVal infixr 2 Source #

Call a JavaScript function

>>> testJSaddle $ eval "something = {}; something[6]=function (x) {return x.length;}; something[6]('World')"
5
>>> testJSaddle $ jsg "something" ## 6 $ ["World"]
5

call :: (MakeObject f, MakeObject this, MakeArgs args) => f -> this -> args -> JSM JSVal Source #

Call function with a given this. In most cases you should use #.

>>> testJSaddle $ eval "(function(){return this;}).apply('Hello', [])"
Hello
>>> testJSaddle $ do { test <- eval "(function(){return this;})"; call test (val "Hello") () }
Hello

obj :: JSM Object Source #

Make an empty object using the default constuctor

>>> testJSaddle $ eval "var a = {}; a.x = 'Hello'; a.x"
Hello
>>> testJSaddle $ do { a <- obj; (a <# "x") "Hello"; a ^. js "x" }
Hello

getProp :: JSString -> Object -> JSM JSVal Source #

get a property from an object. If accessing the property results in an exception, the exception is converted to a JSException. Since exception handling code prevents some optimizations in some JS engines, you may want to use unsafeGetProp instead

asyncFunction Source #

Arguments

:: JSCallAsFunction

Haskell function to call

-> JSM Function

Returns a JavaScript function object that will call the Haskell one when it is called

Make a JavaScript function object that wraps a Haskell function. Calls made to the function will be asynchronous.

fun :: JSCallAsFunction -> JSCallAsFunction Source #

Short hand ::JSCallAsFunction so a haskell function can be passed to a to a JavaScipt one.

>>> testJSaddle $ eval "(function(f) {f('Hello');})(function (a) {console.log(a)})"
undefined
>>> :{
 testJSaddle $ do
   result <- liftIO newEmptyMVar
   deRefVal $ call (eval "(function(f) {f('Hello');})") global [fun $ \ _ _ [arg1] -> do
        valToText arg1 >>= (liftIO . putMVar result)
        ]
   liftIO $ takeMVar result
:}
Hello

global :: Object Source #

JavaScript's global object

propertyNames :: MakeObject this => this -> JSM [JSString] Source #

Get a list containing the property names present on a given object >>> testJSaddle $ show . map strToText $ propertyNames obj [] >>> testJSaddle $ show . map strToText $ propertyNames (eval "({x:1, y:2})") ["x","y"]

properties :: MakeObject this => this -> JSM [JSVal] Source #

Get a list containing references to all the properties present on a given object

objCallAsFunction :: MakeArgs args => Object -> Object -> args -> JSM JSVal Source #

Call a JavaScript object as function. Consider using #.

objCallAsConstructor :: MakeArgs args => Object -> args -> JSM JSVal Source #

Call a JavaScript object as a constructor. Consider using new.

If you pass more than 7 arguments to a constructor for a built in JavaScript type (like Date) then this function will fail.

valToObject :: ToJSVal value => value -> JSM Object Source #

Given a JavaScript value get its object value. May throw JSException.

>>> testJSaddle $ (valToObject JSNull >>= valToText) `catch` \ (JSException e) -> valToText e
null
>>> testJSaddle $ (valToObject () >>= valToText) `catch` \ (JSException e) -> valToText e
undefined
>>> testJSaddle $ valToObject True
true
>>> testJSaddle $ valToObject False
false
>>> testJSaddle $ valToObject (1.0 :: Double)
1
>>> testJSaddle $ valToObject (0.0 :: Double)
0
>>> testJSaddle $ valToObject ""

>>> testJSaddle $ valToObject "1"
1

objGetPropertyByName Source #

Arguments

:: ToJSString name 
=> Object

object to find the property on.

-> name

name of the property.

-> JSM JSVal

returns the property value.

Get a property value given the object and the name of the property.

objGetPropertyAtIndex Source #

Arguments

:: Object

object to find the property on.

-> Int

index of the property.

-> JSM JSVal

returns the property value.

Get a property value given the object and the index of the property.

objSetPropertyByName Source #

Arguments

:: (ToJSString name, ToJSVal val) 
=> Object

object to set the property on.

-> name

name of the property.

-> val

new value to set the property to.

-> JSM () 

Set a property value given the object and the name of the property.

objSetPropertyAtIndex Source #

Arguments

:: ToJSVal val 
=> Object

object to find property on.

-> Int

index of the property.

-> val

new value to set the property to.

-> JSM () 

Set a property value given the object and the index of the property.

strToText :: JSString -> Text Source #

Convert a JavaScript string to a Haskell Text

textToStr :: Text -> JSString Source #

Convert a Haskell Text to a JavaScript string

showJSValue :: JSValue -> String Source #

Show a JSValue but just say "object" if the value is a JavaScript object.

valToBool :: ToJSVal value => value -> JSM Bool Source #

Given a JavaScript value get its boolean value. All values in JavaScript convert to bool.

>>> testJSaddle $ valToBool JSNull
false
>>> testJSaddle $ valToBool ()
false
>>> testJSaddle $ valToBool True
true
>>> testJSaddle $ valToBool False
false
>>> testJSaddle $ valToBool (1.0 :: Double)
true
>>> testJSaddle $ valToBool (0.0 :: Double)
false
>>> testJSaddle $ valToBool ""
false
>>> testJSaddle $ valToBool "1"
true

valToNumber :: ToJSVal value => value -> JSM Double Source #

Given a JavaScript value get its numeric value. May throw JSException.

>>> testJSaddle $ show <$> valToNumber JSNull
0.0
>>> testJSaddle $ show <$> valToNumber ()
NaN
>>> testJSaddle $ show <$> valToNumber True
1.0
>>> testJSaddle $ show <$> valToNumber False
0.0
>>> testJSaddle $ show <$> valToNumber (1.0 :: Double)
1.0
>>> testJSaddle $ show <$> valToNumber (0.0 :: Double)
0.0
>>> testJSaddle $ show <$> valToNumber ""
0.0
>>> testJSaddle $ show <$> valToNumber "1"
1.0

valToStr :: ToJSVal value => value -> JSM JSString Source #

Given a JavaScript value get its string value (as a JavaScript string). May throw JSException.

>>> testJSaddle $ strToText <$> valToStr JSNull
null
>>> testJSaddle $ strToText <$> valToStr ()
undefined
>>> testJSaddle $ strToText <$> valToStr True
true
>>> testJSaddle $ strToText <$> valToStr False
false
>>> testJSaddle $ strToText <$> valToStr (1.0 :: Double)
1
>>> testJSaddle $ strToText <$> valToStr (0.0 :: Double)
0
>>> testJSaddle $ strToText <$> valToStr ""

>>> testJSaddle $ strToText <$> valToStr "1"
1

valToText :: ToJSVal value => value -> JSM Text Source #

Given a JavaScript value get its string value (as a Haskell Text). May throw JSException.

>>> testJSaddle $ show <$> valToText JSNull
"null"
>>> testJSaddle $ show <$> valToText ()
"undefined"
>>> testJSaddle $ show <$> valToText True
"true"
>>> testJSaddle $ show <$> valToText False
"false"
>>> testJSaddle $ show <$> valToText (1.0 :: Double)
"1"
>>> testJSaddle $ show <$> valToText (0.0 :: Double)
"0"
>>> testJSaddle $ show <$> valToText ""
""
>>> testJSaddle $ show <$> valToText "1"
"1"

valToJSON :: ToJSVal value => value -> JSM JSString Source #

Given a JavaScript value get a JSON string value. May throw JSException.

>>> testJSaddle $ strToText <$> valToJSON JSNull
null
>>> testJSaddle $ strToText <$> valToJSON ()

>>> testJSaddle $ strToText <$> valToJSON True
true
>>> testJSaddle $ strToText <$> valToJSON False
false
>>> testJSaddle $ strToText <$> valToJSON (1.0 :: Double)
1
>>> testJSaddle $ strToText <$> valToJSON (0.0 :: Double)
0
>>> testJSaddle $ strToText <$> valToJSON ""
""
>>> testJSaddle $ strToText <$> valToJSON "1"
"1"
>>> testJSaddle $ strToText <$> (obj >>= valToJSON)
{}

val Source #

Arguments

:: ToJSVal value 
=> value

value to convert to a JavaScript value

-> JSM JSVal 

Convert to a JavaScript value (just an alias for toJSVal)

valNull :: JSVal Source #

A null JavaScript value

valIsNull :: ToJSVal value => value -> JSM Bool Source #

Test a JavaScript value to see if it is null

valUndefined :: JSVal Source #

An undefined JavaScript value

valIsUndefined :: ToJSVal value => value -> JSM Bool Source #

Test a JavaScript value to see if it is undefined

maybeNullOrUndefined :: ToJSVal value => value -> JSM (Maybe JSVal) Source #

Convert a JSVal to a Maybe JSVal (converting null and undefined to Nothing)

maybeNullOrUndefined' :: ToJSVal value => (JSVal -> JSM a) -> value -> JSM (Maybe a) Source #

valBool :: Bool -> JSVal Source #

A JavaScript boolean value

valMakeNumber :: Double -> JSM JSVal Source #

Make a JavaScript number

valMakeString :: JSString -> JSM JSVal Source #

Make a JavaScript string from JSString

valMakeText :: Text -> JSM JSVal Source #

Make a JavaScript string from Text

valMakeJSON :: Value -> JSM JSVal Source #

Make a JavaScript string from AESON Value

deRefVal :: ToJSVal value => value -> JSM JSValue Source #

Derefernce a value reference.

>>> testJSaddle $ showJSValue <$> deRefVal JSNull
null
>>> testJSaddle $ showJSValue <$> deRefVal ()
undefined
>>> testJSaddle $ showJSValue <$> deRefVal True
true
>>> testJSaddle $ showJSValue <$> deRefVal False
false
>>> testJSaddle $ showJSValue <$> deRefVal (1.0 :: Double)
1.0
>>> testJSaddle $ showJSValue <$> deRefVal (0.0 :: Double)
0.0
>>> testJSaddle $ showJSValue <$> deRefVal ""
""
>>> testJSaddle $ showJSValue <$> deRefVal "1"
"1"
>>> testJSaddle $ showJSValue <$> (valToObject True >>= deRefVal)
true
>>> testJSaddle $ showJSValue <$> (obj >>= deRefVal)
object

valMakeRef :: JSValue -> JSM JSVal Source #

Make a JavaScript value out of a JSValue ADT.

>>> testJSaddle $ valMakeRef ValNull
null
>>> testJSaddle $ valMakeRef ValUndefined
undefined
>>> testJSaddle $ valMakeRef (ValBool True)
true
>>> testJSaddle $ valMakeRef (ValNumber 1)
1
>>> testJSaddle $ valMakeRef (ValString $ T.pack "Hello")
Hello

strictEqual :: (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool Source #

Determine if two values are equal (JavaScripts ===) >>> testJSaddle $ strictEqual True False false >>> testJSaddle $ strictEqual True True true >>> testJSaddle $ strictEqual Hello () false >>> testJSaddle $ strictEqual Hello Hello true

instanceOf :: (ToJSVal value, MakeObject constructor) => value -> constructor -> JSM Bool Source #

Determine if two values are equal (JavaScripts ===) >>> testJSaddle $ instanceOf obj (Object $ jsg Object) true

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 #