Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides an interface for producing a VariableRow
, the
return type of runVariables
. Its goals are to:
- provide Haskell types that mirror types of downstream applications
ingesting the JSON produced from the data in
runVariables
, such thatVariable
values within aVariableRow
can be seamlessly converted to the target type values via JSON. - define the shape of JSON produced from a
VariableRow
for downstream applications to rely on.
Users should only wrap Haskell values in the Variable
type at the end of
the runVariables
computations, using one of the constructors
provided, such as rVector
. Variable
wraps each of the supported target
type systems for inclusion in the inhomogeneous list VariableRow
.
However, in some cases it can be convenient to work directly with the
target type system representations of this module. See RTypeRep
for
details.
Synopsis
- data Variable where
- RVector :: RTypeRepConstraints r => RTypeRep r -> VarAttrs -> Variable
- RFactor :: Factor -> VarAttrs -> Variable
- StypeVector :: RTypeRepConstraints r => Stype r -> VarAttrs -> Variable
- RAtomicVectorElem :: RTypeRepConstraints r => SEXPElem r -> VarAttrs -> Variable
- type VariableRow = [Variable]
- type VariableConstraints a = (ToJSON a, Typeable a, Show a)
- rVector :: RTypeRepConstraints r => Text -> RTypeRep r -> Variable
- rFactor :: AsCharacter a => Text -> a -> Vector Text -> Variable
- stypeVector :: RTypeRepConstraints r => Text -> Stype r -> Variable
- rAtomicVectorElem :: RTypeRepConstraints r => Text -> SEXPElem r -> Variable
- data SEXPTYPE
- type family SEXPElem (s :: SEXPTYPE) = h | h -> s where ...
- data SomeRTypeRep = forall s.RTypeRepConstraints s => SomeRTypeRep (RTypeRep s)
- type RTypeRep (s :: SEXPTYPE) = Vector (Maybe (SEXPElem s))
- type RTypeRepConstraints (s :: SEXPTYPE) = (SingI s, Typeable s, VariableConstraints (SEXPElem s))
- data Factor = MkFactor {}
- factor :: AsCharacter a => a -> Vector Text -> Factor
- data Stype :: SEXPTYPE -> Type
- data StypeAttrs = MkStypeAttrs {}
- data StypeRole
- v_binary :: RTypeRep 'LGLSXP -> StypeAttrs -> Stype 'LGLSXP
- v_continuous :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP
- v_continuous_nonneg :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP
- v_count :: RTypeRep 'INTSXP -> StypeAttrs -> Stype 'INTSXP
- v_nominal :: AsCharacter a => a -> Vector Text -> StypeAttrs -> Stype 'STRSXP
- v_ordered :: AsCharacter (RTypeRep r) => RTypeRep r -> Vector Text -> StypeAttrs -> Stype 'STRSXP
- v_proportion :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP
- class AsRTypeRep s a where
- as_rtyperep :: a -> RTypeRep s
- type AsLogical = AsRTypeRep 'LGLSXP
- type AsInteger = AsRTypeRep 'INTSXP
- type AsNumeric = AsRTypeRep 'REALSXP
- type AsComplex = AsRTypeRep 'CPLSXP
- type AsCharacter = AsRTypeRep 'STRSXP
- as_logical :: AsLogical a => a -> RTypeRep 'LGLSXP
- as_integer :: AsInteger a => a -> RTypeRep 'INTSXP
- as_numeric :: AsNumeric a => a -> RTypeRep 'REALSXP
- as_character :: AsCharacter a => a -> RTypeRep 'STRSXP
- as_list :: AsList v => v -> RTypeRep 'VECSXP
- sort :: Ord (SEXPElem s) => RTypeRep s -> RTypeRep s
- sortUniq :: Ord a => Vector a -> Vector a
- summarizeWith :: (RTypeRep s -> Maybe (SEXPElem s')) -> RTypeRep s -> RTypeRep s'
- as_v_binary :: AsLogical a => a -> StypeAttrs -> Stype 'LGLSXP
- as_v_continuous :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP
- as_v_continuous_nonneg :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP
- as_v_count :: AsInteger a => a -> StypeAttrs -> Stype 'INTSXP
- as_v_proportion :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP
- withSomeRTypeRep :: SomeRTypeRep -> (forall s. RTypeRepConstraints s => RTypeRep s -> t) -> t
- sexpTypeOf :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> SEXPTYPE
- sexpTypeOfErased :: SomeRTypeRep -> SEXPTYPE
Variable type
Variable
, the element type of VariableRow
, exists to ensure as much as
possible that the values computed within an asclepias
application can be
seamlessly converted to one of the supported target type systems downstream.
At present, the conversions all pass through JSON as an intermediary.
Each supported target has an associated variant of Variable
. See the
variant-specific documentation for details.
Programmers building an asclepias
application are intended to wrap their
computations in Variable
only at the final step of the computations in
runVariables
. Variable
intentionally erases the underlying types
it wraps, so as to allow an inhomogeneous list in VariableRow
. That makes
it inconvenient to work with Variable
directly in most cases.
However, users might find it helpful to work with the underlying target
types that Variable
wraps, such as the base R vectors represented by
RTypeRep r
. See the documentation for the respective types for details.
To construct a Variable
, users will use the smart constructors for each
target type, such as rVector
. Each supported target is represented by one
of the variants of Variable
.
Examples
Example of converting a list of '[Bool]' to the target R logical vector and
wrapping in Variable
all in one step.
The printed output shape shown here is determined by the internal type
VariableWrapped
, which provides the JSON output shape, and is used only
for debugging or logging. It contains target-dependent attributes and type
information needed to interpret values of this Variable
in downstream
applications, as read from JSON.
>>>
:set -XOverloadedStrings
>>>
import Variable
>>>
:{
>>>
myVar :: Variable
>>>
myVar = rVector "myVar" $ as_logical [True, False]
>>>
:}
>>>
myVar
MkVariableWrapped {varTarget = "RVector", vals = Array [Bool True,Bool False], attrs = MkVarAttrs {varType = "LGLSXP", varName = "myVar"}, subAttrs = Array []}
Example of using R vector representations for interim computations,
before wrapping the final value in Variable
. R representations are
Vector
s, so you can use all of the utilities of that module.
Since R has no singleton types, e.g. Integer
, only vectors, summarizing
functions such as maximum
must wrap the results of their
computation in a vector again. The utility summarizeWith
is provided to do so as a convenience.
See RTypeRep
for more on how to use R-related types.
>>>
:set -XOverloadedStrings -XDataKinds
>>>
import Variable
>>>
import qualified Data.Vector as V
>>>
:{
>>>
ageAtEvent :: RTypeRep 'REALSXP
>>>
ageAtEvent = as_numeric [51 :: Double, 30, 60]
>>>
maxAgeVar :: Variable
>>>
maxAgeVar = rVector "maxAgeVar" $ summarizeWith V.maximum ageAtEvent
>>>
:}
>>>
maxAgeVar
MkVariableWrapped {varTarget = "RVector", vals = Array [Number 60.0], attrs = MkVarAttrs {varType = "REALSXP", varName = "maxAgeVar"}, subAttrs = Array []}
RVector :: RTypeRepConstraints r => RTypeRep r -> VarAttrs -> Variable | A subset of base R vector types, those listed among |
RFactor :: Factor -> VarAttrs -> Variable | The unordered |
StypeVector :: RTypeRepConstraints r => Stype r -> VarAttrs -> Variable | Vectors defined in the R |
RAtomicVectorElem :: RTypeRepConstraints r => SEXPElem r -> VarAttrs -> Variable | Element of an 'RTypeRep r'. R has no singleton type for its atomic
vectors. However, it is sometimes convenient when processing data row-wise
to indicate to the downstream consumer that the |
Instances
ToJSON Variable Source # | |
Defined in Variable.Variable toEncoding :: Variable -> Encoding toJSONList :: [Variable] -> Value toEncodingList :: [Variable] -> Encoding | |
Show Variable Source # | |
type VariableRow = [Variable] Source #
A VariableRow
is the output type of runVariables
and is the collection
of computed values associated with each ObsUnit
of a Cohort
. It can be
thought of as a row of data for a given observational unit in a given
cohort, with each component Variable
giving a particular column's value
for that observational unit.
See Variable
for details.
JSON shape
This section describes the JSON shape produced by a single VariableRow
.
The JSON will include one element of this shape for each ObsUnit
.
See the top-level Hasklepias
module documentation for an overview of the
full JSON output shape produced by an asclepias
cohort-building
application.
JSON output from a VariableRow
is an array
, each element of which is an
object
with shape demonstrated by the following example:
{ "varTarget": StypeVector, "attrs": { "varName": "ageAtIndex", "varType": INTSXP }, "subAttrs": { "long_label": "Age at day of index, computed from January 7 of smallest provided birth year.", "short_label": "Age at day of index", "special_attrs": [ "91" ], "study_role": null, "stypeType": "v_nominal" }, "vals": [ 91 ] }
- "varTarget" identifies the supported target type this data was
constructed from, corresponding to one of the
Variable
variant names. - "attrs" is an
object
withstring
fields defining the variable name and target variable type. In this example, the target is aninteger
vector in R with name "ageAtIndex". - "subAttrs" is an
object
that can vary based on the "varTarget". A StypeVector takes additional context. If the "varTarget" were RVector, indicating one of the base RSEXPTYPE
s, this field would benull
. - "vals" contains the values of the
Variable
. At present, only R-related vector types are supported and hence "vals" will always be anarray
. The JSON type of elements in this array will differ based on the "varTarget" and "varType". At present, elements will either be of one of the atomic JSON types (null
,bool
,number
,string
) or will be of the same shape as the JSONVariable
displayed above, in the case of"varType": VECSXP
, representing an R list.
type VariableConstraints a = (ToJSON a, Typeable a, Show a) Source #
Variable constructors
rFactor :: AsCharacter a => Text -> a -> Vector Text -> Variable Source #
Constructor for RFactor
with the given name as first argument, values
as second argument and levels
as third. Calls factor
, which is
associated to an unordered factor
in R. Note the varType
always is
STRSXP
and not the SEXPTYPE
of the input, in keeping with the R
implementation in which factor
variables are backed by character vectors.
stypeVector :: RTypeRepConstraints r => Text -> Stype r -> Variable Source #
Constructor for StypeVector
with the given name as first argument. To
produce a Stype
, use one of the v_*
constructors such as
v_binary
or as_v_binary
.
rAtomicVectorElem :: RTypeRepConstraints r => Text -> SEXPElem r -> Variable Source #
Supported downstream type representations
R vectors
Instances
Show SEXPTYPE Source # | |
Eq SEXPTYPE Source # | |
SingKind SEXPTYPE Source # | |
SingI 'CPLSXP Source # | |
Defined in Variable.R.SEXP | |
SingI 'INTSXP Source # | |
Defined in Variable.R.SEXP | |
SingI 'LGLSXP Source # | |
Defined in Variable.R.SEXP | |
SingI 'REALSXP Source # | |
Defined in Variable.R.SEXP | |
SingI 'STRSXP Source # | |
Defined in Variable.R.SEXP | |
SingI 'VECSXP Source # | |
Defined in Variable.R.SEXP | |
type Demote SEXPTYPE Source # | |
Defined in Variable.R.SEXP | |
type Sing Source # | |
Defined in Variable.R.SEXP type Sing |
data SomeRTypeRep Source #
Existential type used within inhomogeneous lists of R vectors, in
RTypeRep 'VECSXP
.
forall s.RTypeRepConstraints s => SomeRTypeRep (RTypeRep s) |
Instances
ToJSON SomeRTypeRep Source # | |
Defined in Variable.R.SEXP toJSON :: SomeRTypeRep -> Value toEncoding :: SomeRTypeRep -> Encoding toJSONList :: [SomeRTypeRep] -> Value toEncodingList :: [SomeRTypeRep] -> Encoding | |
Show SomeRTypeRep Source # | |
Defined in Variable.R.SEXP showsPrec :: Int -> SomeRTypeRep -> ShowS # show :: SomeRTypeRep -> String # showList :: [SomeRTypeRep] -> ShowS # |
type RTypeRep (s :: SEXPTYPE) = Vector (Maybe (SEXPElem s)) Source #
'RTypeRep s' is a Haskell representation of s
, an SEXPTYPE
, in R.
Nothing
elements represent NA
values.
R SEXP vector types do not distinguish between vectors and their elements,
but Haskell does. SEXPElem
provides a one-to-one correspondence between
'Vector (Maybe a)' and the supported SEXPTYPE
s in R by providing a map
between the a
and its corresponding Haskell type. 'SEXPElem s' for some
SEXPTYPE
s
is chosen such that the conversion from a Haskell value of
type 'RTypeRep s' and the R type s
is as seamless as possible.
Each 'SEXPElem s' is wrapped in Maybe
within an 'RTypeRep s' to allow for
typed NA
values in R. For example, Nothing
in an RTypeRep 'LGLSXP
corresponds to NA_logical_
.
A Haskell programmer can work with 'RTypeRep s' types directly, with little
to no overhead relative to working with any other 'Data.Vector.Vector (Maybe
a)'. Some additional utilities to facilitate conversions are provided as
part of the AsRTypeRep
class with various aliases, e.g. AsLogical
. See
the examples.
To work with RTypeRep
directly you will need at a minimum the DataKinds
extension, and in many cases also the TypeFamilies
and FlexibleContexts
extensions.
Examples
The following mimics R's mean
function behavior, with an `na.rm` argument
removing NA
values. It is generic over types that can be converted to
RTypeRep 'REALSXP
. The auxiliary function mean
returns 'NaN :: Double'
on an empty vector.
>>>
:set -XOverloadedStrings -XDataKinds -XFlexibleContexts
>>>
import Variable
>>>
import qualified Data.Vector as V
>>>
import GHC.Float (int2Double)
>>>
:{
>>>
mean :: V.Vector Double -> Double
>>>
mean v = V.sum v / int2Double (V.length v)
>>>
>>>
rMean :: (AsNumeric a) => Bool -> a -> RTypeRep 'REALSXP
>>>
rMean narm = summarizeWith (op narm) . as_numeric
>>>
where op True = Just . mean . V.catMaybes
>>>
op False = fmap mean . V.sequence
>>>
:}
>>>
rMean False (as_integer [True, True]) == V.singleton (Just 1)
True>>>
rMean False (as_integer [1, 2]) == V.singleton (Just 1.5)
True>>>
rMean True (as_integer [Just 1, Just 2, Nothing]) == V.singleton (Just 1.5)
True>>>
rMean False (as_integer [Just 1, Just 2, Nothing]) == V.singleton Nothing
True
R list representation
RTypeRep 'VECSXP
is worth a few comments, as it presents the greatest
challenge for matching to Haskell's type system:
- R's list type can be named or unnamed, with the latter case meaning that
`names(xs)` is
NULL
.RTypeRep 'VECSXP
is a vector of key-value pairs, and therefore each element has a name. Unnamed lists are represented byRTypeRep 'VECSXP
with names matching the index of the list. - R lists are inhomogeneous, unlike the atomic vectors. That is captured in
the existential type
SomeRTypeRep
, providing the value of each key-value pair within aRTypeRep 'VECSXP
. Type information about theRTypeRep s
stored inSomeRTypeRep
can be recovered using tools from thesingletons
package. See the "Advanced usage" section. Nothing
elements withinRTypeRep 'VECSXP
have no equivalent in R and hence probably should not be used.
Some caveats
- At present, all conversions will pass through JSON, via types
in the
aeson
package, and to R via thejsonlite
package. Therefore, the conversion fromRTypeRep
to its R counterpart depends on those interim conversions, and in particular on the conversion from numeric types (INTSXP
,REALSXP
etc.) toScientific
, from thescientific
package in Haskell. - It is unclear how close the Haskell
Double
corresponds to an element of R'snumeric
orREALSXP
vector. Documentation for both Haskell and R state the types conform to the IEEE double-precision standard, in other words the binary64 format. and which has precision of 16 decimal digits, with maximum values of `2e308`. Haskell's documentation is less clear on that point and leaves open the possibility of greater precision.
Advanced usage
Users can take advantage of the tools from the singletons
package to
extract do type-level programming with RTypeRep
, including recovering the
type erased within SomeRTypeRep
. See sexpTypeOfErased
and as_list
for
an example.
type RTypeRepConstraints (s :: SEXPTYPE) = (SingI s, Typeable s, VariableConstraints (SEXPElem s)) Source #
Constraints for SomeRTypeRep
.
R factors, ordered and unordered
Haskell representation of R's factor
, either ordered or unordered.
Construct with factor
or ordered
, preferably.
Instances
ToJSON Factor Source # | |
Defined in Variable.R.Factor toEncoding :: Factor -> Encoding toJSONList :: [Factor] -> Value toEncodingList :: [Factor] -> Encoding | |
Generic Factor Source # | |
Show Factor Source # | |
Eq Factor Source # | |
Ord Factor Source # | |
type Rep Factor Source # | |
Defined in Variable.R.Factor type Rep Factor = D1 ('MetaData "Factor" "Variable.R.Factor" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "MkFactor" 'PrefixI 'True) (S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RTypeRep 'STRSXP)) :*: S1 ('MetaSel ('Just "levels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Text)))) |
factor :: AsCharacter a => a -> Vector Text -> Factor Source #
Constructor for Factor
. as_character
is called on the first argument.
User provided levels
in the second argument are sorted and made unique
with sortUniq
.
Important: As in R, elements of the input vector that do not appear among
the levels
(after conversion with as_character
) are marked as invalid,
here represented by Nothing
. That check has an \(O(nm)\) runtime cost,
where n is the length of the input and m the length of the levels.
To avoid that cost, users can use MkConstructor
directly but must
themselves ensure all values
appear in the levels
.
Stype vectors
data Stype :: SEXPTYPE -> Type Source #
Haskell representatives of vector types from the stype
R
package. Parameterized
by the "prototype" SEXP
backing the type. For types such as
ContinuousNonneg
, with constrained domains not represented in the standard
Haskell types, the constraints are enforced in the `v_*` constructors, as in
stype
.
Stype
vectors must always be created with their corresponding
StypeAttrs
. However, to reduce the overhead in some cases, they can be
constructed with `as_v_*` functions calling the appropriate `as_*` coercion
functions from SEXP
to create the underlying RTypeRep
directly from some other Haskell type.
To work with Stype
vectors directly, you will want DataKinds
.
Examples
>>>
:set -XOverloadedStrings -XDataKinds
>>>
import Variable
>>>
:{
>>>
src_dbl :: [Maybe Double]
>>>
src_dbl = Nothing : map Just [1, 0.5, 0]
>>>
ctx = MkStypeAttrs "important_var" "A very important variable" Nothing
>>>
v = as_v_proportion src_dbl ctx
:}>>>
v
Proportion [Nothing,Just 1.0,Just 0.5,Just 0.0] MkStypeAttrs {short_label = "important_var", long_label = "A very important variable", study_role = Nothing}
data StypeAttrs Source #
User-provided stype common attributes. SEXPTYPE
and name information is
purposefully ommitted, since that will appear in
VariableAttrs
.
MkStypeAttrs | |
|
Instances
Indication of variable role.
Constructors
v_binary :: RTypeRep 'LGLSXP -> StypeAttrs -> Stype 'LGLSXP Source #
Build a Binary
from RTypeRep 'LGLSXP
and StypeAttrs. Aliases
constructor in this case.
v_continuous :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP Source #
Build a Continuous
from RTypeRep 'REALSXP
and StypeAttrs
. Aliases
constructor.
v_continuous_nonneg :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP Source #
Build a ContinuousNonneg
from RTypeRep 'REALSXP
and StypeAttrs
.
This converts negative elements to NA, unlike the R function with the same
name, which throws an error.
v_count :: RTypeRep 'INTSXP -> StypeAttrs -> Stype 'INTSXP Source #
Build a Count
from the RTypeRep 'INTSXP
and StypeAttrs
. This
converts negative elements to NA, unlike the R function with the same name,
which throws an error.
v_nominal :: AsCharacter a => a -> Vector Text -> StypeAttrs -> Stype 'STRSXP Source #
v_ordered :: AsCharacter (RTypeRep r) => RTypeRep r -> Vector Text -> StypeAttrs -> Stype 'STRSXP Source #
Build a Ordered
with provided levels
as second argument. The 'RTypeRep
r' will be converted to a Factor
via factor
. At present, it is the unescapeArgs
responsibility to ensure the provided levels are in the desired order by values, not
the lexicographical order on the character vector (in R speak) of factor
.
v_proportion :: RTypeRep 'REALSXP -> StypeAttrs -> Stype 'REALSXP Source #
Build a Proportion
from RTypeRep 'REALSXP
and StypeAttrs
. This
converts elements less than 0 or greater than 1 to NA, unlike the R function
with the same name, which throws an error.
Utilities
For casting to R vectors
class AsRTypeRep s a where Source #
Convert Haskell types to 'RTypeRep s'. It is up to the user to define
conversions in a manner consistent with R's behavior. Nothing
elements of
an 'RTypeRep s' correspond to the NA
value in R, where appropriate.
Note: It never makes sense to produce a Nothing
element within an
RTypeRep 'VECSXP
.
as_rtyperep :: a -> RTypeRep s Source #
Instances
type AsLogical = AsRTypeRep 'LGLSXP Source #
type AsInteger = AsRTypeRep 'INTSXP Source #
type AsNumeric = AsRTypeRep 'REALSXP Source #
type AsComplex = AsRTypeRep 'CPLSXP Source #
type AsCharacter = AsRTypeRep 'STRSXP Source #
as_character :: AsCharacter a => a -> RTypeRep 'STRSXP Source #
Analogous to R's as.character
. Includes versions to directly construct
character vectors from lists or vector containing Show elements.
as_list :: AsList v => v -> RTypeRep 'VECSXP Source #
as_list v
is analogous to R's as.list(v)
for v
of the supported
RTypeRep s
. Note R's ...
syntax is not supported here. The constraints
provided are those of SomeRTypeRep
.
For manipulating R vectors
sortUniq :: Ord a => Vector a -> Vector a Source #
Sort a Vector
and return unique elements using
sortUniq
.
summarizeWith :: (RTypeRep s -> Maybe (SEXPElem s')) -> RTypeRep s -> RTypeRep s' Source #
R has no element-of-vector type, only vector types. This utiltity takes Haskell functions that summarize an R vector, and wrap the output in the appropriate RTypeRep, as a singleton, mimicing what R would do and (I hope) lowering the overhead.
For casting to Stype vectors
as_v_binary :: AsLogical a => a -> StypeAttrs -> Stype 'LGLSXP Source #
Construct a Binary
from any a
that can be converted to RTypeRep
'LGLSXP
.
as_v_continuous :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP Source #
Construct a Continuous
from any a
that can be converted to RTypeRep
'REALSXP
.
as_v_continuous_nonneg :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP Source #
Attempt to construct a ContinuousNonneg
from any a
that can be
converted to RTypeRep 'REALSXP
.
as_v_count :: AsInteger a => a -> StypeAttrs -> Stype 'INTSXP Source #
Attempt to build a Count
from any a
that can be converted to RTypeRep
'INTSXP
.
as_v_proportion :: AsNumeric a => a -> StypeAttrs -> Stype 'REALSXP Source #
Attempt to build a Proportion
from an a
that can be converted to
RTypeRep 'REALSXP
.
For type-level programming
withSomeRTypeRep :: SomeRTypeRep -> (forall s. RTypeRepConstraints s => RTypeRep s -> t) -> t Source #
Run a routine with SomeRTypeRep
, whose 'RTypeRep s' type you cannot
inspect.
sexpTypeOf :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> SEXPTYPE Source #
Return the SEXPTYPE
of an 'RTypeRep (s :: SEXPTYPE)'.
>>>
sexpTypeOf (V.fromList [True]) == LGLSXP
>>>
sexpTypeOf (V.fromList [1 :: Double]) == REALSXP
sexpTypeOfErased :: SomeRTypeRep -> SEXPTYPE Source #
Recover the 'Sing r' from SomeRTypeRep
, which recovers the type
information lost in the existential type.