hasklepias-core-0.30.3: Domain-aware tools and types for constructing epidemiological cohorts
Safe HaskellSafe-Inferred
LanguageHaskell2010

Variable

Description

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 that Variable values within a VariableRow 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

Variable type

data Variable where Source #

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

Expand

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
[]}

Constructors

RVector :: RTypeRepConstraints r => RTypeRep r -> VarAttrs -> Variable

A subset of base R vector types, those listed among SEXPTYPE, backed by the Haskell types given in RTypeRep. A Variable intended for this target should be constructed with rVector.

RFactor :: Factor -> VarAttrs -> Variable

The unordered factor type in R, backed by the Factor type in Haskell and constructed with rFactor.

StypeVector :: RTypeRepConstraints r => Stype r -> VarAttrs -> Variable

Vectors defined in the R stype package, backed by some Stype and constructed with stypeVector. All but v_rcensored is supported.

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 Variable should be a singleton, to be wrapped in the associated SEXPTYPE vector indicated by parameter r of the input. It is up to the user to ensure r is not 'VECSXP.

Instances

Instances details
ToJSON Variable Source # 
Instance details

Defined in Variable.Variable

Methods

toJSON :: Variable -> Value

toEncoding :: Variable -> Encoding

toJSONList :: [Variable] -> Value

toEncodingList :: [Variable] -> Encoding

Show Variable Source # 
Instance details

Defined in Variable.Variable

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

Expand

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 with string fields defining the variable name and target variable type. In this example, the target is an integer 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 R SEXPTYPE s, this field would be null.
  • "vals" contains the values of the Variable. At present, only R-related vector types are supported and hence "vals" will always be an array. 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 JSON Variable displayed above, in the case of "varType": VECSXP, representing an R list.

type VariableConstraints a = (ToJSON a, Typeable a, Show a) Source #

Variable constructors

rVector :: RTypeRepConstraints r => Text -> RTypeRep r -> Variable Source #

Constructor for RVector with the given name as first argument, automatically producing type attribute information. To produce an RTypeRep, use of the of as_* constructors or produce one directly by constructing the 'Data.Vector.Vector a' with appropriate a, as determined by RTypeRep.

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.

Supported downstream type representations

R vectors

data SEXPTYPE Source #

Instances

Instances details
Show SEXPTYPE Source # 
Instance details

Defined in Variable.R.SEXP

Eq SEXPTYPE Source # 
Instance details

Defined in Variable.R.SEXP

SingKind SEXPTYPE Source # 
Instance details

Defined in Variable.R.SEXP

Associated Types

type Demote SEXPTYPE = (r :: Type)

Methods

fromSing :: forall (a :: SEXPTYPE). Sing a -> Demote SEXPTYPE

toSing :: Demote SEXPTYPE -> SomeSing SEXPTYPE

SingI 'CPLSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'CPLSXP

SingI 'INTSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'INTSXP

SingI 'LGLSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'LGLSXP

SingI 'REALSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'REALSXP

SingI 'STRSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'STRSXP

SingI 'VECSXP Source # 
Instance details

Defined in Variable.R.SEXP

Methods

sing :: Sing 'VECSXP

type Demote SEXPTYPE Source # 
Instance details

Defined in Variable.R.SEXP

type Demote SEXPTYPE = SEXPTYPE
type Sing Source # 
Instance details

Defined in Variable.R.SEXP

type Sing

type family SEXPElem (s :: SEXPTYPE) = h | h -> s where ... Source #

The "element" type of an RTypeRep. See RTypeRep for more.

data SomeRTypeRep Source #

Existential type used within inhomogeneous lists of R vectors, in RTypeRep 'VECSXP.

Constructors

forall s.RTypeRepConstraints s => SomeRTypeRep (RTypeRep s) 

Instances

Instances details
ToJSON SomeRTypeRep Source # 
Instance details

Defined in Variable.R.SEXP

Methods

toJSON :: SomeRTypeRep -> Value

toEncoding :: SomeRTypeRep -> Encoding

toJSONList :: [SomeRTypeRep] -> Value

toEncodingList :: [SomeRTypeRep] -> Encoding

Show SomeRTypeRep Source # 
Instance details

