{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} module Main where import RlangQQ import GHC.TypeLits import Control.Lens makeLabelable "x y z" inRec = x .==. "xlabel" .*. y .==. [1,2,3::Double] .*. z .==. [3,2,1 :: Double] .*. emptyRecord main = do o <- [r| print(hs_inRec) hs_inRec <- within(hs_inRec, y <- y + z) |] let inR = hLens' (Label :: Label "inRec") print (o ^.inR.y)