{-# LINE 1 "src/Foreign/R/Context.hsc" #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CApiFFI #-}
module Foreign.R.Context
( rCtx
, SEXPREC
, SEXP0
, Logical(..)
) where
import Data.Complex
import qualified Data.Map as Map
import Foreign.C
import Foreign.Ptr
import Foreign.Storable
import Language.C.Types (TypeSpecifier(TypeName))
import Language.C.Inline.Context (Context(..))
import Internal.Error
data {-# CTYPE "SEXPREC" #-} SEXPREC
type SEXP0 = Ptr SEXPREC
data {-# CTYPE "Logical" #-} Logical = FALSE
| TRUE
| NA
deriving (Eq, Ord, Show)
instance Storable Logical where
sizeOf _ = sizeOf (undefined :: CInt)
alignment _ = alignment (undefined :: CInt)
poke ptr FALSE = poke (castPtr ptr) (0 :: CInt)
poke ptr TRUE = poke (castPtr ptr) (1 :: CInt)
poke ptr NA = poke (castPtr ptr) (-2147483648 :: CInt)
{-# LINE 45 "src/Foreign/R/Context.hsc" #-}
peek ptr = do
x <- peek (castPtr ptr)
case x :: CInt of
0 -> return FALSE
1 -> return TRUE
-2147483648 -> return NA
{-# LINE 51 "src/Foreign/R/Context.hsc" #-}
_ -> failure "Storable Logical peek" "Not a Logical."
rCtx :: Context
rCtx = mempty { ctxTypesTable = Map.fromList tytabs }
where
tytabs =
[ (TypeName "SEXP", [t| Ptr SEXPREC |])
, (TypeName "Rcomplex", [t| Complex Double |])
]