diff --git a/inline-r/inline-r.cabal b/inline-r/inline-r.cabal index a669f3d1..a5d2b072 100644 --- a/inline-r/inline-r.cabal +++ b/inline-r/inline-r.cabal @@ -78,7 +78,7 @@ library Foreign.R.EventLoop -- Language.R.Event other-modules: --- Control.Monad.R.Class + Control.Monad.R.Class -- Control.Monad.R.Internal -- Data.Vector.SEXP.Mutable.Internal Internal.Error diff --git a/inline-r/src/Control/Monad/R/Class.hs b/inline-r/src/Control/Monad/R/Class.hs index 5fed0f99..67803829 100644 --- a/inline-r/src/Control/Monad/R/Class.hs +++ b/inline-r/src/Control/Monad/R/Class.hs @@ -2,15 +2,18 @@ -- Copyright: (C) 2013 Amgen, Inc. -- +{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DefaultSignatures #-} +{-# OPTIONS_GHC -fplugin-opt=LiquidHaskell:--skip-module=False #-} module Control.Monad.R.Class ( MonadR(..) , Region - , acquireSome ) where import Control.Memory.Region +import qualified Data.Kind +import Foreign.C -- only needed to help name resolution in LH import Foreign.R import Control.Applicative @@ -19,6 +22,12 @@ import Control.Monad.Trans (MonadIO(..)) import Control.Monad.Primitive (PrimMonad, PrimState) import Prelude +-- Synonym for LH +type EqT = (~) + +_f :: EqT a b => CString +_f = undefined + -- | The class of R interaction monads. For safety, in compiled code we normally -- use the 'Language.R.Instance.R' monad. For convenience, in a GHCi session, we -- normally use the 'IO' monad directly (by means of a 'MonadR' instance for @@ -29,15 +38,16 @@ class (Applicative m, MonadIO m, MonadCatch m, MonadMask m, PrimMonad m) io :: IO a -> m a io = liftIO + {-@ acquire :: EqT s V => a:SEXP s -> m (TSEXP (Region m) (typeOf a)) @-} -- | Acquire ownership in the current region of the given object. This means -- that the liveness of the object is guaranteed so long as the current region -- remains active (the R garbage collector will not attempt to free it). - acquire :: s ~ V => SEXP s a -> m (SEXP (Region m) a) - default acquire :: (MonadIO m, Region m ~ G) => SEXP s a -> m (SEXP (Region m) a) - acquire = liftIO . protect + acquire :: s ~ V => SEXP s -> m (SEXP (Region m)) + default acquire :: (MonadIO m, Region m ~ G) => SEXP s -> m (SEXP (Region m)) + acquire = defaultAcquire -- | A reification of an R execution context, i.e. a "session". - data ExecContext m :: * + data ExecContext m :: Data.Kind.Type -- | Get the current execution context. getExecContext :: m (ExecContext m) @@ -47,8 +57,10 @@ class (Applicative m, MonadIO m, MonadCatch m, MonadMask m, PrimMonad m) -- For internal use only. unsafeRunWithExecContext :: m a -> ExecContext m -> IO a -type Region m = PrimState m +-- For some reason the implementation below causes LH +-- to fail. +{-@ ignore defaultAcquire @-} +defaultAcquire :: MonadIO m => SEXP s -> m (SEXP G) +defaultAcquire = liftIO . protect --- | 'acquire' for 'SomeSEXP'. -acquireSome :: (MonadR m) => SomeSEXP V -> m (SomeSEXP (Region m)) -acquireSome (SomeSEXP s) = SomeSEXP <$> acquire s +type Region m = PrimState m