Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
H.Prelude
Contents
Description
| Copyright: (C) 2013 Amgen, Inc.
DEPRECATED: use Language.R instead.
Synopsis
- module Language.R.Instance
- class (Applicative m, MonadIO m, MonadCatch m, MonadMask m, PrimMonad m) => MonadR m where
- data ExecContext m :: *
- io :: IO a -> m a
- acquire :: s ~ V => SEXP s a -> m (SEXP (Region m) a)
- getExecContext :: m (ExecContext m)
- unsafeRunWithExecContext :: m a -> ExecContext m -> IO a
- type Region m = PrimState m
- acquireSome :: MonadR m => SomeSEXP V -> m (SomeSEXP (Region m))
- module Foreign.R.Error
- type family Sing :: k -> Type
- data Logical
- type IsExpression (a :: SEXPTYPE) = (SingI a, a :∈ [Lang, Expr, Symbol])
- type IsPairList (a :: SEXPTYPE) = (SingI a, a :∈ [List, Nil])
- type IsList (a :: SEXPTYPE) = (SingI a, a :∈ ('Char ': ('Logical ': ('Int ': ('Real ': ('Complex ': ('String ': ('Vector ': ('Expr ': ('WeakRef ': ('Raw ': (List ': '[]))))))))))))
- type IsGenericVector (a :: SEXPTYPE) = (SingI a, a :∈ [Vector, Expr, WeakRef])
- type IsVector (a :: SEXPTYPE) = (SingI a, a :∈ ('Char ': ('Logical ': ('Int ': ('Real ': ('Complex ': ('String ': ('Vector ': ('Expr ': ('WeakRef ': ('Raw ': '[])))))))))))
- type PairList = List
- data SSEXPTYPE :: SEXPTYPE -> Type where
- SNil :: SSEXPTYPE ('Nil :: SEXPTYPE)
- SSymbol :: SSEXPTYPE ('Symbol :: SEXPTYPE)
- SList :: SSEXPTYPE ('List :: SEXPTYPE)
- SClosure :: SSEXPTYPE ('Closure :: SEXPTYPE)
- SEnv :: SSEXPTYPE ('Env :: SEXPTYPE)
- SPromise :: SSEXPTYPE ('Promise :: SEXPTYPE)
- SLang :: SSEXPTYPE ('Lang :: SEXPTYPE)
- SSpecial :: SSEXPTYPE ('Special :: SEXPTYPE)
- SBuiltin :: SSEXPTYPE ('Builtin :: SEXPTYPE)
- SChar :: SSEXPTYPE ('Char :: SEXPTYPE)
- SLogical :: SSEXPTYPE ('Logical :: SEXPTYPE)
- SInt :: SSEXPTYPE ('Int :: SEXPTYPE)
- SReal :: SSEXPTYPE ('Real :: SEXPTYPE)
- SComplex :: SSEXPTYPE ('Complex :: SEXPTYPE)
- SString :: SSEXPTYPE ('String :: SEXPTYPE)
- SDotDotDot :: SSEXPTYPE ('DotDotDot :: SEXPTYPE)
- SAny :: SSEXPTYPE ('Any :: SEXPTYPE)
- SVector :: SSEXPTYPE ('Vector :: SEXPTYPE)
- SExpr :: SSEXPTYPE ('Expr :: SEXPTYPE)
- SBytecode :: SSEXPTYPE ('Bytecode :: SEXPTYPE)
- SExtPtr :: SSEXPTYPE ('ExtPtr :: SEXPTYPE)
- SWeakRef :: SSEXPTYPE ('WeakRef :: SEXPTYPE)
- SRaw :: SSEXPTYPE ('Raw :: SEXPTYPE)
- SS4 :: SSEXPTYPE ('S4 :: SEXPTYPE)
- SNew :: SSEXPTYPE ('New :: SEXPTYPE)
- SFree :: SSEXPTYPE ('Free :: SEXPTYPE)
- SFun :: SSEXPTYPE ('Fun :: SEXPTYPE)
- data SomeSEXP s = forall a. SomeSEXP !(SEXP s a)
- data SEXP s (a :: SEXPTYPE)
- unSomeSEXP :: SomeSEXP s -> (forall a. SEXP s a -> r) -> r
- typeOf :: SEXP s a -> SEXPTYPE
- cast :: SSEXPTYPE a -> SomeSEXP s -> SEXP s a
- asTypeOf :: SomeSEXP s -> SEXP s a -> SEXP s a
- unsafeCoerce :: SEXP s a -> SEXP s b
- automatic :: MonadR m => SEXP s a -> m (SEXP G a)
- automaticSome :: MonadR m => SomeSEXP s -> m (SomeSEXP G)
- pokeRVariables :: RVariables -> IO ()
- isRInteractive :: Ptr CInt
- signalHandlersPtr :: Ptr CInt
- unboundValue :: SEXP G 'Symbol
- nilValue :: SEXP G 'Nil
- missingArg :: SEXP G 'Symbol
- baseEnv :: SEXP G 'Env
- emptyEnv :: SEXP G 'Env
- globalEnv :: SEXP G 'Env
- inputHandlers :: Ptr InputHandler
- data Config = Config {}
- data R s a
- withEmbeddedR :: Config -> IO a -> IO a
- runRegion :: NFData a => (forall s. R s a) -> IO a
- unsafeRunRegion :: NFData a => R s a -> IO a
- defaultConfig :: Config
- initialize :: Config -> IO ()
- finalize :: IO ()
- class SingI ty => Literal a ty | a -> ty where
- mkSEXP :: (Literal a b, MonadR m) => a -> m (SEXP (Region m) b)
- fromSomeSEXP :: forall s a form. Literal a form => SomeSEXP s -> a
- dynSEXP :: forall a s ty. Literal a ty => SomeSEXP s -> a
- mkSEXPVector :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> SEXP s a
- mkSEXPVectorIO :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> IO (SEXP s a)
- mkProtectedSEXPVector :: IsVector b => SSEXPTYPE b -> [SEXP s a] -> SEXP s b
- mkProtectedSEXPVectorIO :: IsVector b => SSEXPTYPE b -> [SEXP s a] -> IO (SEXP s b)
- toPairList :: MonadR m => [(String, SomeSEXP (Region m))] -> m (SomeSEXP (Region m))
- fromPairList :: SomeSEXP s -> [(String, SomeSEXP s)]
- funToSEXP :: HFunWrap a b => (b -> IO (FunPtr b)) -> a -> IO (SEXP s 'ExtPtr)
- parseFile :: FilePath -> (SEXP s 'Expr -> IO a) -> IO a
- parseText :: String -> Bool -> IO (SEXP V 'Expr)
- install :: MonadR m => String -> m (SEXP V 'Symbol)
- string :: String -> IO (SEXP V 'Char)
- strings :: String -> IO (SEXP V 'String)
- evalEnv :: MonadR m => SEXP s a -> SEXP s 'Env -> m (SomeSEXP (Region m))
- eval :: MonadR m => SEXP s a -> m (SomeSEXP (Region m))
- eval_ :: MonadR m => SEXP s a -> m ()
- throwR :: MonadR m => SEXP s 'Env -> m a
- cancel :: IO ()
- throwRMessage :: MonadR m => String -> m a
- refresh :: MonadR m => m ()
- 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).
Minimal complete definition
Associated Types
data ExecContext m :: * Source #
A reification of an R execution context, i.e. a "session".
Methods
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).
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.
Instances
MonadR IO Source # | |
Defined in H.Prelude.Interactive Associated Types data ExecContext IO Source # | |
MonadR (R s) Source # | |
Defined in Language.R.Instance Associated Types data ExecContext (R s) Source # |
module Foreign.R.Error
Language.R functions
type family Sing :: k -> Type #
The singleton kind-indexed type family.
Instances
type Sing Source # | |
Defined in Foreign.R.Type | |
type Sing | |
Defined in Data.Singletons | |
type Sing | |
Defined in Data.Singletons |
R uses three-valued logic.
Instances
Storable Logical Source # | |
Show Logical Source # | |
Eq Logical Source # | |
Ord Logical Source # | |
Literal Logical 'Logical Source # | |
Literal [Logical] 'Logical Source # | |
type IsPairList (a :: SEXPTYPE) = (SingI a, a :∈ [List, Nil]) Source #
IsPairList a
holds iff R's is.pairlist()
returns TRUE
.
type IsList (a :: SEXPTYPE) = (SingI a, a :∈ ('Char ': ('Logical ': ('Int ': ('Real ': ('Complex ': ('String ': ('Vector ': ('Expr ': ('WeakRef ': ('Raw ': (List ': '[])))))))))))) Source #
IsList a
holds iff R's is.list()
returns TRUE
.
type IsGenericVector (a :: SEXPTYPE) = (SingI a, a :∈ [Vector, Expr, WeakRef]) Source #
Non-atomic vector forms. See src/main/memory.c:SET_VECTOR_ELT
in the
R source distribution.
type IsVector (a :: SEXPTYPE) = (SingI a, a :∈ ('Char ': ('Logical ': ('Int ': ('Real ': ('Complex ': ('String ': ('Vector ': ('Expr ': ('WeakRef ': ('Raw ': '[]))))))))))) Source #
Constraint synonym grouping all vector forms into one class. IsVector a
holds iff R's is.vector()
returns TRUE
.
Used where the R documentation speaks of "pairlists", which are really just regular lists.
data SSEXPTYPE :: SEXPTYPE -> Type where Source #
Constructors
A SEXP
of unknown form.
Instances
ToJSON (SomeSEXP s) Source # | |
Defined in Language.R.Debug | |
Storable (SomeSEXP s) Source # | |
Defined in Foreign.R.Internal Methods alignment :: SomeSEXP s -> Int # peekElemOff :: Ptr (SomeSEXP s) -> Int -> IO (SomeSEXP s) # pokeElemOff :: Ptr (SomeSEXP s) -> Int -> SomeSEXP s -> IO () # peekByteOff :: Ptr b -> Int -> IO (SomeSEXP s) # pokeByteOff :: Ptr b -> Int -> SomeSEXP s -> IO () # | |
Show (SomeSEXP s) Source # | |
NFData (SomeSEXP s) Source # | |
Defined in Foreign.R.Internal | |
PrintR (SomeSEXP s) Source # | |
Literal (SomeSEXP s) 'Any Source # | |
data SEXP s (a :: SEXPTYPE) Source #
The basic type of all R expressions, classified by the form of the expression, and the memory region in which it has been allocated.
Instances
ToJSON (SEXP s a) Source # | |
Defined in Language.R.Debug | |
Storable (SEXP s a) Source # | |
Defined in Foreign.R.Internal | |
Show (SEXP s a) Source # | |
NFData (SEXP s a) Source # | |
Defined in Foreign.R.Internal | |
Eq (SEXP s a) Source # | |
Ord (SEXP s a) Source # | |
Defined in Foreign.R.Internal | |
PrintR (SEXP s a) Source # | |
SingI a => Literal (SEXP s a) a Source # | |
unSomeSEXP :: SomeSEXP s -> (forall a. SEXP s a -> r) -> r Source #
typeOf :: SEXP s a -> SEXPTYPE Source #
Return the "type" tag (aka the form tag) of the given SEXP
. This
function is pure because the type of an object does not normally change over
the lifetime of the object.
cast :: SSEXPTYPE a -> SomeSEXP s -> SEXP s a Source #
Cast the type of a SEXP
into another type. This function is partial: at
runtime, an error is raised if the source form tag does not match the target
form tag.
asTypeOf :: SomeSEXP s -> SEXP s a -> SEXP s a Source #
Cast form of first argument to that of the second argument.
unsafeCoerce :: SEXP s a -> SEXP s b Source #
Unsafe coercion from one form to another. This is unsafe, in the sense that
using this function improperly could cause code to crash in unpredictable
ways. Contrary to cast
, it has no runtime cost since it does not introduce
any dynamic check at runtime.
automatic :: MonadR m => SEXP s a -> m (SEXP G a) Source #
Declare memory management for this value to be automatic. That is, the memory associated with it may be freed as soon as the garbage collector notices that it is safe to do so.
Values with automatic memory management are tagged with the global region. The reason is that just like for other global values, deallocation of the value can never be observed. Indeed, it is a mere "optimization" to deallocate the value sooner - it would still be semantically correct to never deallocate it at all.
pokeRVariables :: RVariables -> IO () Source #
isRInteractive :: Ptr CInt Source #
unboundValue :: SEXP G 'Symbol Source #
Special value to which all symbols unbound in the current environment resolve to.
missingArg :: SEXP G 'Symbol Source #
Value substituted for all missing actual arguments of a function call.
Configuration options for the R runtime. Configurations form monoids, so arguments can be accumulated left-to-right through monoidal composition.
Constructors
Config | |
Fields
|
The R
monad, for sequencing actions interacting with a single instance of
the R interpreter, much as the IO
monad sequences actions interacting with
the real world. The R
monad embeds the IO
monad, so all IO
actions can
be lifted to R
actions.
Instances
MonadFail (R s) Source # | |
Defined in Language.R.Instance | |
MonadIO (R s) Source # | |
Defined in Language.R.Instance | |
Applicative (R s) Source # | |
Functor (R s) Source # | |
Monad (R s) Source # | |
MonadCatch (R s) Source # | |
MonadMask (R s) Source # | |
MonadThrow (R s) Source # | |
Defined in Language.R.Instance | |
MonadR (R s) Source # | |
Defined in Language.R.Instance Associated Types data ExecContext (R s) Source # | |
PrimMonad (R s) Source # | |
(NFData a, Literal a b) => Literal (R s a) 'ExtPtr Source # | |
(NFData b, Literal a a0, Literal b b0) => Literal (a -> R s b) 'ExtPtr Source # | |
(NFData c, Literal a a0, Literal b b0, Literal c c0) => Literal (a -> b -> R s c) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a1 i4) => Literal (a2 -> a3 -> a4 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a1 i5) => Literal (a2 -> a3 -> a4 -> a5 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a1 i6) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a1 i7) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a1 i8) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a1 i9) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a1 i10) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a1 i11) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a1 i12) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a13 i12, Literal a1 i13) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> a13 -> R s a1) 'ExtPtr Source # | |
newtype ExecContext (R s) Source # | |
Defined in Language.R.Instance | |
type PrimState (R s) Source # | |
Defined in Language.R.Instance |
withEmbeddedR :: Config -> IO a -> IO a Source #
Initialize a new instance of R, execute actions that interact with the
R instance and then finalize the instance. This is typically called at the
very beginning of the main
function of the program.
main = withEmbeddedR $ do {...}
Note that R does not currently support reinitialization after finalization,
so this function should be called only once during the lifetime of the
program (see srcunixsystem.c:Rf_initialize()
in the R source code).
runRegion :: NFData a => (forall s. R s a) -> IO a Source #
Run an R action in the global R instance from the IO monad. This action
provides no static guarantees that the R instance was indeed initialized and
has not yet been finalized. Make sure to call it within the scope of
withEmbeddedR
.
runRegion m
fully evaluates the result of action m
, to ensure that no
thunks hold onto resources in a way that would extrude the scope of the
region. This means that the result must be first-order data (i.e. not
a function).
throws
Error
. Generaly any R function may throw RError
that
is safe to be cached and computation can proceed. However RError
will cancel
entire R block. So in order to catch exception in more fine grained way one
has to use function tryCatch
inside R block.
defaultConfig :: Config Source #
Default argument to pass to initialize
.
initialize :: Config -> IO () Source #
Create a new embedded instance of the R interpreter. Only works from the
main thread of the program. That is, from the same thread of execution that
the program's main
function is running on. In GHCi, use -fno-ghci-sandbox
to achieve this.
class SingI ty => Literal a ty | a -> ty where Source #
Values that can be converted to SEXP
.
Minimal complete definition
Nothing
Methods
Instances
Literal Int32 'Int Source # | |
Literal Logical 'Logical Source # | |
Literal Text 'String Source # | |
Literal String 'String Source # | |
Literal Double 'Real Source # | |
Literal (Complex Double) 'Complex Source # | |
Literal (SomeSEXP s) 'Any Source # | |
Literal [Complex Double] 'Complex Source # | |
Literal [Int32] 'Int Source # | |
Literal [Logical] 'Logical Source # | |
Literal [String] 'String Source # | |
Literal [Double] 'Real Source # | |
SVECTOR ty a => Literal (Vector ty a) ty Source # | |
SingI a => Literal (SEXP s a) a Source # | |
(NFData a, Literal a b) => Literal (R s a) 'ExtPtr Source # | |
(NFData b, Literal a a0, Literal b b0) => Literal (a -> R s b) 'ExtPtr Source # | |
(NFData c, Literal a a0, Literal b b0, Literal c c0) => Literal (a -> b -> R s c) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a1 i4) => Literal (a2 -> a3 -> a4 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a1 i5) => Literal (a2 -> a3 -> a4 -> a5 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a1 i6) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a1 i7) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a1 i8) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a1 i9) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a1 i10) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a1 i11) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a1 i12) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> R s a1) 'ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a13 i12, Literal a1 i13) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> a13 -> R s a1) 'ExtPtr Source # | |
VECTOR V ty a => Literal (MVector V ty a) ty Source # | |
mkSEXP :: (Literal a b, MonadR m) => a -> m (SEXP (Region m) b) Source #
Create a SEXP value and protect it in current region
fromSomeSEXP :: forall s a form. Literal a form => SomeSEXP s -> a Source #
Like fromSEXP
, but with no static type satefy. Performs a dynamic
(i.e. at runtime) check instead.
dynSEXP :: forall a s ty. Literal a ty => SomeSEXP s -> a Source #
Like fromSomeSEXP
, but behaves like the as.*
family of functions
in R, by performing a best effort conversion to the target form (e.g. rounds
reals to integers, etc) for atomic types.
mkSEXPVector :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> SEXP s a Source #
mkSEXPVectorIO :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> IO (SEXP s a) Source #
toPairList :: MonadR m => [(String, SomeSEXP (Region m))] -> m (SomeSEXP (Region m)) Source #
Create a pairlist from an association list. Result is either a pairlist or
nilValue
if the input is the null list. These are two distinct forms. Hence
why the type of this function is not more precise.
fromPairList :: SomeSEXP s -> [(String, SomeSEXP s)] Source #
Create an association list from a pairlist. R Pairlists are nil-terminated chains of nested cons cells, as in LISP.
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.
Arguments
:: String | Text to parse |
-> Bool | Whether to annotate the AST with source locations. |
-> IO (SEXP V 'Expr) |
Deprecated: Use [r| parse(text=...) |] instead.
string :: String -> IO (SEXP V 'Char) Source #
Deprecated: Use mkSEXP instead
Create an R character string from a Haskell string.
strings :: String -> IO (SEXP V 'String) Source #
Deprecated: Use mkSEXP instead
Create an R string vector from a Haskell string.
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.
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.
Throw an R error as an exception.
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).
throwRMessage :: MonadR m => String -> m a Source #
Throw an R exception with specified message.
refresh :: MonadR m => m () Source #
Manually trigger processing all pending events. Useful when at an interactive prompt and no event loop is running.
module Language.R.HExp
module Language.R.Literal
module Language.R.QQ
Globals
module Language.R.Globals