{-# 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" 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 + $(n+1) ) |] print ((o' .!. inRecL) .!. y) {- $output >>> f2 [6.0,6.0,6.0] [7.0,7.0,7.0] [8.0,8.0,8.0] [9.0,9.0,9.0] -} main = f2