Copyright | 2013 (C) Amgen Inc |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Wrappers for low-level R functions.
- module Foreign.R
- module Foreign.R.Type
- module Language.R.Instance
- module Language.R.Globals
- module Language.R.GC
- module Language.R.Literal
- eval :: MonadR m => SEXP s a -> m (SomeSEXP (Region m))
- eval_ :: MonadR m => SEXP s a -> m ()
- evalEnv :: MonadR m => SEXP s a -> SEXP s Env -> m (SomeSEXP (Region m))
- install :: MonadR m => String -> m (SEXP V Symbol)
- cancel :: IO ()
- throwR :: MonadR m => SEXP s Env -> m a
- throwRMessage :: MonadR m => String -> m a
- parseFile :: FilePath -> (SEXP s Expr -> IO a) -> IO a
- parseText :: String -> Bool -> IO (SEXP V Expr)
- string :: String -> IO (SEXP V Char)
- strings :: String -> IO (SEXP V String)
Documentation
module Foreign.R
module Foreign.R.Type
module Language.R.Instance
module Language.R.Globals
module Language.R.GC
module Language.R.Literal
Evaluation
eval :: MonadR m => SEXP s a -> m (SomeSEXP (Region m)) Source #
Evaluate a (sequence of) expression(s) in the global environment.
eval_ :: MonadR m => SEXP s a -> m () Source #
Silent version of eval
function that discards it's result.
evalEnv :: MonadR m => SEXP s a -> SEXP s Env -> m (SomeSEXP (Region m)) Source #
Evaluate a (sequence of) expression(s) in the given environment, returning the value of the last.
Cancel any ongoing R computation in the current process. After interruption
an RError
exception will be raised.
This call is safe to run in any thread. If there is no R computation running, the next computaion will be immediately cancelled. Note that R will only interrupt computations at so-called "safe points" (in particular, not in the middle of a C call).
Exceptions
Throw an R error as an exception.
throwRMessage :: MonadR m => String -> m a Source #
Throw an R exception with specified message.
Deprecated
parseFile :: FilePath -> (SEXP s Expr -> IO a) -> IO a Source #
Deprecated: Use [r| parse(file="pathtofile") |] instead.
Parse file and perform some actions on parsed file.
This function uses continuation because this is an easy way to make operations GC-safe.
Deprecated: Use [r| parse(text=...) |] instead.