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

Description

Definition of SEXPTYPE, which classifies the possible forms of an R expression (a SEXP). It is normally not necessary to import this module directly, since it is reexported by Foreign.R.

This is done in a separate module because we want to use hsc2hs rather than c2hs for discharging the boilerplate around SEXPTYPE. This is because SEXPTYPE is nearly but not quite a true enumeration and c2hs has trouble dealing with that.

This module also defines a singleton version of SEXPTYPE, called SSEXPTYPE. This is actually a family of types, one for each possible SEXPTYPE. Singleton types are a way of emulating dependent types in a language that does not have true dependent type. They are useful in functions whose result type depends on the value of one of its arguments. See e.g. allocVector.

Synopsis

Documentation

data SEXPTYPE Source #

R "type". Note that what R calls a "type" is not what is usually meant by the term: there is really only a single type, called SEXP, and an R "type" in fact refers to the class or form of the expression.

To better illustrate the distinction, note that any sane type system normally has the subject reduction property: that the type of an expression is invariant under reduction. For example, (x -> x) 1 has type Int, and so does the value of this expression, 2, have type Int. Yet the form of the expression is an application of a function to a literal, while the form of its reduct is an integer literal.

We introduce convenient Haskell-like names for forms because this datatype is used to index SEXP and other types through the DataKinds extension.

Instances

Enum SEXPTYPE Source # 
Eq SEXPTYPE Source # 
Ord SEXPTYPE Source # 
Show SEXPTYPE Source # 
Lift SEXPTYPE Source # 

Methods

lift :: SEXPTYPE -> Q Exp #

NFData SEXPTYPE Source # 

Methods

rnf :: SEXPTYPE -> () #

SingKind SEXPTYPE Source # 

Associated Types

type Demote SEXPTYPE = (r :: *)

Methods

fromSing :: Sing SEXPTYPE a -> Demote SEXPTYPE

toSing :: Demote SEXPTYPE -> SomeSing SEXPTYPE

SingI SEXPTYPE Nil Source # 

Methods

sing :: Sing Nil a

SingI SEXPTYPE Symbol Source # 

Methods

sing :: Sing Symbol a

SingI SEXPTYPE List Source # 

Methods

sing :: Sing List a

SingI SEXPTYPE Closure Source # 

Methods

sing :: Sing Closure a

SingI SEXPTYPE Env Source # 

Methods

sing :: Sing Env a

SingI SEXPTYPE Promise Source # 

Methods

sing :: Sing Promise a

SingI SEXPTYPE Lang Source # 

Methods

sing :: Sing Lang a

SingI SEXPTYPE Special Source # 

Methods

sing :: Sing Special a

SingI SEXPTYPE Builtin Source # 

Methods

sing :: Sing Builtin a

SingI SEXPTYPE Char Source # 

Methods

sing :: Sing Char a

SingI SEXPTYPE Logical Source # 

Methods

sing :: Sing Logical a

SingI SEXPTYPE Int Source # 

Methods

sing :: Sing Int a

SingI SEXPTYPE Real Source # 

Methods

sing :: Sing Real a

SingI SEXPTYPE Complex Source # 

Methods

sing :: Sing Complex a

SingI SEXPTYPE String Source # 

Methods

sing :: Sing String a

SingI SEXPTYPE DotDotDot Source # 

Methods

sing :: Sing DotDotDot a

SingI SEXPTYPE Any Source # 

Methods

sing :: Sing Any a

SingI SEXPTYPE Vector Source # 

Methods

sing :: Sing Vector a

SingI SEXPTYPE Expr Source # 

Methods

sing :: Sing Expr a

SingI SEXPTYPE Bytecode Source # 

Methods

sing :: Sing Bytecode a

SingI SEXPTYPE ExtPtr Source # 

Methods

sing :: Sing ExtPtr a

SingI SEXPTYPE WeakRef Source # 

Methods

sing :: Sing WeakRef a

SingI SEXPTYPE Raw Source # 

Methods

sing :: Sing Raw a

SingI SEXPTYPE S4 Source # 

Methods

sing :: Sing S4 a

SingI SEXPTYPE New Source # 

Methods

sing :: Sing New a

SingI SEXPTYPE Free Source # 

Methods

sing :: Sing Free a

SingI SEXPTYPE Fun Source # 

Methods

sing :: Sing Fun a

TestEquality SEXPTYPE (HExp s) # 

Methods

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

type Demote SEXPTYPE Source # 
type Demote SEXPTYPE = SEXPTYPE
data Sing SEXPTYPE Source # 

data family Sing k (a :: k) :: * #

Instances

data Sing Bool 
data Sing Bool where
data Sing Ordering 
data Sing Nat 
data Sing Nat where
data Sing Symbol 
data Sing Symbol where
data Sing () 
data Sing () where
data Sing SEXPTYPE # 
data Sing [a] 
data Sing [a] where
data Sing (Maybe a) 
data Sing (Maybe a) where
data Sing (NonEmpty a) 
data Sing (NonEmpty a) where
data Sing (Either a b) 
data Sing (Either a b) where
data Sing (a, b) 
data Sing (a, b) where
data Sing ((~>) k1 k2) 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a, b, c) 
data Sing (a, b, c) where
data Sing (a, b, c, d) 
data Sing (a, b, c, d) where
data Sing (a, b, c, d, e) 
data Sing (a, b, c, d, e) where
data Sing (a, b, c, d, e, f) 
data Sing (a, b, c, d, e, f) where
data Sing (a, b, c, d, e, f, g) 
data Sing (a, b, c, d, e, f, g) where

type PairList = List Source #

Used where the R documentation speaks of "pairlists", which are really just regular lists.

type IsVector (a :: SEXPTYPE) = (SingI a, a :∈ (Char ': (Logical ': (Int ': (Real ': (Complex ': (String ': (Vector ': (Expr ': (WeakRef ': (Raw ': '[]))))))))))) Source #

Constraint synonym grouping all vector forms into one class. IsVector a holds iff R's is.vector() returns TRUE.

type IsGenericVector (a :: SEXPTYPE) = (SingI a, a :∈ [Vector, Expr, WeakRef]) Source #

Non-atomic vector forms. See src/main/memory.c:SET_VECTOR_ELT in the R source distribution.

type IsList (a :: SEXPTYPE) = (SingI a, a :∈ (Char ': (Logical ': (Int ': (Real ': (Complex ': (String ': (Vector ': (Expr ': (WeakRef ': (Raw ': (List ': '[])))))))))))) Source #

IsList a holds iff R's is.list() returns TRUE.

type IsPairList (a :: SEXPTYPE) = (SingI a, a :∈ [List, Nil]) Source #

IsPairList a holds iff R's is.pairlist() returns TRUE.

type IsExpression (a :: SEXPTYPE) = (SingI a, a :∈ [Lang, Expr, Symbol]) Source #

Constraint synonym grouping all expression forms into one class. According to R internals, an expression is usually a Lang, but can sometimes also be an Expr or a Symbol.