{-# OPTIONS_GHC -optc-DUSE_RINTERNALS #-}
{-# LINE 1 "src/Foreign/R.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LINE 24 "src/Foreign/R.hsc" #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
module Foreign.R
( module Foreign.R.Type
, SEXP(..)
, SomeSEXP(..)
, unSomeSEXP
, cast
, asTypeOf
, unsafeCoerce
, allocSEXP
, allocList
, allocVector
, allocVectorProtected
, install
, mkString
, mkChar
, CEType(..)
, mkCharCE
, mkWeakRef
, typeOf
, isS4
, setAttributes
, getAttribute
, getAttributes
, cons
, lcons
, car
, cdr
, tag
, setCar
, setCdr
, setTag
, envFrame
, envEnclosing
, envHashtab
, closureFormals
, closureBody
, closureEnv
, promiseCode
, promiseEnv
, promiseValue
, symbolPrintName
, symbolValue
, symbolInternal
, length
, trueLength
, char
, real
, integer
, logical
, complex
, raw
, string
, unsafeSEXPToVectorPtr
, unsafeVectorPtrToSEXP
, readVector
, writeVector
, eval
, tryEval
, tryEvalSilent
, lang1
, lang2
, lang3
, findFun
, findVar
, protect
, unprotect
, unprotectPtr
, preserveObject
, releaseObject
, gc
, isRInteractive
, nilValue
, unboundValue
, missingArg
, baseEnv
, emptyEnv
, globalEnv
, signalHandlers
, interruptsPending
, printValue
, SEXPInfo(..)
, peekInfo
, pokeInfo
, mark
, named
, SEXPREC
, SEXP0
, sexp
, unsexp
, release
, unsafeRelease
, withProtected
, indexVector
) where
import Control.Memory.Region
import Data.Monoid ((<>))
import Foreign.R.Internal
import Foreign.R.Type
import Foreign.R.Type as R
import Control.Applicative
import Control.Exception (bracket)
import Data.Complex
import Data.Int (Int32)
{-# LINE 169 "src/Foreign/R.hsc" #-}
import Foreign (Ptr, castPtr)
import Foreign.C
import Foreign.R.Context (rCtx, SEXP0, SEXPREC)
import qualified Language.C.Inline as C
import Prelude hiding (asTypeOf, length)
C.context (C.baseCtx <> rCtx)
C.include "<Rinternals.h>"
C.include "<stdlib.h>"
C.include "<stdint.h>"
car :: SEXP s a -> IO (SomeSEXP s)
car (unsexp -> s) = somesexp <$> [C.exp| SEXP { CAR( $(SEXP s) ) } |]
cdr :: SEXP s a -> IO (SomeSEXP s)
cdr (unsexp -> s) = somesexp <$> [C.exp| SEXP { CAR( $(SEXP s) ) } |]
tag :: SEXP s a -> IO (SomeSEXP s)
tag (unsexp -> s) = somesexp <$> [C.exp| SEXP { TAG( $(SEXP s) ) } |]
envFrame :: (SEXP s 'R.Env) -> IO (SEXP s R.PairList)
envFrame (unsexp -> s) = sexp <$> [C.exp| SEXP { FRAME( $(SEXP s) ) } |]
envEnclosing :: SEXP s 'R.Env -> IO (SEXP s 'R.Env)
envEnclosing (unsexp -> s) = sexp <$> [C.exp| SEXP { ENCLOS( $(SEXP s) ) } |]
envHashtab :: SEXP s 'R.Env -> IO (SEXP s 'R.Vector)
envHashtab (unsexp -> s) = sexp <$> [C.exp| SEXP { HASHTAB( $(SEXP s) ) } |]
closureFormals :: SEXP s 'R.Closure -> IO (SEXP s R.PairList)
closureFormals (unsexp -> s) = sexp <$> [C.exp| SEXP { FORMALS( $(SEXP s) ) }|]
closureBody :: SEXP s 'R.Closure -> IO (SomeSEXP s)
closureBody (unsexp -> s) = somesexp <$> [C.exp| SEXP { BODY( $(SEXP s) ) } |]
closureEnv :: SEXP s 'R.Closure -> IO (SEXP s 'R.Env)
closureEnv (unsexp -> s) = sexp <$> [C.exp| SEXP { CLOENV( $(SEXP s) ) }|]
promiseCode :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseCode (unsexp -> s) = somesexp <$> [C.exp| SEXP { PRCODE( $(SEXP s) )}|]
promiseEnv :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseEnv (unsexp -> s) = somesexp <$> [C.exp| SEXP { PRENV( $(SEXP s) )}|]
promiseValue :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseValue (unsexp -> s) = somesexp <$> [C.exp| SEXP { PRVALUE( $(SEXP s) )}|]
trueLength :: R.IsVector a => SEXP s a -> IO CInt
trueLength (unsexp -> s) = [C.exp| int { TRUELENGTH( $(SEXP s) ) }|]
char :: SEXP s 'R.Char -> IO CString
char (unsexp -> s) = castPtr <$> [C.exp| const char* { CHAR($(SEXP s))}|]
real :: SEXP s 'R.Real -> IO (Ptr Double)
real (unsexp -> s) = castPtr <$> [C.exp| double* { REAL( $(SEXP s)) }|]
integer :: SEXP s 'R.Int -> IO (Ptr Int32)
integer (unsexp -> s) = [C.exp| int32_t* { INTEGER( $(SEXP s) )}|]
raw :: SEXP s 'R.Raw -> IO (Ptr CChar)
raw (unsexp -> s) = [C.exp| char* { RAW($(SEXP s)) } |]
logical :: SEXP s 'R.Logical -> IO (Ptr R.Logical)
logical (unsexp -> s) = castPtr <$>
[C.exp| int* { LOGICAL($(SEXP s)) } |]
complex :: SEXP s 'R.Complex -> IO (Ptr (Complex Double))
complex (unsexp -> s) = [C.exp| Rcomplex* { COMPLEX($(SEXP s)) }|]
string :: SEXP s 'R.String -> IO (Ptr (SEXP s 'R.Char))
string (unsexp -> s) = castPtr <$>
[C.exp| SEXP* { STRING_PTR($(SEXP s)) }|]
readVector :: R.IsGenericVector a => SEXP s a -> Int -> IO (SomeSEXP s)
readVector (unsexp -> s) (fromIntegral -> n) = somesexp <$>
[C.exp| SEXP { VECTOR_ELT( $(SEXP s), $(int n) ) } |]
indexVector :: IsGenericVector a => SEXP s a -> Int -> IO (SomeSEXP s)
{-# DEPRECATED indexVector "Use readVector instead." #-}
indexVector = readVector
writeVector :: R.IsGenericVector a => SEXP s a -> Int -> SEXP s b -> IO (SEXP s a)
writeVector (unsexp -> a) (fromIntegral -> n) (unsexp -> b) = sexp <$>
[C.exp| SEXP { SET_VECTOR_ELT($(SEXP a),$(int n), $(SEXP b)) } |]
symbolPrintName :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolPrintName (unsexp -> s) = sexp <$> [C.exp| SEXP { PRINTNAME( $(SEXP s)) } |]
symbolValue :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolValue (unsexp -> s) = sexp <$> [C.exp| SEXP { SYMVALUE( $(SEXP s)) } |]
symbolInternal :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolInternal (unsexp -> s) = sexp <$> [C.exp| SEXP { INTERNAL( $(SEXP s)) }|]
mkString :: CString -> IO (SEXP V 'R.String)
mkString value = sexp <$> [C.exp| SEXP { Rf_mkString($(char * value)) } |]
mkChar :: CString -> IO (SEXP V 'R.Char)
mkChar value = sexp <$> [C.exp| SEXP { Rf_mkChar($(char * value)) } |]
mkCharCE :: CEType -> CString -> IO (SEXP V 'R.Char)
mkCharCE (cIntFromEnum -> ce) value = sexp <$>
[C.exp| SEXP { Rf_mkCharCE($(char * value), $(int ce)) } |]
install :: CString -> IO (SEXP V 'R.Symbol)
install name = sexp <$>
[C.exp| SEXP { Rf_install($(char * name)) }|]
allocSEXP :: SSEXPTYPE a -> IO (SEXP V a)
allocSEXP (cUIntFromSingEnum -> s) = sexp <$>
[C.exp| SEXP { Rf_allocSExp( $(unsigned int s) ) }|]
allocList :: Int -> IO (SEXP V 'R.List)
allocList (fromIntegral -> n) = sexp <$> [C.exp| SEXP {Rf_allocList($(int n))} |]
allocVector :: R.IsVector a => SSEXPTYPE a -> Int -> IO (SEXP V a)
allocVector (cUIntFromSingEnum -> p) (fromIntegral -> n) = sexp <$>
[C.exp| SEXP {Rf_allocVector( $(unsigned int p), $(int n)) } |]
allocVectorProtected :: (R.IsVector a) => SSEXPTYPE a -> Int -> IO (SEXP s a)
allocVectorProtected ty n = fmap release (protect =<< allocVector ty n)
cons :: SEXP s a -> SEXP s b -> IO (SEXP V 'R.List)
cons (unsexp -> a) (unsexp -> b) = sexp <$>
[C.exp| SEXP { Rf_cons($(SEXP a), $(SEXP b)) }|]
lcons :: SEXP s a -> SEXP s b -> IO (SEXP V 'R.Lang)
lcons (unsexp -> a) (unsexp -> b) = sexp <$>
[C.exp| SEXP { Rf_lcons($(SEXP a), $(SEXP b)) } |]
printValue :: SEXP s a -> IO ()
printValue (unsexp -> s) =
[C.exp| void { Rf_PrintValue($(SEXP s)) }|]
protect :: SEXP s a -> IO (SEXP G a)
protect (unsexp -> s) = sexp <$>
[C.exp| SEXP { Rf_protect($(SEXP s)) }|]
unprotect :: Int -> IO ()
unprotect (fromIntegral -> i) =
[C.exp| void { Rf_unprotect($(int i)) } |]
unprotectPtr :: SEXP G a -> IO ()
unprotectPtr (unsexp -> s) =
[C.exp| void { Rf_unprotect_ptr($(SEXP s)) }|]
gc :: IO ()
gc = [C.exp| void { R_gc() }|]
preserveObject :: SEXP s a -> IO ()
preserveObject (unsexp -> s) =
[C.exp| void { R_PreserveObject( $(SEXP s) )} |]
releaseObject :: SEXP s a -> IO ()
releaseObject (unsexp -> s) =
[C.exp| void { R_ReleaseObject( $(SEXP s) )} |]
eval :: SEXP s a -> SEXP s 'R.Env -> IO (SomeSEXP V)
eval (unsexp -> expr) (unsexp -> env) = somesexp <$>
[C.exp| SEXP { Rf_eval($(SEXP expr), $(SEXP env)) }|]
tryEval :: SEXP s a -> SEXP s 'R.Env -> Ptr CInt -> IO (SomeSEXP V)
tryEval (unsexp -> expr) (unsexp -> env) retCode = somesexp <$>
[C.exp| SEXP { R_tryEval($(SEXP expr), $(SEXP env), $(int* retCode)) }|]
tryEvalSilent :: SEXP s a -> SEXP s 'R.Env -> Ptr CInt -> IO (SomeSEXP V)
tryEvalSilent (unsexp -> expr) (unsexp -> env) retCode = somesexp <$>
[C.exp| SEXP { R_tryEvalSilent($(SEXP expr), $(SEXP env), $(int* retCode)) }|]
lang1 :: SEXP s a -> IO (SEXP V 'R.Lang)
lang1 (unsexp -> s) = sexp <$>
[C.exp| SEXP {Rf_lang1($(SEXP s)) }|]
lang2 :: SEXP s a -> SEXP s b -> IO (SEXP V 'R.Lang)
lang2 (unsexp -> f) (unsexp -> x) = sexp <$>
[C.exp| SEXP {Rf_lang2($(SEXP f), $(SEXP x)) }|]
lang3 :: SEXP s a -> SEXP s b -> SEXP s c -> IO (SEXP V 'R.Lang)
lang3 (unsexp -> f) (unsexp -> x) (unsexp -> y) = sexp <$>
[C.exp| SEXP {Rf_lang3($(SEXP f), $(SEXP x), $(SEXP y)) }|]
findFun :: SEXP s a -> SEXP s 'R.Env -> IO (SomeSEXP s)
findFun (unsexp -> a) (unsexp -> env) = somesexp <$>
[C.exp| SEXP { Rf_findFun($(SEXP a), $(SEXP env)) }|]
findVar :: SEXP s a -> SEXP s 'R.Env -> IO (SEXP s 'R.Symbol)
findVar (unsexp -> a) (unsexp -> env) = sexp <$>
[C.exp| SEXP {Rf_findVar($(SEXP a), $(SEXP env))}|]
mkWeakRef :: SEXP s a -> SEXP s b -> SEXP s c -> Bool -> IO (SEXP V 'R.WeakRef)
mkWeakRef (unsexp -> a) (unsexp -> b) (unsexp -> c) (cIntFromEnum -> t) = sexp <$>
[C.exp| SEXP {R_MakeWeakRef($(SEXP a), $(SEXP b), $(SEXP c), $(int t))}|]
data CEType
= CE_Native
| CE_UTF8
| CE_Latin1
| CE_Bytes
| CE_Symbol
| CE_Any
deriving (Eq, Show)
instance Enum CEType where
fromEnum CE_Native = 0
{-# LINE 474 "src/Foreign/R.hsc" #-}
fromEnum CE_UTF8 = 1
{-# LINE 475 "src/Foreign/R.hsc" #-}
fromEnum CE_Latin1 = 2
{-# LINE 476 "src/Foreign/R.hsc" #-}
fromEnum CE_Bytes = 3
{-# LINE 477 "src/Foreign/R.hsc" #-}
fromEnum CE_Symbol = 5
{-# LINE 478 "src/Foreign/R.hsc" #-}
fromEnum CE_Any = 99
{-# LINE 479 "src/Foreign/R.hsc" #-}
toEnum i = case i of
(0) -> CE_Native
{-# LINE 481 "src/Foreign/R.hsc" #-}
(1) -> CE_UTF8
{-# LINE 482 "src/Foreign/R.hsc" #-}
(2) -> CE_Latin1
{-# LINE 483 "src/Foreign/R.hsc" #-}
(3) -> CE_Bytes
{-# LINE 484 "src/Foreign/R.hsc" #-}
(5) -> CE_Symbol
{-# LINE 485 "src/Foreign/R.hsc" #-}
(99) -> CE_Any
{-# LINE 486 "src/Foreign/R.hsc" #-}
_ -> error "CEType.fromEnum: unknown tag"
withProtected :: IO (SEXP V a)
-> (SEXP s a -> IO b)
-> IO b
withProtected create f =
bracket
(do { x <- create; _ <- protect x; return x })
(const $ unprotect 1)
(f . unsafeRelease)