inline-r-0.9.1: Seamlessly call R from Haskell and vice versa. No FFI required.

Copyright(C) 2013 Amgen Inc.
Safe HaskellNone
LanguageHaskell2010

Foreign.R.Internal

Description

Low-level bindings to core R datatypes and functions which depend on computing offsets of C struct field. We use hsc2hs for this purpose.

Synopsis

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.

Constructors

SEXP 

Fields

Instances

Eq (SEXP s a) Source # 

Methods

(==) :: SEXP s a -> SEXP s a -> Bool #

(/=) :: SEXP s a -> SEXP s a -> Bool #

Ord (SEXP s a) Source # 

Methods

compare :: SEXP s a -> SEXP s a -> Ordering #

(<) :: SEXP s a -> SEXP s a -> Bool #

(<=) :: SEXP s a -> SEXP s a -> Bool #

(>) :: SEXP s a -> SEXP s a -> Bool #

(>=) :: SEXP s a -> SEXP s a -> Bool #

max :: SEXP s a -> SEXP s a -> SEXP s a #

min :: SEXP s a -> SEXP s a -> SEXP s a #

Show (SEXP s a) Source # 

Methods

showsPrec :: Int -> SEXP s a -> ShowS #

show :: SEXP s a -> String #

showList :: [SEXP s a] -> ShowS #

Storable (SEXP s a) Source # 

Methods

sizeOf :: SEXP s a -> Int #

alignment :: SEXP s a -> Int #

peekElemOff :: Ptr (SEXP s a) -> Int -> IO (SEXP s a) #

pokeElemOff :: Ptr (SEXP s a) -> Int -> SEXP s a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (SEXP s a) #

pokeByteOff :: Ptr b -> Int -> SEXP s a -> IO () #

peek :: Ptr (SEXP s a) -> IO (SEXP s a) #

poke :: Ptr (SEXP s a) -> SEXP s a -> IO () #

NFData (SEXP s a) Source # 

Methods

rnf :: SEXP s a -> () #

PrintR (SEXP s a) Source # 

Methods

printR :: MonadR m => SEXP s a -> m () Source #

SingI SEXPTYPE a => Literal (SEXP s a) a Source # 

Methods

mkSEXPIO :: SEXP s a -> IO (SEXP V a) Source #

fromSEXP :: SEXP s a -> SEXP s a Source #

sexp :: SEXP0 -> SEXP s a Source #

Add a type index to the pointer.

unsexp :: SEXP s a -> SEXP0 Source #

Remove the type index from the pointer.

somesexp :: SEXP0 -> SomeSEXP s Source #

Like sexp but for SomeSEXP.

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.<=)'.

data SomeSEXP s Source #

A SEXP of unknown form.

Constructors

SomeSEXP !(SEXP s a) 

Instances

Show (SomeSEXP s) Source # 

Methods

showsPrec :: Int -> SomeSEXP s -> ShowS #

show :: SomeSEXP s -> String #

showList :: [SomeSEXP s] -> ShowS #

Storable (SomeSEXP s) Source # 

Methods

sizeOf :: SomeSEXP s -> Int #

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 () #

peek :: Ptr (SomeSEXP s) -> IO (SomeSEXP s) #

poke :: Ptr (SomeSEXP s) -> SomeSEXP s -> IO () #

NFData (SomeSEXP s) Source # 

Methods

rnf :: SomeSEXP s -> () #

PrintR (SomeSEXP s) Source # 

Methods

printR :: MonadR m => SomeSEXP s -> m () Source #

Literal (SomeSEXP s) Any Source # 

unSomeSEXP :: SomeSEXP s -> (forall a. SEXP s a -> r) -> r Source #

Deconstruct a SomeSEXP. Takes a continuation since otherwise the existentially quantified variable hidden inside SomeSEXP would escape.

cIntConv :: (Integral a, Integral b) => a -> b Source #

cIntToEnum :: Enum a => CInt -> a 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.

length :: IsVector a => SEXP s a -> IO Int Source #

Length of the vector.

unsafeSEXPToVectorPtr :: SEXP s a -> Ptr () Source #

Extract the data pointer from a vector.

unsafeVectorPtrToSEXP :: Ptr a -> SomeSEXP s Source #

Inverse of vectorPtr.

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.

baseEnv :: Ptr (SEXP G Env) Source #

The base environment.

emptyEnv :: Ptr (SEXP G Env) Source #

The empty environment.

globalEnv :: Ptr (SEXP G Env) Source #

Global environment.

signalHandlers :: Ptr CInt Source #

Signal handler switch

interruptsPending :: Ptr CInt Source #

Flag that shows if computation should be interrupted.

data SEXPInfo Source #

Info header for the SEXP data structure.

Constructors

SEXPInfo 

Fields

peekInfo :: SEXP s a -> IO SEXPInfo Source #

Extract the header from the given SEXP.

pokeInfo :: SEXP s a -> SEXPInfo -> IO () Source #

Write a new header.

mark :: Bool -> SEXP s a -> IO () Source #

Set the GC mark.

named :: Int -> SEXP s a -> IO () Source #

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.

getAttributes :: SEXP s a -> IO (SEXP s b) Source #

Get the attribute list from the given object.

getAttribute Source #

Arguments

:: SEXP s a

Value

-> SEXP s2 b

Attribute name

-> SEXP s c 

Get attribute with the given name.

setAttributes :: SEXP s a -> SEXP s b -> IO () Source #

Set the attribute list.