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

Language.R.HExp

Description

Provides a shallow view of a SEXP R value as an algebraic datatype. This is useful to define functions over R values in Haskell with pattern matching. For example:

toPair :: SEXP a -> (SomeSEXP, SomeSEXP)
toPair (hexp -> List _ (Just car) (Just cdr)) = (SomeSEXP car, SomeSEXP cdr)
toPair (hexp -> Lang car (Just cdr)) = (SomeSEXP car, SomeSEXP cdr)
toPair s = error $ "Cannot extract pair from object of type " ++ typeOf s

(See SomeSEXP for why we need to use it here.)

The view is said to be shallow because it only unfolds the head of the R value into an algebraic datatype. In this way, functions producing views can be written non-recursively, hence inlined at all call sites and simplified away. When produced by a view function in a pattern match, allocation of the view can be compiled away and hence producing a view can be done at no runtime cost. In fact, pattern matching on a view in this way is more efficient than using the accessor functions defined in Foreign.R, because we avoid the overhead of calling one or more FFI functions entirely.

HExp is the view and hexp is the view function that projects SEXPs into HExp views.

Synopsis

Documentation

data HExp :: * -> SEXPTYPE -> * where Source #

A view of R's internal SEXP structure as an algebraic datatype. Because this is in fact a GADT, the use of named record fields is not possible here. Named record fields give rise to functions for whom it is not possible to assign a reasonable type (existentially quantified type variables would escape).

See https://cran.r-project.org/doc/manuals/r-release/R-ints.html#SEXPTYPEs.

Constructors

Nil :: HExp s 'Nil

The NULL value (NILSXP).

Symbol

A symbol (SYMSXP).

Fields

List

A list (LISTSXP).

Fields

Env

An environment (ENVSXP).

Fields

Closure

A closure (CLOSXP).

Fields

Promise

A promise (PROMSXP).

Fields

Lang

Language objects (LANGSXP) are calls (including formulae and so on). Internally they are pairlists with first element a reference to the function to be called with remaining elements the actual arguments for the call (and with the tags if present giving the specified argument names). Although this is not enforced, many places in the R code assume that the pairlist is of length one or more, often without checking.

Fields

Special :: HExp s 'Special

A special (built-in) function call (SPECIALSXP). It carries an offset into the table of primitives but for our purposes is opaque.

Builtin :: HExp s 'Builtin

A BUILTINSXP. This is similar to Special, except the arguments to a Builtin are always evaluated.

Char :: !(Vector 'Char Word8) -> HExp s 'Char

An internal character string (CHARSXP).

Logical :: !(Vector 'Logical Logical) -> HExp s 'Logical

A logical vector (LGLSXP).

Int :: !(Vector 'Int Int32) -> HExp s 'Int

An integer vector (INTSXP).

Real :: !(Vector 'Real Double) -> HExp s 'Real

A numeric vector (REALSXP).

Complex :: !(Vector 'Complex (Complex Double)) -> HExp s 'Complex

A complex vector (CPLXSXP).

String :: !(Vector 'String (SEXP V 'Char)) -> HExp s 'String

A character vector (STRSXP).

DotDotDot

A special type of LISTSXP for the value bound to a ... symbol

Fields

Vector

A list/generic vector (VECSXP).

Fields

Expr

An expression vector (EXPRSXP).

Fields

Bytecode :: HExp s 'Bytecode

A ‘byte-code’ object generated by R (BCODESXP).

ExtPtr

An external pointer (EXTPTRSXP)

Fields

WeakRef

A weak reference (WEAKREFSXP).

Fields

Raw :: !(Vector 'Raw Word8) -> HExp s 'Raw

A raw vector (RAWSXP).

S4

An S4 class which does not consist solely of a simple type such as an atomic vector or function (S4SXP).

Fields

Instances

Instances details
TestEquality (HExp s :: SEXPTYPE -> Type) Source # 
Instance details

Defined in Language.R.HExp

Methods

testEquality :: forall (a :: k) (b :: k). HExp s a -> HExp s b -> Maybe (a :~: b) #

Eq (HExp s a) Source # 
Instance details

Defined in Language.R.HExp

Methods

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

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

(===) :: TestEquality f => f a -> f b -> Bool Source #

Heterogeneous equality.

hexp :: SEXP s a -> HExp s a Source #

A view function projecting a view of SEXP as an algebraic datatype, that can be analyzed through pattern matching.

vector :: IsVector a => SEXP s a -> Vector a (ElemRep V a) Source #

Project the vector out of SEXPs.