| Copyright | (C) 2013 Amgen Inc. | 
|---|---|
| Safe Haskell | None | 
| Language | Haskell2010 | 
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.
- data SEXPTYPE
- type SSEXPTYPE = (Sing :: SEXPTYPE -> Type)
- data family Sing k (a :: k) :: *
- data Logical
- type PairList = List
- type IsVector (a :: SEXPTYPE) = (SingI a, a :∈ (Char ': (Logical ': (Int ': (Real ': (Complex ': (String ': (Vector ': (Expr ': (WeakRef ': (Raw ': '[])))))))))))
- type IsGenericVector (a :: SEXPTYPE) = (SingI a, a :∈ [Vector, Expr, WeakRef])
- type IsList (a :: SEXPTYPE) = (SingI a, a :∈ (Char ': (Logical ': (Int ': (Real ': (Complex ': (String ': (Vector ': (Expr ': (WeakRef ': (Raw ': (List ': '[]))))))))))))
- type IsPairList (a :: SEXPTYPE) = (SingI a, a :∈ [List, Nil])
- type IsExpression (a :: SEXPTYPE) = (SingI a, a :∈ [Lang, Expr, Symbol])
Documentation
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.
Constructors
| Nil | |
| Symbol | |
| List | |
| Closure | |
| Env | |
| Promise | |
| Lang | |
| Special | |
| Builtin | |
| Char | |
| Logical | |
| Int | |
| Real | |
| Complex | |
| String | |
| DotDotDot | |
| Any | |
| Vector | |
| Expr | |
| Bytecode | |
| ExtPtr | |
| WeakRef | |
| Raw | |
| S4 | |
| New | |
| Free | |
| Fun | 
Instances
data family Sing k (a :: k) :: * #
Instances
| data Sing Bool | |
| data Sing Ordering | |
| data Sing Nat | |
| data Sing Symbol | |
| data Sing () | |
| data Sing SEXPTYPE # | |
| data Sing [a] | |
| data Sing (Maybe a) | |
| data Sing (NonEmpty a) | |
| data Sing (Either a b) | |
| data Sing (a, b) | |
| data Sing ((~>) k1 k2) | |
| data Sing (a, b, c) | |
| data Sing (a, b, c, d) | |
| data Sing (a, b, c, d, e) | |
| data Sing (a, b, c, d, e, f) | |
| data Sing (a, b, c, d, e, f, g) | |
R uses three-valued logic.
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.