inline-r-1.0.1: Seamlessly call R from Haskell and vice versa. No FFI required.
Copyright2013 (C) Amgen Inc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.R

Description

Wrappers for low-level R functions.

Synopsis

Documentation

data SomeSEXP s Source #

A SEXP of unknown form.

Constructors

forall a. SomeSEXP !(SEXP s a) 

Instances

Instances details
ToJSON (SomeSEXP s) Source # 
Instance details

Defined in Language.R.Debug

Storable (SomeSEXP s) Source # 
Instance details

Defined in Foreign.R.Internal

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

Show (SomeSEXP s) Source # 
Instance details

Defined in Foreign.R.Internal

Methods

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

show :: SomeSEXP s -> String #

showList :: [SomeSEXP s] -> ShowS #

NFData (SomeSEXP s) Source # 
Instance details

Defined in Foreign.R.Internal

Methods

rnf :: SomeSEXP s -> () #

PrintR (SomeSEXP s) Source # 
Instance details

Defined in H.Prelude.Interactive

Methods

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

Literal (SomeSEXP s) 'Any Source # 
Instance details

Defined in Language.R.Literal

Methods

mkSEXPIO :: SomeSEXP s -> IO (SEXP V 'Any) Source #

fromSEXP :: SEXP s0 'Any -> SomeSEXP s 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

Instances details
ToJSON (SEXP s a) Source # 
Instance details

Defined in Language.R.Debug

Methods

toJSON :: SEXP s a -> Value #

toEncoding :: SEXP s a -> Encoding #

toJSONList :: [SEXP s a] -> Value #

toEncodingList :: [SEXP s a] -> Encoding #

Storable (SEXP s a) Source # 
Instance details

Defined in Foreign.R.Internal

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

Show (SEXP s a) Source # 
Instance details

Defined in Foreign.R.Internal

Methods

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

show :: SEXP s a -> String #

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

NFData (SEXP s a) Source # 
Instance details

Defined in Foreign.R.Internal

Methods

rnf :: SEXP s a -> () #

Eq (SEXP s a) Source # 
Instance details

Defined in Foreign.R.Internal

Methods

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

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

Ord (SEXP s a) Source # 
Instance details

Defined in Foreign.R.Internal

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 #

PrintR (SEXP s a) Source # 
Instance details

Defined in H.Prelude.Interactive

Methods

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

SingI a => Literal (SEXP s a) a Source # 
Instance details

Defined in Language.R.Literal

Methods

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

fromSEXP :: SEXP s0 a -> SEXP s a 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.

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.

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.

install :: MonadR m => String -> m (SEXP V 'Symbol) Source #

Internalize a symbol name.

cancel :: IO () Source #

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

throwR Source #

Arguments

:: MonadR m 
=> SEXP s 'Env

Environment in which to find error.

-> m a 

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.

parseText Source #

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.