Defined in Variable.R.SEXP

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

Expand

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

Expand

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 by RTypeRep '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 a RTypeRep 'VECSXP. Type information about the RTypeRep s stored in SomeRTypeRep can be recovered using tools from the singletons package. See the "Advanced usage" section.
  • Nothing elements within RTypeRep 'VECSXP have no equivalent in R and hence probably should not be used.

Some caveats

Expand
  • At present, all conversions will pass through JSON, via types in the aeson package, and to R via the jsonlite package. Therefore, the conversion from RTypeRep to its R counterpart depends on those interim conversions, and in particular on the conversion from numeric types (INTSXP, REALSXP etc.) to Scientific, from the scientific package in Haskell.
  • It is unclear how close the Haskell Double corresponds to an element of R's numeric or REALSXP 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

Expand

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

data Factor Source #

Haskell representation of R's factor, either ordered or unordered. Construct with factor or ordered, preferably.

Constructors

MkFactor 

Fields

Instances

Instances details
ToJSON Factor Source # 
Instance details

Defined in Variable.R.Factor

Methods

toJSON :: Factor -> Value

toEncoding :: Factor -> Encoding

toJSONList :: [Factor] -> Value

toEncodingList :: [Factor] -> Encoding

Generic Factor Source # 
Instance details

Defined in Variable.R.Factor

Associated Types

type Rep Factor :: Type -> Type #

Methods

from :: Factor -> Rep Factor x #

to :: Rep Factor x -> Factor #

Show Factor Source # 
Instance details

Defined in Variable.R.Factor

Eq Factor Source # 
Instance details

Defined in Variable.R.Factor

Methods

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

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

Ord Factor Source # 
Instance details

Defined in Variable.R.Factor

type Rep Factor Source # 
Instance details

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

Expand
>>> :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}

Instances

Instances details
Show (SEXPElem s) => Show (Stype s) Source # 
Instance details

Defined in Variable.R.Stype

Methods

showsPrec :: Int -> Stype s -> ShowS #

show :: Stype s -> String #

showList :: [Stype s] -> ShowS #

data StypeAttrs Source #

User-provided stype common attributes. SEXPTYPE and name information is purposefully ommitted, since that will appear in VariableAttrs.

Constructors

MkStypeAttrs 

Fields

Instances

Instances details
ToJSON StypeAttrs Source # 
Instance details

Defined in Variable.R.Stype

Methods

toJSON :: StypeAttrs -> Value

toEncoding :: StypeAttrs -> Encoding

toJSONList :: [StypeAttrs] -> Value

toEncodingList :: [StypeAttrs] -> Encoding

Generic StypeAttrs Source # 
Instance details

Defined in Variable.R.Stype

Associated Types

type Rep StypeAttrs :: Type -> Type #

Show StypeAttrs Source # 
Instance details

Defined in Variable.R.Stype

Eq StypeAttrs Source # 
Instance details

Defined in Variable.R.Stype

type Rep StypeAttrs Source # 
Instance details

Defined in Variable.R.Stype

