{-# LANGUAGE DataKinds, TemplateHaskell, QuasiQuotes #-} module Main where import RlangQQ import GHC.TypeLits -- ghc7.6 workaround import Control.Monad makeLabels6 (words "x y z") inRec = x .=. "xlabel" .*. y .=. [1,2,3::Double] .*. z .=. [3,2,1 :: Double] .*. emptyRecord inRecL = Label :: Label "inRec" {- $test note that the same R-session is run for all calls to f1, that is why the results differ between f1 and f2: >>> f1 [5.0,5.0,5.0] [10.0,9.0,8.0] [16.0,14.0,12.0] [23.0,20.0,17.0] >>> f2 [5.0,5.0,5.0] [6.0,6.0,6.0] [7.0,7.0,7.0] [8.0,8.0,8.0] -} f1 = do w <- newRChan [r| # this shouldn't be necessary to force INOUT print(hs_inRec) hs_inRec <- within(hs_inRec, y <- y + z + ch_w) |] forM_ [1,2,3,4 :: Double] $ \n -> do o' <- sendRcv w n print ((o' .!. inRecL) .!. y) f2 = forM_ [1,2,3,4 :: Double] $ \n -> do o' <- [r| # this shouldn't be necessary to force INOUT print(hs_inRec) hs_inRec <- within(hs_inRec, y <- y + z + hs_n) |] print ((o' .!. inRecL) .!. y) main = do f1;f2