Copyright | (C) 2013 Amgen Inc. |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Low-level bindings to core R datatypes and functions which depend on computing offsets of C struct field. We use hsc2hs for this purpose.
- newtype SEXP s (a :: SEXPTYPE) = SEXP {}
- sexp :: SEXP0 -> SEXP s a
- unsexp :: SEXP s a -> SEXP0
- somesexp :: SEXP0 -> SomeSEXP s
- release :: t <= s => SEXP s a -> SEXP t a
- unsafeRelease :: SEXP s a -> SEXP r a
- data SomeSEXP s = SomeSEXP !(SEXP s a)
- unSomeSEXP :: SomeSEXP s -> (forall a. SEXP s a -> r) -> r
- cIntConv :: (Integral a, Integral b) => a -> b
- cIntToEnum :: Enum a => CInt -> a
- cUIntFromSingEnum :: SSEXPTYPE a -> CUInt
- cIntFromEnum :: Enum a => a -> CInt
- typeOf :: SEXP s a -> SEXPTYPE
- cTYPEOF :: SEXP0 -> IO CInt
- setCar :: SEXP s a -> SEXP s b -> IO ()
- setCdr :: SEXP s a -> SEXP s b -> IO ()
- setTag :: SEXP s a -> SEXP s b -> IO ()
- unsafeCast :: SEXPTYPE -> SomeSEXP s -> SEXP s b
- cast :: SSEXPTYPE a -> SomeSEXP s -> SEXP s a
- asTypeOf :: SomeSEXP s -> SEXP s a -> SEXP s a
- unsafeCoerce :: SEXP s a -> SEXP s b
- length :: IsVector a => SEXP s a -> IO Int
- unsafeSEXPToVectorPtr :: SEXP s a -> Ptr ()
- unsafeVectorPtrToSEXP :: Ptr a -> SomeSEXP s
- isRInteractive :: Ptr CInt
- nilValue :: Ptr (SEXP G Nil)
- unboundValue :: Ptr (SEXP G Symbol)
- missingArg :: Ptr (SEXP G Symbol)
- baseEnv :: Ptr (SEXP G Env)
- emptyEnv :: Ptr (SEXP G Env)
- globalEnv :: Ptr (SEXP G Env)
- signalHandlers :: Ptr CInt
- interruptsPending :: Ptr CInt
- data SEXPInfo = SEXPInfo {}
- peekInfo :: SEXP s a -> IO SEXPInfo
- cOBJECT :: SEXP0 -> IO CInt
- cNAMED :: SEXP0 -> IO CInt
- cLEVELS :: SEXP0 -> IO CInt
- cMARK :: SEXP0 -> IO CInt
- cRDEBUG :: SEXP0 -> IO CInt
- cRTRACE :: SEXP0 -> IO CInt
- cRSTEP :: SEXP0 -> IO CInt
- cGCGEN :: SEXP0 -> IO CInt
- cGCCLS :: SEXP0 -> IO CInt
- pokeInfo :: SEXP s a -> SEXPInfo -> IO ()
- cSET_TYPEOF :: SEXP0 -> CInt -> IO ()
- cSET_OBJECT :: SEXP0 -> CInt -> IO ()
- cSET_NAMED :: SEXP0 -> CInt -> IO ()
- cSETLEVELS :: SEXP0 -> CInt -> IO ()
- cSET_MARK :: SEXP0 -> CInt -> IO ()
- cSET_RDEBUG :: SEXP0 -> CInt -> IO ()
- cSET_RTRACE :: SEXP0 -> CInt -> IO ()
- cSET_RSTEP :: SEXP0 -> CInt -> IO ()
- cSET_GCGEN :: SEXP0 -> CInt -> IO ()
- cSET_GCCLS :: SEXP0 -> CInt -> IO ()
- mark :: Bool -> SEXP s a -> IO ()
- named :: Int -> SEXP s a -> IO ()
- isS4 :: SEXP s ty -> Bool
- getAttributes :: SEXP s a -> IO (SEXP s b)
- getAttribute :: SEXP s a -> SEXP s2 b -> SEXP s c
- setAttributes :: SEXP s a -> SEXP s b -> IO ()
- cAttrib :: SEXP0 -> IO SEXP0
- csetAttrib :: SEXP0 -> SEXP0 -> IO ()
- cgetAttrib :: SEXP0 -> SEXP0 -> SEXP0
- cisS4 :: SEXP0 -> Int
Documentation
newtype 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.
release :: t <= s => SEXP s a -> SEXP t a Source #
Release object into another region. Releasing is safe so long as the target region is "smaller" than the source region, in the sense of '(Control.Memory.Region.<=)'.
unsafeRelease :: SEXP s a -> SEXP r a Source #
A SEXP
of unknown form.
unSomeSEXP :: SomeSEXP s -> (forall a. SEXP s a -> r) -> r Source #
cIntToEnum :: Enum a => CInt -> a Source #
cUIntFromSingEnum :: SSEXPTYPE a -> CUInt Source #
cIntFromEnum :: Enum a => a -> CInt 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.
setCar :: SEXP s a -> SEXP s b -> IO () Source #
Set CAR field of object, when object is viewed as a cons cell.
setCdr :: SEXP s a -> SEXP s b -> IO () Source #
Set CDR field of object, when object is viewed as a cons cell.
setTag :: SEXP s a -> SEXP s b -> IO () Source #
Set TAG field of object, when object is viewed as a cons cell.
Coercions have no runtime cost, but are completely unsafe. Use with
caution, only when you know that a SEXP
is of the target type. Casts are
safer, but introduce a runtime type check. The difference between the two is
akin to the difference between a C-style typecasts and C++-style
dynamic_cast
's.
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.
unsafeSEXPToVectorPtr :: SEXP s a -> Ptr () Source #
Extract the data pointer from a vector.
unsafeVectorPtrToSEXP :: Ptr a -> SomeSEXP s Source #
Inverse of vectorPtr
.
isRInteractive :: Ptr CInt Source #
nilValue :: Ptr (SEXP G Nil) Source #
Global nil value. Constant throughout the lifetime of the R instance.
unboundValue :: Ptr (SEXP G Symbol) Source #
Unbound marker. Constant throughout the lifetime of the R instance.
missingArg :: Ptr (SEXP G Symbol) Source #
Missing argument marker. Constant throughout the lifetime of the R instance.
signalHandlers :: Ptr CInt Source #
Signal handler switch
interruptsPending :: Ptr CInt Source #
Flag that shows if computation should be interrupted.
Info header for the SEXP data structure.
SEXPInfo | |
|
isS4 :: SEXP s ty -> Bool Source #
Check if object is an S4 object.
This is a function call so it will be more precise than using typeOf
.
Get attribute with the given name.