{-# OPTIONS_GHC -optc-DUSE_RINTERNALS #-}
{-# LINE 1 "src/Foreign/R.hsc" #-}
-- |
-- Copyright: (C) 2013 Amgen, Inc.
--
-- Low-level bindings to core R datatypes and functions. Nearly all structures
-- allocated internally in R are instances of a 'SEXPREC'. A pointer to
-- a 'SEXPREC' is called a 'SEXP'.
--
-- To allow for precise typing of bindings to primitive R functions, we index
-- 'SEXP's by 'SEXPTYPE', which classifies the /form/ of a 'SEXP' (see
-- "Foreign.R.Type"). A function accepting 'SEXP' arguments of any type should
-- leave the type index uninstantiated. A function returning a 'SEXP' result of
-- unknown type should use 'SomeSEXP'. (More precisely, unknown types in
-- /negative/ position should be /universally/ quantified and unknown types in
-- /positive/ position should be /existentially/ quantified).
--
-- This module is intended to be imported qualified.

{-# 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 #-}

-- Warns about some sanity checks like IsVector, that has no methods and are
-- not used.
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

module Foreign.R
  ( module Foreign.R.Type
    -- * Internal R structures
  , SEXP(..)
  , SomeSEXP(..)
  , unSomeSEXP
    -- * Casts and coercions
    -- $cast-coerce
  , cast
  , asTypeOf
  , unsafeCoerce
    -- * Node creation
  , allocSEXP
  , allocList
  , allocVector
  , allocVectorProtected
  , install
  , mkString
  , mkChar
  , CEType(..)
  , mkCharCE
  , mkCharLenCE
  , mkWeakRef
    -- * Node attributes
  , typeOf
  , isS4
  , setAttributes
  , getAttribute
  , getAttributes
    -- * Node accessor functions
    -- ** Lists
  , cons
  , lcons
  , car
  , cdr
  , tag
  , setCar
  , setCdr
  , setTag
    -- ** Environments
  , envFrame
  , envEnclosing
  , envHashtab
    -- ** Closures
  , closureFormals
  , closureBody
  , closureEnv
    -- ** Promises
  , promiseCode
  , promiseEnv
  , promiseValue
    -- ** Symbols
  , symbolPrintName
  , symbolValue
  , symbolInternal
    -- ** Vectors
  , length
  , trueLength
  , char
  , real
  , integer
  , logical
  , complex
  , raw
  , string
  , unsafeSEXPToVectorPtr
  , unsafeVectorPtrToSEXP
  , readVector
  , writeVector
    -- * Evaluation
  , eval
  , tryEval
  , tryEvalSilent
  , lang1
  , lang2
  , lang3
  , findFun
  , findVar
    -- * GC functions
  , protect
  , unprotect
  , unprotectPtr
  , preserveObject
  , releaseObject
  , gc
    -- * Globals
  , isRInteractive
  , nilValue
  , unboundValue
  , missingArg
  , baseEnv
  , emptyEnv
  , globalEnv
  , signalHandlers
  , interruptsPending
    -- * Communication with runtime
  , printValue
    -- * Low level info header access
  , SEXPInfo(..)
  , peekInfo
  , pokeInfo
  , mark
  , named
  -- * Internal types and functions
  --
  -- | Should not be used in user code. These exports are only needed for
  -- binding generation tools.
  , SEXPREC
  , SEXP0
  , sexp
  , unsexp
  , release
  , unsafeRelease
  , unsafeReleaseSome
  , withProtected
  -- * Deprecated
  , indexVector
  ) where

import Control.Memory.Region

{-# LINE 162 "src/Foreign/R.hsc" #-}
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 173 "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>"

--------------------------------------------------------------------------------
-- Generic accessor functions                                                 --
--------------------------------------------------------------------------------

-- | read CAR object value
car :: SEXP s a -> IO (SomeSEXP s)
car :: SEXP s a -> IO (SomeSEXP s)
car (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { CAR( $(SEXP s) ) } |]

-- | read CDR object
cdr :: SEXP s a -> IO (SomeSEXP s)
cdr :: SEXP s a -> IO (SomeSEXP s)
cdr (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { CAR( $(SEXP s) ) } |]

-- | read object`s Tag
tag :: SEXP s a -> IO (SomeSEXP s)
tag :: SEXP s a -> IO (SomeSEXP s)
tag (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { TAG( $(SEXP s) ) } |]

--------------------------------------------------------------------------------
-- Environment functions                                                      --
--------------------------------------------------------------------------------

envFrame :: (SEXP s 'R.Env) -> IO (SEXP s R.PairList)
envFrame :: SEXP s 'Env -> IO (SEXP s PairList)
envFrame (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s PairList
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s PairList) -> IO SEXP0 -> IO (SEXP s PairList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { FRAME( $(SEXP s) ) } |]

-- | Enclosing environment.
envEnclosing :: SEXP s 'R.Env -> IO (SEXP s 'R.Env)
envEnclosing :: SEXP s 'Env -> IO (SEXP s 'Env)
envEnclosing (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s 'Env
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s 'Env) -> IO SEXP0 -> IO (SEXP s 'Env)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { ENCLOS( $(SEXP s) ) } |]

-- | Hash table associated with the environment, used for faster name lookups.
envHashtab :: SEXP s 'R.Env -> IO (SEXP s 'R.Vector)
envHashtab :: SEXP s 'Env -> IO (SEXP s 'Vector)
envHashtab (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s 'Vector
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s 'Vector) -> IO SEXP0 -> IO (SEXP s 'Vector)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { HASHTAB( $(SEXP s) ) } |]

--------------------------------------------------------------------------------
-- Closure functions                                                          --
--------------------------------------------------------------------------------

-- | Closure formals (aka the actual arguments).
closureFormals :: SEXP s 'R.Closure -> IO (SEXP s R.PairList)
closureFormals :: SEXP s 'Closure -> IO (SEXP s PairList)
closureFormals (SEXP s 'Closure -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s PairList
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s PairList) -> IO SEXP0 -> IO (SEXP s PairList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { FORMALS( $(SEXP s) ) }|]

-- | The code of the closure.
closureBody :: SEXP s 'R.Closure -> IO (SomeSEXP s)
closureBody :: SEXP s 'Closure -> IO (SomeSEXP s)
closureBody (SEXP s 'Closure -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { BODY( $(SEXP s) ) } |]

-- | The environment of the closure.
closureEnv :: SEXP s 'R.Closure -> IO (SEXP s 'R.Env)
closureEnv :: SEXP s 'Closure -> IO (SEXP s 'Env)
closureEnv (SEXP s 'Closure -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s 'Env
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s 'Env) -> IO SEXP0 -> IO (SEXP s 'Env)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { CLOENV( $(SEXP s) ) }|]

--------------------------------------------------------------------------------
-- Promise functions                                                          --
--------------------------------------------------------------------------------

-- | The code of a promise.
promiseCode :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseCode :: SEXP s 'Promise -> IO (SomeSEXP s)
promiseCode (SEXP s 'Promise -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { PRCODE( $(SEXP s) )}|]

-- | The environment in which to evaluate the promise.
promiseEnv :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseEnv :: SEXP s 'Promise -> IO (SomeSEXP s)
promiseEnv (SEXP s 'Promise -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { PRENV( $(SEXP s) )}|]

-- | The value of the promise, if it has already been forced.
promiseValue :: SEXP s 'R.Promise -> IO (SomeSEXP s)
promiseValue :: SEXP s 'Promise -> IO (SomeSEXP s)
promiseValue (SEXP s 'Promise -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { PRVALUE( $(SEXP s) )}|]

--------------------------------------------------------------------------------
-- Vector accessor functions                                                  --
--------------------------------------------------------------------------------

-- | Read True Length vector field.
trueLength :: R.IsVector a => SEXP s a -> IO CInt
trueLength :: SEXP s a -> IO CInt
trueLength (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = [C.exp| int { TRUELENGTH( $(SEXP s) ) }|]

-- | Read character vector data
char :: SEXP s 'R.Char -> IO CString
char :: SEXP s 'Char -> IO CString
char (SEXP s 'Char -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = CString -> CString
forall a b. Ptr a -> Ptr b
castPtr (CString -> CString) -> IO CString -> IO CString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| const char* { CHAR($(SEXP s))}|]
-- XXX: check if we really need Word8 here, maybe some better handling of
-- encoding

-- | Read real vector data.
real :: SEXP s 'R.Real -> IO (Ptr Double)
real :: SEXP s 'Real -> IO (Ptr Double)
real (SEXP s 'Real -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = Ptr CDouble -> Ptr Double
forall a b. Ptr a -> Ptr b
castPtr (Ptr CDouble -> Ptr Double) -> IO (Ptr CDouble) -> IO (Ptr Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| double* { REAL( $(SEXP s)) }|]

-- | Read integer vector data.
integer :: SEXP s 'R.Int -> IO (Ptr Int32)
integer :: SEXP s 'Int -> IO (Ptr Int32)
integer (SEXP s 'Int -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = [C.exp| int32_t* { INTEGER( $(SEXP s) )}|]

-- | Read raw data.
raw :: SEXP s 'R.Raw -> IO (Ptr CChar)
raw :: SEXP s 'Raw -> IO CString
raw (SEXP s 'Raw -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = [C.exp| char* { RAW($(SEXP s)) } |]

-- | Read logical vector data.
logical :: SEXP s 'R.Logical -> IO (Ptr R.Logical)
logical :: SEXP s 'Logical -> IO (Ptr Logical)
logical (SEXP s 'Logical -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = Ptr CInt -> Ptr Logical
forall a b. Ptr a -> Ptr b
castPtr (Ptr CInt -> Ptr Logical) -> IO (Ptr CInt) -> IO (Ptr Logical)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| int* { LOGICAL($(SEXP s)) } |]

-- | Read complex vector data.
complex :: SEXP s 'R.Complex -> IO (Ptr (Complex Double))
complex :: SEXP s 'Complex -> IO (Ptr (Complex Double))
complex (SEXP s 'Complex -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = [C.exp| Rcomplex* { COMPLEX($(SEXP s)) }|]

-- | Read string vector data.
string :: SEXP s 'R.String -> IO (Ptr (SEXP s 'R.Char))
string :: SEXP s 'String -> IO (Ptr (SEXP s 'Char))
string (SEXP s 'String -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = Ptr SEXP0 -> Ptr (SEXP s 'Char)
forall a b. Ptr a -> Ptr b
castPtr (Ptr SEXP0 -> Ptr (SEXP s 'Char))
-> IO (Ptr SEXP0) -> IO (Ptr (SEXP s 'Char))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP* { STRING_PTR($(SEXP s)) }|]

readVector :: R.IsGenericVector a => SEXP s a -> Int -> IO (SomeSEXP s)
readVector :: SEXP s a -> Int -> IO (SomeSEXP s)
readVector (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
n) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [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 :: SEXP s a -> Int -> IO (SomeSEXP s)
indexVector = SEXP s a -> Int -> IO (SomeSEXP s)
forall (a :: SEXPTYPE) s.
IsGenericVector a =>
SEXP s a -> Int -> IO (SomeSEXP s)
readVector

writeVector :: R.IsGenericVector a => SEXP s a -> Int -> SEXP s b -> IO (SEXP s a)
writeVector :: SEXP s a -> Int -> SEXP s b -> IO (SEXP s a)
writeVector (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
n) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
b) = SEXP0 -> SEXP s a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s a) -> IO SEXP0 -> IO (SEXP s a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { SET_VECTOR_ELT($(SEXP a),$(int n), $(SEXP b)) } |]

--------------------------------------------------------------------------------
-- Symbol accessor functions                                                  --
--------------------------------------------------------------------------------

-- | Read a name from symbol.
symbolPrintName :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolPrintName :: SEXP s 'Symbol -> IO (SEXP s a)
symbolPrintName (SEXP s 'Symbol -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s a) -> IO SEXP0 -> IO (SEXP s a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { PRINTNAME( $(SEXP s)) } |]

-- | Read value from symbol.
symbolValue :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolValue :: SEXP s 'Symbol -> IO (SEXP s a)
symbolValue (SEXP s 'Symbol -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s a) -> IO SEXP0 -> IO (SEXP s a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { SYMVALUE( $(SEXP s)) } |]

-- | Read internal value from symbol.
symbolInternal :: SEXP s 'R.Symbol -> IO (SEXP s a)
symbolInternal :: SEXP s 'Symbol -> IO (SEXP s a)
symbolInternal (SEXP s 'Symbol -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP s a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s a) -> IO SEXP0 -> IO (SEXP s a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { INTERNAL( $(SEXP s)) }|]

--------------------------------------------------------------------------------
-- Value contruction                                                          --
--------------------------------------------------------------------------------

-- | Initialize a new string vector.
mkString :: CString -> IO (SEXP V 'R.String)
mkString :: CString -> IO (SEXP V 'String)
mkString value :: CString
value = SEXP0 -> SEXP V 'String
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'String) -> IO SEXP0 -> IO (SEXP V 'String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  [C.exp| SEXP { Rf_mkString($(char * value)) } |]

-- | Initialize a new character vector (aka a string).
mkChar :: CString -> IO (SEXP V 'R.Char)
mkChar :: CString -> IO (SEXP V 'Char)
mkChar value :: CString
value = SEXP0 -> SEXP V 'Char
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Char) -> IO SEXP0 -> IO (SEXP V 'Char)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP { Rf_mkChar($(char * value)) } |]

-- | Create Character value with specified encoding
mkCharCE :: CEType -> CString -> IO (SEXP V 'R.Char)
mkCharCE :: CEType -> CString -> IO (SEXP V 'Char)
mkCharCE (CEType -> CInt
forall a. Enum a => a -> CInt
cIntFromEnum -> CInt
ce) value :: CString
value = SEXP0 -> SEXP V 'Char
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Char) -> IO SEXP0 -> IO (SEXP V 'Char)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 
  [C.exp| SEXP  { Rf_mkCharCE($(char * value), $(int ce)) } |]

mkCharLenCE :: CEType -> CString -> Int -> IO (SEXP V 'R.Char)
mkCharLenCE :: CEType -> CString -> Int -> IO (SEXP V 'Char)
mkCharLenCE (CEType -> CInt
forall a. Enum a => a -> CInt
cIntFromEnum -> CInt
ce) value :: CString
value (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
len) = SEXP0 -> SEXP V 'Char
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Char) -> IO SEXP0 -> IO (SEXP V 'Char)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_mkCharLenCE($(char * value), $(int len), $(int ce)) } |]

-- | Intern a string @name@ into the symbol table.
--
-- If @name@ is not found, it is added to the symbol table. The symbol
-- corresponding to the string @name@ is returned.
install :: CString -> IO (SEXP V 'R.Symbol)
install :: CString -> IO (SEXP V 'Symbol)
install name :: CString
name = SEXP0 -> SEXP V 'Symbol
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Symbol) -> IO SEXP0 -> IO (SEXP V 'Symbol)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_install($(char * name)) }|]

-- | Allocate a 'SEXP'.
allocSEXP :: SSEXPTYPE a -> IO (SEXP V a)
allocSEXP :: SSEXPTYPE a -> IO (SEXP V a)
allocSEXP (SSEXPTYPE a -> CUInt
forall (a :: SEXPTYPE). SSEXPTYPE a -> CUInt
cUIntFromSingEnum -> CUInt
s) = SEXP0 -> SEXP V a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V a) -> IO SEXP0 -> IO (SEXP V a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_allocSExp( $(unsigned int s) ) }|]

-- | Allocate a pairlist of 'SEXP's, chained together.
allocList :: Int -> IO (SEXP V 'R.List)
allocList :: Int -> IO (SEXP V PairList)
allocList (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
n) = SEXP0 -> SEXP V PairList
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V PairList) -> IO SEXP0 -> IO (SEXP V PairList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| SEXP {Rf_allocList($(int n))} |]

-- | Allocate Vector.
allocVector :: R.IsVector a => SSEXPTYPE a -> Int -> IO (SEXP V a)
allocVector :: SSEXPTYPE a -> Int -> IO (SEXP V a)
allocVector (SSEXPTYPE a -> CUInt
forall (a :: SEXPTYPE). SSEXPTYPE a -> CUInt
cUIntFromSingEnum -> CUInt
p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
n) = SEXP0 -> SEXP V a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V a) -> IO SEXP0 -> IO (SEXP V a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP {Rf_allocVector( $(unsigned int p), $(int n)) } |]

allocVectorProtected :: (R.IsVector a) => SSEXPTYPE a -> Int -> IO (SEXP s a)
allocVectorProtected :: SSEXPTYPE a -> Int -> IO (SEXP s a)
allocVectorProtected ty :: SSEXPTYPE a
ty n :: Int
n = (SEXP G a -> SEXP s a) -> IO (SEXP G a) -> IO (SEXP s a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SEXP G a -> SEXP s a
forall t s (a :: SEXPTYPE). (t <= s) => SEXP s a -> SEXP t a
release (SEXP V a -> IO (SEXP G a)
forall s (a :: SEXPTYPE). SEXP s a -> IO (SEXP G a)
protect (SEXP V a -> IO (SEXP G a)) -> IO (SEXP V a) -> IO (SEXP G a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SSEXPTYPE a -> Int -> IO (SEXP V a)
forall (a :: SEXPTYPE).
IsVector a =>
SSEXPTYPE a -> Int -> IO (SEXP V a)
allocVector SSEXPTYPE a
ty Int
n)

-- | Allocate a so-called cons cell, in essence a pair of 'SEXP' pointers.
cons :: SEXP s a -> SEXP s b -> IO (SEXP V 'R.List)
cons :: SEXP s a -> SEXP s b -> IO (SEXP V PairList)
cons (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
b) = SEXP0 -> SEXP V PairList
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V PairList) -> IO SEXP0 -> IO (SEXP V PairList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_cons($(SEXP a), $(SEXP b)) }|]

-- | Allocate a so-called cons cell of language objects, in essence a pair of
-- 'SEXP' pointers.
lcons :: SEXP s a -> SEXP s b -> IO (SEXP V 'R.Lang)
lcons :: SEXP s a -> SEXP s b -> IO (SEXP V 'Lang)
lcons (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
b) = SEXP0 -> SEXP V 'Lang
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Lang) -> IO SEXP0 -> IO (SEXP V 'Lang)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_lcons($(SEXP a), $(SEXP b)) } |]


printValue :: SEXP s a -> IO ()
printValue :: SEXP s a -> IO ()
printValue (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) =
  [C.exp| void { Rf_PrintValue($(SEXP s)) }|]

--------------------------------------------------------------------------------
-- Garbage collection                                                         --
--------------------------------------------------------------------------------

-- | Protect a 'SEXP' from being garbage collected by R. It is in particular
-- necessary to do so for objects that are not yet pointed by any other object,
-- e.g. when constructing a tree bottom-up rather than top-down.
--
-- To avoid unbalancing calls to 'protect' and 'unprotect', do not use these
-- functions directly but use 'Language.R.withProtected' instead.
protect :: SEXP s a -> IO (SEXP G a)
protect :: SEXP s a -> IO (SEXP G a)
protect (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP G a
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP G a) -> IO SEXP0 -> IO (SEXP G a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 
  [C.exp| SEXP { Rf_protect($(SEXP s)) }|]

-- | @unprotect n@ unprotects the last @n@ objects that were protected.
unprotect :: Int -> IO ()
unprotect :: Int -> IO ()
unprotect (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
i) =
  [C.exp| void { Rf_unprotect($(int i)) } |]

-- | Unprotect a specific object, referred to by pointer.
unprotectPtr :: SEXP G a -> IO ()
unprotectPtr :: SEXP G a -> IO ()
unprotectPtr (SEXP G a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) =
  [C.exp| void { Rf_unprotect_ptr($(SEXP s)) }|]

-- | Invoke an R garbage collector sweep.
gc :: IO ()
gc :: IO ()
gc = [C.exp| void { R_gc() }|]

-- | Preserve an object accross GCs.
preserveObject :: SEXP s a -> IO ()
preserveObject :: SEXP s a -> IO ()
preserveObject (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) =
  [C.exp| void { R_PreserveObject( $(SEXP s) )} |]

-- | Allow GC to remove an preserved object.
releaseObject :: SEXP s a -> IO ()
releaseObject :: SEXP s a -> IO ()
releaseObject (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) =
  [C.exp| void { R_ReleaseObject( $(SEXP s) )} |]

--------------------------------------------------------------------------------
-- Evaluation                                                                 --
--------------------------------------------------------------------------------

-- | Evaluate any 'SEXP' to its value.
eval :: SEXP s a -> SEXP s 'R.Env -> IO (SomeSEXP V)
eval :: SEXP s a -> SEXP s 'Env -> IO (SomeSEXP V)
eval (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
expr) (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
env) = SEXP0 -> SomeSEXP V
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP V) -> IO SEXP0 -> IO (SomeSEXP V)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_eval($(SEXP expr), $(SEXP env)) }|]

-- | Try to evaluate expression.
tryEval :: SEXP s a -> SEXP s 'R.Env -> Ptr CInt -> IO (SomeSEXP V)
tryEval :: SEXP s a -> SEXP s 'Env -> Ptr CInt -> IO (SomeSEXP V)
tryEval (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
expr) (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
env) retCode :: Ptr CInt
retCode = SEXP0 -> SomeSEXP V
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP V) -> IO SEXP0 -> IO (SomeSEXP V)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { R_tryEval($(SEXP expr), $(SEXP env), $(int* retCode)) }|]

-- | Try to evaluate without printing error/warning messages to stdout.
tryEvalSilent :: SEXP  s a -> SEXP s 'R.Env -> Ptr CInt -> IO (SomeSEXP V)
tryEvalSilent :: SEXP s a -> SEXP s 'Env -> Ptr CInt -> IO (SomeSEXP V)
tryEvalSilent (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
expr) (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
env) retCode :: Ptr CInt
retCode = SEXP0 -> SomeSEXP V
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP V) -> IO SEXP0 -> IO (SomeSEXP V)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { R_tryEvalSilent($(SEXP expr), $(SEXP env), $(int* retCode)) }|]

-- | Construct a nullary function call.
lang1 :: SEXP s a -> IO (SEXP V 'R.Lang)
lang1 :: SEXP s a -> IO (SEXP V 'Lang)
lang1 (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
s) = SEXP0 -> SEXP V 'Lang
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Lang) -> IO SEXP0 -> IO (SEXP V 'Lang)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP {Rf_lang1($(SEXP s)) }|]

-- | Construct unary function call.
lang2 :: SEXP s a -> SEXP s b ->  IO (SEXP V 'R.Lang)
lang2 :: SEXP s a -> SEXP s b -> IO (SEXP V 'Lang)
lang2 (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
f) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
x) = SEXP0 -> SEXP V 'Lang
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Lang) -> IO SEXP0 -> IO (SEXP V 'Lang)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP {Rf_lang2($(SEXP f), $(SEXP x)) }|]

-- | Construct a binary function call.
lang3 :: SEXP s a -> SEXP s b ->  SEXP s c -> IO (SEXP V 'R.Lang)
lang3 :: SEXP s a -> SEXP s b -> SEXP s c -> IO (SEXP V 'Lang)
lang3 (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
f) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
x) (SEXP s c -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
y) = SEXP0 -> SEXP V 'Lang
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'Lang) -> IO SEXP0 -> IO (SEXP V 'Lang)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP {Rf_lang3($(SEXP f), $(SEXP x), $(SEXP y)) }|]

-- | Find a function by name.
findFun :: SEXP s a -> SEXP s 'R.Env -> IO (SomeSEXP s)
findFun :: SEXP s a -> SEXP s 'Env -> IO (SomeSEXP s)
findFun (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
env) = SEXP0 -> SomeSEXP s
forall s. SEXP0 -> SomeSEXP s
somesexp (SEXP0 -> SomeSEXP s) -> IO SEXP0 -> IO (SomeSEXP s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP { Rf_findFun($(SEXP a), $(SEXP env)) }|]

-- | Find a variable by name.
findVar :: SEXP s a -> SEXP s 'R.Env -> IO (SEXP s 'R.Symbol)
findVar :: SEXP s a -> SEXP s 'Env -> IO (SEXP s 'Symbol)
findVar (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (SEXP s 'Env -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
env) = SEXP0 -> SEXP s 'Symbol
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP s 'Symbol) -> IO SEXP0 -> IO (SEXP s 'Symbol)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [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 :: SEXP s a -> SEXP s b -> SEXP s c -> Bool -> IO (SEXP V 'WeakRef)
mkWeakRef (SEXP s a -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
a) (SEXP s b -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
b) (SEXP s c -> SEXP0
forall s (a :: SEXPTYPE). SEXP s a -> SEXP0
unsexp -> SEXP0
c) (Bool -> CInt
forall a. Enum a => a -> CInt
cIntFromEnum -> CInt
t) = SEXP0 -> SEXP V 'WeakRef
forall s (a :: SEXPTYPE). SEXP0 -> SEXP s a
sexp (SEXP0 -> SEXP V 'WeakRef) -> IO SEXP0 -> IO (SEXP V 'WeakRef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  [C.exp| SEXP {R_MakeWeakRef($(SEXP a), $(SEXP b), $(SEXP c), $(int t))}|]

-------------------------------------------------------------------------------
-- Encoding                                                                  --
-------------------------------------------------------------------------------

-- | Content encoding.
data CEType
  = CE_Native
  | CE_UTF8
  | CE_Latin1
  | CE_Bytes
  | CE_Symbol
  | CE_Any
  deriving (CEType -> CEType -> Bool
(CEType -> CEType -> Bool)
-> (CEType -> CEType -> Bool) -> Eq CEType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CEType -> CEType -> Bool
$c/= :: CEType -> CEType -> Bool
== :: CEType -> CEType -> Bool
$c== :: CEType -> CEType -> Bool
Eq, Int -> CEType -> ShowS
[CEType] -> ShowS
CEType -> String
(Int -> CEType -> ShowS)
-> (CEType -> String) -> ([CEType] -> ShowS) -> Show CEType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CEType] -> ShowS
$cshowList :: [CEType] -> ShowS
show :: CEType -> String
$cshow :: CEType -> String
showsPrec :: Int -> CEType -> ShowS
$cshowsPrec :: Int -> CEType -> ShowS
Show)

instance Enum CEType where
  fromEnum :: CEType -> Int
fromEnum CE_Native = 0
{-# LINE 482 "src/Foreign/R.hsc" #-}
  fromEnum CE_UTF8   = 1
{-# LINE 483 "src/Foreign/R.hsc" #-}
  fromEnum CE_Latin1 = 2
{-# LINE 484 "src/Foreign/R.hsc" #-}
  fromEnum CE_Bytes  = 3
{-# LINE 485 "src/Foreign/R.hsc" #-}
  fromEnum CE_Symbol = 5
{-# LINE 486 "src/Foreign/R.hsc" #-}
  fromEnum CE_Any    = 99
{-# LINE 487 "src/Foreign/R.hsc" #-}
  toEnum i = case i of
    (0) -> CE_Native
{-# LINE 489 "src/Foreign/R.hsc" #-}
    (1)   -> CE_UTF8
{-# LINE 490 "src/Foreign/R.hsc" #-}
    (2) -> CE_Latin1
{-# LINE 491 "src/Foreign/R.hsc" #-}
    (3)  -> CE_Bytes
{-# LINE 492 "src/Foreign/R.hsc" #-}
    (5) -> CE_Symbol
{-# LINE 493 "src/Foreign/R.hsc" #-}
    (99)    -> CE_Any
{-# LINE 494 "src/Foreign/R.hsc" #-}
    _ -> error "CEType.fromEnum: unknown tag"

-- | Perform an action with resource while protecting it from the garbage
-- collection. This function is a safer alternative to 'R.protect' and
-- 'R.unprotect', guaranteeing that a protected resource gets unprotected
-- irrespective of the control flow, much like 'Control.Exception.bracket_'.
withProtected :: IO (SEXP V a)      -- Action to acquire resource
              -> (SEXP s a -> IO b) -- Action
              -> IO b
withProtected :: IO (SEXP V a) -> (SEXP s a -> IO b) -> IO b
withProtected create :: IO (SEXP V a)
create f :: SEXP s a -> IO b
f =
    IO (SEXP V a) -> (SEXP V a -> IO ()) -> (SEXP V a -> IO b) -> IO b
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
      (do { SEXP V a
x <- IO (SEXP V a)
create; SEXP G a
_ <- SEXP V a -> IO (SEXP G a)
forall s (a :: SEXPTYPE). SEXP s a -> IO (SEXP G a)
protect SEXP V a
x; SEXP V a -> IO (SEXP V a)
forall (m :: * -> *) a. Monad m => a -> m a
return SEXP V a
x })
      (IO () -> SEXP V a -> IO ()
forall a b. a -> b -> a
const (IO () -> SEXP V a -> IO ()) -> IO () -> SEXP V a -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
unprotect 1)
      (SEXP s a -> IO b
f (SEXP s a -> IO b) -> (SEXP V a -> SEXP s a) -> SEXP V a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SEXP V a -> SEXP s a
forall s (a :: SEXPTYPE) r. SEXP s a -> SEXP r a
unsafeRelease)