Safe Haskell | None |
---|---|
Language | Haskell2010 |
| Copyright: (C) 2013 Amgen, Inc.
DEPRECATED: use Language.R instead.
- module Language.R.Instance
- class (Applicative m, MonadIO m, MonadCatch m, MonadMask m, PrimMonad m) => MonadR m where
- data ExecContext m :: *
- type Region m = PrimState m
- acquireSome :: MonadR m => SomeSEXP V -> m (SomeSEXP (Region m))
- module Foreign.R.Error
- module Language.R
- module Language.R.Event
- module Language.R.HExp
- module Language.R.Literal
- module Language.R.QQ
- module Language.R.Globals
Documentation
module Language.R.Instance
class (Applicative m, MonadIO m, MonadCatch m, MonadMask m, PrimMonad m) => MonadR m where Source #
The class of R interaction monads. For safety, in compiled code we normally
use the R
monad. For convenience, in a GHCi session, we
normally use the IO
monad directly (by means of a MonadR
instance for
IO
, imported only in GHCi).
data ExecContext m :: * Source #
A reification of an R execution context, i.e. a "session".
Lift an IO
action.
acquire :: s ~ V => SEXP s a -> m (SEXP (Region m) a) Source #
Acquire ownership in the current region of the given object. This means that the liveness of the object is guaranteed so long as the current region remains active (the R garbage collector will not attempt to free it).
acquire :: (MonadIO m, Region m ~ G) => SEXP s a -> m (SEXP (Region m) a) Source #
Acquire ownership in the current region of the given object. This means that the liveness of the object is guaranteed so long as the current region remains active (the R garbage collector will not attempt to free it).
getExecContext :: m (ExecContext m) Source #
Get the current execution context.
unsafeRunWithExecContext :: m a -> ExecContext m -> IO a Source #
Provides no static guarantees that resources do not extrude the scope of their region. Acquired resources are not freed automatically upon exit. For internal use only.
module Foreign.R.Error
Language.R functions
module Language.R
module Language.R.Event
module Language.R.HExp
module Language.R.Literal
module Language.R.QQ
Globals
module Language.R.Globals