type Rep StypeAttrs = D1 ('MetaData "StypeAttrs" "Variable.R.Stype" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "MkStypeAttrs" 'PrefixI 'True) (S1 ('MetaSel ('Just "short_label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "long_label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "study_role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StypeRole)))))

data StypeRole Source #

Indication of variable role.

Instances

Instances details
ToJSON StypeRole Source # 
Instance details

Defined in Variable.R.Stype

Methods

toJSON :: StypeRole -> Value

toEncoding :: StypeRole -> Encoding

toJSONList :: [StypeRole] -> Value

toEncodingList :: [StypeRole] -> Encoding

Generic StypeRole Source # 
Instance details

Defined in Variable.R.Stype

Associated Types

type Rep StypeRole :: Type -> Type #

Show StypeRole Source # 
Instance details

Defined in Variable.R.Stype

Eq StypeRole Source # 
Instance details

Defined in Variable.R.Stype

type Rep StypeRole Source # 
Instance details

Defined in Variable.R.Stype

type Rep StypeRole = D1 ('MetaData "StypeRole" "Variable.R.Stype" "hasklepias-core-0.30.3-inplace" 'False) (C1 ('MetaCons "StypeCovariate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StypeOutcome" 'PrefixI 'False) (U1 :: Type -> Type))

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 #

Build a Nominal with the provided levels as second argument. The RTypeRep r will be converted to a Factor via factor.

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.

Methods

as_rtyperep :: a -> RTypeRep s Source #

Instances

Instances details
AsRTypeRep 'INTSXP Int32 Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP Integer Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'LGLSXP Bool Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'REALSXP Double Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Int32 Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Text Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Day Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP String Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Integer Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Bool Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Double Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP Int Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP (Complex Double) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP (Vector (Complex Double)) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP (Vector (Maybe (Complex Double))) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP (Maybe (Complex Double)) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP [Complex Double] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'CPLSXP [Maybe (Complex Double)] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP (Vector Int32) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Int32 -> RTypeRep 'INTSXP Source #

AsRTypeRep 'INTSXP (Vector (Maybe Int32)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'INTSXP Source #

AsRTypeRep 'INTSXP (Vector (Maybe Integer)) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP (Vector (Maybe Bool)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'INTSXP Source #

AsRTypeRep 'INTSXP (Vector Integer) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Integer -> RTypeRep 'INTSXP Source #

AsRTypeRep 'INTSXP (Vector Bool) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Bool -> RTypeRep 'INTSXP Source #

AsRTypeRep 'INTSXP (Maybe Int32) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP (Maybe Integer) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Int32] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Maybe Int32] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Maybe Integer] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Maybe Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Integer] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'INTSXP [Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'LGLSXP (Vector (Maybe Bool)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'LGLSXP Source #

AsRTypeRep 'LGLSXP (Vector Bool) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Bool -> RTypeRep 'LGLSXP Source #

AsRTypeRep 'LGLSXP (Maybe Bool) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'LGLSXP [Maybe Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'LGLSXP [Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'REALSXP (Vector Int32) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Int32 -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector (Maybe Int32)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector (Maybe Bool)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector (Maybe Double)) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'REALSXP (Vector (Maybe Int)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Int) -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector Bool) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Bool -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector Double) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Double -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Vector Int) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Int -> RTypeRep 'REALSXP Source #

AsRTypeRep 'REALSXP (Maybe Double) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'REALSXP [Maybe Double] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'REALSXP [Double] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Vector Int32) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Int32 -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Text) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Text -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Day) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Day -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector String) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector String -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Int32)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Text)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Text) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Day)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Day) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe String)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe String) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Integer)) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Vector (Maybe Bool)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Double)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Double) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector (Maybe Int)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe Int) -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Integer) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Integer -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Bool) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Bool -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Double) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Double -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Vector Int) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector Int -> RTypeRep 'STRSXP Source #

AsRTypeRep 'STRSXP (Maybe Int32) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Text) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Day) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe String) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Integer) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Bool) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Double) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP (Maybe Int) Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Int32] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Text] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Day] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [String] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Int32] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Text] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Day] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe String] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Integer] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Double] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Maybe Int] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Integer] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Bool] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Double] Source # 
Instance details

Defined in Variable.R.SEXP

AsRTypeRep 'STRSXP [Int] Source # 
Instance details

Defined in Variable.R.SEXP

(RTypeRepConstraints s, a ~ SEXPElem s) => AsRTypeRep 'VECSXP (Vector (Maybe a)) Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: Vector (Maybe a) -> RTypeRep 'VECSXP Source #

(RTypeRepConstraints s, a ~ SEXPElem s) => AsRTypeRep 'VECSXP [a] Source # 
Instance details

Defined in Variable.R.SEXP

Methods

as_rtyperep :: [a] -> RTypeRep 'VECSXP Source #

as_logical :: AsLogical a => a -> RTypeRep 'LGLSXP Source #

Analogous to R's as.logical.

as_integer :: AsInteger a => a -> RTypeRep 'INTSXP Source #

Analogous to R's as.integer.

as_numeric :: AsNumeric a => a -> RTypeRep 'REALSXP Source #

Analogous to R's as.numeric.

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

sort :: Ord (SEXPElem s) => RTypeRep s -> RTypeRep s Source #

Sort a RTypeRep using sort.

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.