{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
module Language.R.QQ
( r
, rsafe
) where
import Control.Memory.Region
import Control.Monad.R.Class
import qualified Data.Vector.SEXP as Vector
import qualified Foreign.R as R
import qualified Foreign.R.Parse as R
import Foreign.R (SEXP, SomeSEXP(..))
import Foreign.R.Error
import Internal.Error
import Language.R (eval)
import Language.R.Globals (nilValue, globalEnv)
import Language.R.GC (automaticSome)
import Language.R.HExp
import Language.R.Instance
import Language.R.Literal (mkSEXPIO)
import Language.Haskell.TH (Q, runIO)
import Language.Haskell.TH.Quote
import qualified Language.Haskell.TH.Syntax as TH
import qualified Language.Haskell.TH.Lib as TH
import Control.Concurrent (MVar, newMVar, withMVar)
import Control.Exception (throwIO)
import Control.Monad (unless)
import Data.List (intercalate, isSuffixOf)
import qualified Data.Set as Set
import Data.Set (Set)
import Foreign (alloca, peek)
import Foreign.C.String (withCString)
import System.IO.Unsafe (unsafePerformIO)
r :: QuasiQuoter
r = QuasiQuoter
{ quoteExp = \txt -> [| eval =<< $(expQQ txt) |]
, quotePat = unimplemented "quotePat"
, quoteType = unimplemented "quoteType"
, quoteDec = unimplemented "quoteDec"
}
rsafe :: QuasiQuoter
rsafe = QuasiQuoter
{ quoteExp = \txt -> [| unsafePerformIO $ runRegion $ automaticSome =<< eval =<< $(expQQ txt) |]
, quotePat = unimplemented "quotePat"
, quoteType = unimplemented "quoteType"
, quoteDec = unimplemented "quoteDec"
}
qqLock :: MVar ()
qqLock = unsafePerformIO $ newMVar ()
{-# NOINLINE qqLock #-}
parse :: String -> IO (R.SEXP V 'R.Expr)
parse txt = do
initialize defaultConfig
withMVar qqLock $ \_ ->
withCString txt $ \ctxt ->
R.withProtected (R.mkString ctxt) $ \rtxt ->
alloca $ \status -> do
R.withProtected (R.parseVector rtxt (-1) status (R.release nilValue)) $ \exprs -> do
rc <- fromIntegral <$> peek status
unless (R.PARSE_OK == toEnum rc) $
throwIO . RError $ "Parse error in: " ++ txt
return exprs
antiSuffix :: String
antiSuffix = "_hs"
isAnti :: SEXP s 'R.Char -> Bool
isAnti (hexp -> Char (Vector.toString -> name)) = antiSuffix `isSuffixOf` name
isAnti _ = error "Impossible"
chop :: String -> String
chop name = take (length name - length antiSuffix) name
collectAntis :: R.SEXP s a -> Set (SEXP s 'R.Char)
collectAntis (hexp -> Symbol (R.unsafeCoerce -> name) _ _)
| isAnti name = Set.singleton name
collectAntis (hexp -> (List sxa sxb sxc)) = do
Set.unions [collectAntis sxa, collectAntis sxb, collectAntis sxc]
collectAntis (hexp -> (Lang (hexp -> Symbol (R.unsafeCoerce -> name) _ _) sxb))
| isAnti name = Set.insert name (collectAntis sxb)
collectAntis (hexp -> (Lang sxa sxb)) =
Set.union (collectAntis sxa) (collectAntis sxb)
collectAntis (hexp -> (Closure sxa sxb sxc)) =
Set.unions [collectAntis sxa, collectAntis sxb, collectAntis sxc]
collectAntis (hexp -> (Vector _ sxv)) =
Set.unions [collectAntis sx | SomeSEXP sx <- Vector.toList sxv]
collectAntis (hexp -> (Expr _ sxv)) =
Set.unions [collectAntis sx | SomeSEXP sx <- Vector.toList sxv]
collectAntis _ = Set.empty
expQQ :: String -> Q TH.Exp
expQQ input = do
expr <- runIO $ R.protect =<< parse input
let antis = [x | (hexp -> Char (Vector.toString -> x))
<- Set.toList (collectAntis expr)]
args = map (TH.dyn . chop) antis
closure = "function(" ++ intercalate "," antis ++ "){" ++ input ++ "}"
z = [| return (R.release nilValue) |]
vars <- mapM (\_ -> TH.newName "x") antis
x <- (\body -> foldl TH.appE body args) $ TH.lamE (map TH.varP vars)
[| do
let sx = unsafePerformIO $ do
exprs <- parse closure
SomeSEXP e <- R.readVector exprs 0
clos <- R.eval e (R.release globalEnv)
R.unSomeSEXP clos R.preserveObject
return clos
io $ case sx of
SomeSEXP f ->
R.lcons f =<<
$(foldr (\x xs -> [| R.withProtected $xs $ \cdr -> do
car <- mkSEXPIO $(TH.varE x)
R.lcons car cdr |]) z vars)
|]
runIO $ R.unprotectPtr expr
pure x