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

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 SEXPTYPE, and so does the value of this expression, 2, have type SEXPTYPE. 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

Instances details
ToJSON SEXPTYPE Source # 
Instance details

Defined in Language.R.Debug

Enum SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

Show SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

NFData SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

Methods

rnf :: SEXPTYPE -> () #

Eq SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

Ord SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

SingKind SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

Associated Types

type Demote SEXPTYPE = (r :: Type) #

SingI 'Any Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Any #

SingI 'Builtin Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Builtin #

SingI 'Bytecode Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Bytecode #

SingI 'Char Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Char #

SingI 'Closure Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Closure #

SingI 'Complex Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Complex #

SingI 'DotDotDot Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'DotDotDot #

SingI 'Env Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Env #

SingI 'Expr Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Expr #

SingI 'ExtPtr Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'ExtPtr #

SingI 'Free Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Free #

SingI 'Fun Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Fun #

SingI 'Int Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Int #

SingI 'Lang Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Lang #

SingI 'List Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'List #

SingI 'Logical Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Logical #

SingI 'New Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'New #

SingI 'Nil Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Nil #

SingI 'Promise Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Promise #

SingI 'Raw Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Raw #

SingI 'Real Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Real #

SingI 'S4 Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'S4 #

SingI 'Special Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Special #

SingI 'String Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'String #

SingI 'Symbol Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Symbol #

SingI 'Vector Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'Vector #

SingI 'WeakRef Source # 
Instance details

Defined in Foreign.R.Type

Methods

sing :: Sing 'WeakRef #

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

Lift SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

Methods

lift :: Quote m => SEXPTYPE -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SEXPTYPE -> Code m SEXPTYPE #

type Demote SEXPTYPE Source # 
Instance details

Defined in Foreign.R.Type

type Sing Source # 
Instance details

Defined in Foreign.R.Type

type family Sing :: k -> Type #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Foreign.R.Type

type Sing 
Instance details

Defined in Data.Singletons

type Sing 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> Type

data Logical Source #

R uses three-valued logic.

Constructors

FALSE 
TRUE 
NA 

Instances

Instances details
Storable Logical Source # 
Instance details

Defined in Foreign.R.Context

Show Logical Source # 
Instance details

Defined in Foreign.R.Context

Eq Logical Source # 
Instance details

Defined in Foreign.R.Context

Methods

(==) :: Logical -> Logical -> Bool #

(/=) :: Logical -> Logical -> Bool #

Ord Logical Source # 
Instance details

Defined in Foreign.R.Context

Literal Logical 'Logical Source # 
Instance details

Defined in Language.R.Literal

Literal [Logical] 'Logical Source # 
Instance details

Defined in Language.R.Literal

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.