Copyright | (c) Samuel Balco 2020 |
---|---|
License | MIT |
Maintainer | goodlyrottenapple@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data JSValue
- type JSContextPtr = Ptr JSContext
- quickjs :: MonadIO m => ReaderT (Ptr JSContext) m b -> m b
- quickjsMultithreaded :: MonadUnliftIO m => ReaderT (Ptr JSContext) m b -> m b
- call :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> [JSValue] -> m Value
- eval :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> m Value
- eval_ :: (MonadThrow m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> m ()
- withJSValue :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m, ToJSON a) => a -> (JSValue -> m b) -> m b
- fromJSValue_ :: (MonadCatch m, MonadReader JSContextPtr m, MonadIO m) => JSValue -> m Value
Documentation
Instances
Eq JSValue Source # | |
Show JSValue Source # | |
Storable JSValue Source # | |
type JSContextPtr = Ptr JSContext Source #
quickjs :: MonadIO m => ReaderT (Ptr JSContext) m b -> m b Source #
This function initialises a new JS runtime and performs the given computation within this context.
For example, we can evaluate an expression:
quickjs $ do res <- eval "1+2" liftIO $ print res
Declare a function and call it on an argument:
quickjs $ do _ <- eval_ "f = (x) => x+1" res <- eval "f(2)" liftIO $ print res
Pass a Haskell value to the JS runtime:
quickjs $ do _ <- eval_ "f = (x) => x+1" res <- withJSValue (3::Int) $ \x -> call "f" [x] liftIO $ print res
quickjsMultithreaded :: MonadUnliftIO m => ReaderT (Ptr JSContext) m b -> m b Source #
This env differs from regular quickjs
, in that it wraps the computation in the runInBoundThread
function.
This is needed when running the Haskell program mutithreaded (e.g. when using the testing framework Tasty),
since quickjs does not like being called from an OS thread other than the one it was started in.
Because Haskell uses lightweight threads, this might happen if threaded mode is enabled, as is the case in Tasty.
This problem does not occur when running via Main.hs, if compiled as single threaded...
For more info see the paper Extending the Haskell Foreign Function Interface with Concurrency
call :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> [JSValue] -> m Value Source #
eval :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> m Value Source #
Evaluates the given string and returns a Value
(if the result can be converted).
eval_ :: (MonadThrow m, MonadReader JSContextPtr m, MonadIO m) => ByteString -> m () Source #
More efficient than eval
if we don't care about the value of the expression,
e.g. if we are evaluating a function definition or performing other side-effects such as
printing to console/modifying state.
withJSValue :: (MonadMask m, MonadReader JSContextPtr m, MonadIO m, ToJSON a) => a -> (JSValue -> m b) -> m b Source #
Takes a value with a defined ToJSON
instance. This value is marshalled to a JSValue
and passed as an argument to the callback function, provided as the second argument to withJSValue
fromJSValue_ :: (MonadCatch m, MonadReader JSContextPtr m, MonadIO m) => JSValue -> m Value Source #