Copyright | 2013 (C) Amgen Inc |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
- class SingI ty => Literal a ty | a -> ty where
- toPairList :: MonadR m => [(String, SomeSEXP (Region m))] -> m (SomeSEXP (Region m))
- fromPairList :: SomeSEXP s -> [(String, SomeSEXP s)]
- fromSomeSEXP :: forall s a form. Literal a form => SomeSEXP s -> a
- mkSEXP :: (Literal a b, MonadR m) => a -> m (SEXP (Region m) b)
- dynSEXP :: forall a s ty. Literal a ty => SomeSEXP s -> a
- mkSEXPVector :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> SEXP s a
- mkSEXPVectorIO :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> IO (SEXP s a)
- mkProtectedSEXPVector :: IsVector b => SSEXPTYPE b -> [SEXP s a] -> SEXP s b
- mkProtectedSEXPVectorIO :: IsVector b => SSEXPTYPE b -> [SEXP s a] -> IO (SEXP s b)
- funToSEXP :: HFunWrap a b => (b -> IO (FunPtr b)) -> a -> IO (SEXP s ExtPtr)
Literals conversion
class SingI ty => Literal a ty | a -> ty where Source #
Values that can be converted to SEXP
.
mkSEXPIO :: a -> IO (SEXP V ty) Source #
Internal function for converting a literal to a SEXP
value. You
probably want to be using mkSEXP
instead.
fromSEXP :: SEXP s ty -> a Source #
mkSEXPIO :: (IsVector ty, Literal [a] ty) => a -> IO (SEXP V ty) Source #
Internal function for converting a literal to a SEXP
value. You
probably want to be using mkSEXP
instead.
fromSEXP :: (IsVector ty, Literal [a] ty) => SEXP s ty -> a Source #
Literal Double Real Source # | |
Literal Int32 Int Source # | |
Literal String String Source # | |
Literal Logical Logical Source # | |
Literal [Double] Real Source # | |
Literal [Int32] Int Source # | |
Literal [Complex Double] Complex Source # | |
Literal [String] String Source # | |
Literal [Logical] Logical Source # | |
Literal (Complex Double) Complex Source # | |
Literal (SomeSEXP s) Any Source # | |
(NFData c, Literal a a0, Literal b b0, Literal c c0) => Literal (a -> b -> R s c) ExtPtr Source # | |
(NFData b, Literal a a0, Literal b b0) => Literal (a -> R s b) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a1 i4) => Literal (a2 -> a3 -> a4 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a1 i5) => Literal (a2 -> a3 -> a4 -> a5 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a1 i6) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a1 i7) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a1 i8) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a1 i9) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a1 i10) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a1 i11) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a1 i12) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> R s a1) ExtPtr Source # | |
(NFData a1, Literal a2 i1, Literal a3 i2, Literal a4 i3, Literal a5 i4, Literal a6 i5, Literal a7 i6, Literal a8 i7, Literal a9 i8, Literal a10 i9, Literal a11 i10, Literal a12 i11, Literal a13 i12, Literal a1 i13) => Literal (a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> a11 -> a12 -> a13 -> R s a1) ExtPtr Source # | |
SingI SEXPTYPE a => Literal (SEXP s a) a Source # | |
(NFData a, Literal a b) => Literal (R s a) ExtPtr Source # | |
VECTOR V ty a => Literal (MVector V ty a) ty Source # | |
VECTOR V ty a => Literal (Vector V ty a) ty Source # | |
toPairList :: MonadR m => [(String, SomeSEXP (Region m))] -> m (SomeSEXP (Region m)) Source #
Create a pairlist from an association list. Result is either a pairlist or
nilValue
if the input is the null list. These are two distinct forms. Hence
why the type of this function is not more precise.
fromPairList :: SomeSEXP s -> [(String, SomeSEXP s)] Source #
Create an association list from a pairlist. R Pairlists are nil-terminated chains of nested cons cells, as in LISP.
Derived helpers
fromSomeSEXP :: forall s a form. Literal a form => SomeSEXP s -> a Source #
Like fromSEXP
, but with no static type satefy. Performs a dynamic
(i.e. at runtime) check instead.
mkSEXP :: (Literal a b, MonadR m) => a -> m (SEXP (Region m) b) Source #
Create a SEXP value and protect it in current region
dynSEXP :: forall a s ty. Literal a ty => SomeSEXP s -> a Source #
Like fromSomeSEXP
, but behaves like the as.*
family of functions
in R, by performing a best effort conversion to the target form (e.g. rounds
reals to integers, etc) for atomic types.
mkSEXPVector :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> SEXP s a Source #
mkSEXPVectorIO :: (Storable (ElemRep s a), IsVector a) => SSEXPTYPE a -> [IO (ElemRep s a)] -> IO (SEXP s a) Source #