Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data JSContextRef = JSContextRef {
- contextId :: Int64
- startTime :: UTCTime
- doSendCommand :: Command -> IO Result
- doSendAsyncCommand :: AsyncCommand -> IO ()
- addCallback :: Object -> JSCallAsFunction -> IO ()
- nextRef :: TVar JSValueRef
- doEnableLogging :: Bool -> IO ()
- finalizerThreads :: MVar (Set Text)
- animationFrameHandlers :: MVar [Double -> JSM ()]
- liveRefs :: MVar (Set Int64)
- newtype JSM a = JSM {
- unJSM :: ReaderT JSContextRef IO a
- class (Applicative m, MonadIO m) => MonadJSM m where
- liftJSM :: MonadJSM m => JSM a -> m a
- newtype GHCJSPure a = GHCJSPure (JSM a)
- ghcjsPure :: GHCJSPure a -> JSM a
- ghcjsPureMap :: (a -> b) -> GHCJSPure a -> GHCJSPure b
- ghcjsPureId :: a -> GHCJSPure a
- newtype JSVal = JSVal (IORef JSValueRef)
- class IsJSVal a where
- jsval :: IsJSVal a => a -> GHCJSPure JSVal
- newtype SomeJSArray m = SomeJSArray JSVal
- type JSArray = SomeJSArray Immutable
- type MutableJSArray = SomeJSArray Mutable
- type STJSArray s = SomeJSArray (STMutable s)
- newtype Object = Object JSVal
- newtype JSString = JSString Text
- newtype Nullable a = Nullable a
- type JSCallAsFunction = JSVal -> JSVal -> [JSVal] -> JSM ()
- type JSadddleHasCallStack = (() :: Constraint)
- data MutabilityType s
- = Mutable_ s
- | Immutable_ s
- | STMutable s
- type Mutable = Mutable_ ()
- type Immutable = Immutable_ ()
- data IsItMutable
- type family Mutability (a :: MutabilityType s) :: IsItMutable where ...
- newtype JSValueReceived = JSValueReceived JSValueRef
- newtype JSValueForSend = JSValueForSend JSValueRef
- newtype JSStringReceived = JSStringReceived Text
- newtype JSStringForSend = JSStringForSend Text
- newtype JSObjectForSend = JSObjectForSend JSValueForSend
- data AsyncCommand
- = FreeRef Text JSValueForSend
- | FreeRefs Text
- | SetPropertyByName JSObjectForSend JSStringForSend JSValueForSend
- | SetPropertyAtIndex JSObjectForSend Int JSValueForSend
- | StringToValue JSStringForSend JSValueForSend
- | NumberToValue Double JSValueForSend
- | JSONValueToValue Value JSValueForSend
- | GetPropertyByName JSObjectForSend JSStringForSend JSValueForSend
- | GetPropertyAtIndex JSObjectForSend Int JSValueForSend
- | CallAsFunction JSObjectForSend JSObjectForSend [JSValueForSend] JSValueForSend
- | CallAsConstructor JSObjectForSend [JSValueForSend] JSValueForSend
- | NewEmptyObject JSValueForSend
- | NewAsyncCallback JSValueForSend
- | NewSyncCallback JSValueForSend
- | FreeCallback JSValueForSend
- | NewArray [JSValueForSend] JSValueForSend
- | EvaluateScript JSStringForSend JSValueForSend
- | SyncWithAnimationFrame JSValueForSend
- | StartSyncBlock
- | EndSyncBlock
- data Command
- = DeRefVal JSValueForSend
- | ValueToBool JSValueForSend
- | ValueToNumber JSValueForSend
- | ValueToString JSValueForSend
- | ValueToJSON JSValueForSend
- | ValueToJSONValue JSValueForSend
- | IsNull JSValueForSend
- | IsUndefined JSValueForSend
- | StrictEqual JSValueForSend JSValueForSend
- | InstanceOf JSValueForSend JSObjectForSend
- | PropertyNames JSObjectForSend
- | Sync
- data Batch = Batch [Either AsyncCommand Command] Bool Int
- data Result
- = DeRefValResult JSValueRef Text
- | ValueToBoolResult Bool
- | ValueToNumberResult Double
- | ValueToStringResult JSStringReceived
- | ValueToJSONResult JSStringReceived
- | ValueToJSONValueResult Value
- | IsNullResult Bool
- | IsUndefinedResult Bool
- | StrictEqualResult Bool
- | InstanceOfResult Bool
- | PropertyNamesResult [JSStringReceived]
- | ThrowJSValue JSValueReceived
- | SyncResult
- data BatchResults
- data Results
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.
JSContextRef | |
|
The JSM Monad
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
JSM | |
|
class (Applicative m, MonadIO m) => MonadJSM m where Source #
liftJSM' :: JSM a -> m a Source #
liftJSM' :: (MonadJSM m', MonadTrans t, m ~ t m') => JSM a -> m a Source #
MonadJSM JSM Source # | |
MonadJSM m => MonadJSM (ListT m) Source # | |
MonadJSM m => MonadJSM (MaybeT m) Source # | |
MonadJSM m => MonadJSM (IdentityT * m) Source # | |
(Error e, MonadJSM m) => MonadJSM (ErrorT e m) Source # | |
MonadJSM m => MonadJSM (ExceptT e m) Source # | |
MonadJSM m => MonadJSM (StateT s m) Source # | |
MonadJSM m => MonadJSM (StateT s m) Source # | |
(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) Source # | |
(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) Source # | |
MonadJSM m => MonadJSM (ContT * r m) Source # | |
MonadJSM m => MonadJSM (ReaderT * r m) Source # | |
(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) Source # | |
(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) Source # | |
Pure GHCJS functions
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
.
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 #
ghcjsPureId :: a -> GHCJSPure a Source #
JavaScript Value Types
class IsJSVal a where Source #
IsJSVal (SomeJSArray s m) Source # | |
IsJSVal (SomeArrayBuffer s m) Source # | |
IsJSVal (SomeTypedArray s e m) Source # | |
type MutableJSArray = SomeJSArray Mutable Source #
See MutableJSArray
See Object
MakeObject Object Source # | If we already have a Object we are fine |
A wrapper around a JavaScript string
type JSCallAsFunction Source #
= JSVal | Function object |
-> JSVal | this |
-> [JSVal] | Function arguments |
-> JSM () | Only () (aka |
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
JavaScript Context Commands
data MutabilityType s Source #
Mutable_ s | |
Immutable_ s | |
STMutable s |
type Immutable = Immutable_ () Source #
type family Mutability (a :: MutabilityType s) :: IsItMutable where ... Source #
newtype JSValueReceived Source #
Wrapper used when receiving a JSVal
from the JavaScript context
newtype JSValueForSend Source #
Wrapper used when sending a JSVal
to the JavaScript context
newtype JSStringReceived Source #
Wrapper used when receiving a JSString
from the JavaScript context
newtype JSStringForSend Source #
Wrapper used when sending a JString
to the JavaScript context
newtype JSObjectForSend Source #
Wrapper used when sending a Object
to the JavaScript context
data AsyncCommand Source #
Command sent to a JavaScript context for execution asynchronously
Command sent to a JavaScript context for execution synchronously
Batch of commands that can be sent together to the JavaScript context
Result of a Command
returned from the JavaScript context
data BatchResults Source #