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

Safe HaskellNone
LanguageHaskell2010

Language.R.HExp

Description

 

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

Note further that Haddock does not currently support constructor comments when using the GADT syntax.

Constructors

Nil :: HExp s Nil 
Symbol :: a :∈ '[Char, Nil] => SEXP s a -> SEXP s b -> SEXP s c -> HExp s Symbol 
List :: (IsPairList b, c :∈ '[Symbol, Nil]) => SEXP s a -> SEXP s b -> SEXP s c -> HExp s List 
Env :: (IsPairList a, b :∈ '[Env, Nil], c :∈ '[Vector, Nil]) => SEXP s a -> SEXP s b -> SEXP s c -> HExp s Env 
Closure :: IsPairList a => SEXP s a -> SEXP s b -> SEXP s Env -> HExp s Closure 
Promise :: (IsExpression b, c :∈ '[Env, Nil]) => SEXP s a -> SEXP s b -> SEXP s c -> HExp s Promise 
Lang :: (IsExpression a, IsPairList b) => SEXP s a -> SEXP s b -> HExp s Lang 
Special :: !Int32 -> HExp s Special 
Builtin :: !Int32 -> HExp s Builtin 
Char :: !(Vector s Char Word8) -> HExp s Char 
Logical :: !(Vector s Logical Logical) -> HExp s Logical 
Int :: !(Vector s Int Int32) -> HExp s Int 
Real :: !(Vector s Real Double) -> HExp s Real 
Complex :: !(Vector s Complex (Complex Double)) -> HExp s Complex 
String :: !(Vector s String (SEXP s Char)) -> HExp s String 
DotDotDot :: IsPairList a => SEXP s a -> HExp s List 
Vector :: !Int32 -> !(Vector s Vector (SomeSEXP s)) -> HExp s Vector 
Expr :: !Int32 -> !(Vector s Expr (SomeSEXP s)) -> HExp s Expr 
Bytecode :: HExp s Bytecode 
ExtPtr :: Ptr () -> SEXP s b -> SEXP s Symbol -> HExp s ExtPtr 
WeakRef :: (a :∈ '[Env, ExtPtr, Nil], c :∈ '[Closure, Builtin, Special, Nil], d :∈ '[WeakRef, Nil]) => SEXP s a -> SEXP s b -> SEXP s c -> SEXP s d -> HExp s WeakRef 
Raw :: !(Vector s Raw Word8) -> HExp s Raw 
S4 :: SEXP s a -> HExp s S4 

Instances

TestEquality SEXPTYPE (HExp s) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((HExp s :~: a) b) #

Eq (HExp s a) Source # 

Methods

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

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

Storable (HExp s a) Source # 

Methods

sizeOf :: HExp s a -> Int #

alignment :: HExp s a -> Int #

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

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

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

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

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

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

(===) :: 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.

unhexp :: MonadR m => HExp (Region m) a -> m (SEXP (Region m) a) Source #

Inverse hexp view to the real structure, note that for scalar types hexp will allocate new SEXP, and unhexp . hexp is not an identity function. however for vector types it will return original SEXP.

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

Project the vector out of SEXPs.