{-# LANGUAGE ViewPatterns #-} -- for pun {-# LANGUAGE DataKinds #-} {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} module Main where import RlangQQ import GHC.TypeLits makeLabels6 (words "x y z") inRec = x .=. "xlabel" .*. y .=. [1,2,3::Double] .*. z .=. [3,2,1 :: Double] .*. emptyRecord -- fixity is bad for .!. see test3_lens.hs for something better? main = do o <- [r| print(hs_inRec) hs_inRec <- within(hs_inRec, y <- y + z) |] print ((o .!. (Label :: Label "inRec")) .!. y) -- alternative to the above (shadows the label y) let [pun| inRec{ y } |] = o print y