{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TypeFamilies #-}
module Language.R.Instance
(
R
, runRegion
, unsafeRunRegion
, Config(..)
, defaultConfig
, withEmbeddedR
, initialize
, finalize
) where
import Control.Monad.Primitive (PrimMonad(..))
import Control.Monad.R.Class
import Control.Monad.ST.Unsafe (unsafeSTToIO)
import Data.Monoid
import Data.Default.Class (Default(..))
import qualified Foreign.R as R
import qualified Foreign.R.Embedded as R
#ifndef mingw32_HOST_OS
import qualified Foreign.R.EventLoop as R
#endif
import Foreign.C.String
import Language.R.Globals
import Control.Applicative
import Control.Concurrent.MVar
( newMVar
, withMVar
, MVar
)
import Control.DeepSeq ( NFData, deepseq )
import Control.Exception
( bracket
, bracket_
, uninterruptibleMask_
)
import Control.Monad.Catch ( MonadCatch, MonadMask, MonadThrow )
import Control.Monad.Reader
import Data.IORef (IORef, newIORef, readIORef, modifyIORef')
import Foreign
( Ptr
, allocaArray
)
import Foreign.C.Types ( CInt(..) )
import Foreign.Storable (Storable(..))
import System.Environment ( getProgName, lookupEnv )
import System.IO.Unsafe ( unsafePerformIO )
import System.Process ( readProcess )
import System.SetEnv
#ifndef mingw32_HOST_OS
import Control.Exception ( onException )
import System.IO ( hPutStrLn, stderr )
import System.Posix.Resource
#endif
import Prelude
newtype R s a = R { unR :: ReaderT (IORef Int) IO a }
deriving (Applicative, Functor, Monad, MonadIO, MonadCatch, MonadMask, MonadThrow)
instance PrimMonad (R s) where
type PrimState (R s) = s
primitive f = R $ lift $ unsafeSTToIO $ primitive f
instance MonadR (R s) where
io m = R $ ReaderT $ \_ -> m
acquire s = R $ ReaderT $ \cnt -> uninterruptibleMask_ $ do
x <- R.release <$> R.protect s
modifyIORef' cnt succ
return x
newtype ExecContext (R s) = ExecContext (IORef Int)
getExecContext = R $ ReaderT $ \ref -> return (ExecContext ref)
unsafeRunWithExecContext m (ExecContext ref) = runReaderT (unR m) ref
withEmbeddedR :: Config -> IO a -> IO a
withEmbeddedR config = bracket_ (initialize config) finalize
runRegion :: NFData a => (forall s. R s a) -> IO a
runRegion r = unsafeRunRegion r
unsafeRunRegion :: NFData a => R s a -> IO a
unsafeRunRegion r =
bracket (newIORef 0)
(R.unprotect <=< readIORef)
(\d -> do
x <- runReaderT (unR r) d
x `deepseq` return x)
data Config = Config
{
configProgName :: Last String
, configArgs :: [String]
, configSignalHandlers :: Last Bool
}
instance Default Config where
def = defaultConfig
instance Monoid Config where
mempty = defaultConfig
mappend cfg1 cfg2 = Config
{ configProgName = configProgName cfg1 <> configProgName cfg2
, configArgs = configArgs cfg1 <> configArgs cfg2
, configSignalHandlers = configSignalHandlers cfg1 <> configSignalHandlers cfg2
}
defaultConfig :: Config
defaultConfig = Config (Last Nothing) ["--vanilla", "--silent"] (Last (Just False))
populateEnv :: IO ()
populateEnv = do
mh <- lookupEnv "R_HOME"
when (mh == Nothing) $
setEnv "R_HOME" =<< fmap (head . lines) (readProcess "R" ["-e","cat(R.home())","--quiet","--slave"] "")
foreign import ccall "missing_r.h &isRInitialized" isRInitializedPtr :: Ptr CInt
newCArray :: Storable a
=> [a]
-> (Ptr a -> IO r)
-> IO r
newCArray xs k =
allocaArray (length xs) $ \ptr -> do
zipWithM_ (pokeElemOff ptr) [0..] xs
k ptr
initLock :: MVar ()
initLock = unsafePerformIO $ newMVar ()
{-# NOINLINE initLock #-}
initialize :: Config -> IO ()
initialize Config{..} = do
#ifndef mingw32_HOST_OS
#ifdef darwin_HOST_OS
let stackLimit = ResourceLimit 67104768
#else
let stackLimit = ResourceLimitUnknown
#endif
setResourceLimit ResourceStackSize (ResourceLimits stackLimit stackLimit)
`onException` (hPutStrLn stderr $
"Language.R.Interpreter: "
++ "Cannot increase stack size limit."
++ "Try increasing your stack size limit manually:"
#ifdef darwin_HOST_OS
++ "$ launchctl limit stack 67104768"
++ "$ ulimit -s 65532"
#else
++ "$ ulimit -s unlimited"
#endif
)
#endif
initialized <- fmap (==1) $ peek isRInitializedPtr
unless initialized $ withMVar initLock $ const $ do
initialized2 <- fmap (==1) $ peek isRInitializedPtr
unless initialized2 $ mdo
pokeRVariables
( R.baseEnv
, R.emptyEnv
, R.globalEnv
, R.nilValue
, R.unboundValue
, R.missingArg
, R.isRInteractive
, R.signalHandlers
#ifndef mingw32_HOST_OS
, R.inputHandlers
#endif
)
populateEnv
args <- (:) <$> maybe getProgName return (getLast configProgName)
<*> pure configArgs
argv <- mapM newCString args
let argc = length argv
unless (maybe False id $ getLast configSignalHandlers) $
poke signalHandlersPtr 0
newCArray argv $ R.initEmbeddedR argc
poke isRInteractive 0
poke isRInitializedPtr 1
finalize :: IO ()
finalize = do
R.endEmbeddedR 0
poke isRInitializedPtr 0