[Git][ghc/ghc][wip/romes/template-haskell-quote-strictness] fix: Consider strictness annotation in rep_bind
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Tue Feb 28 19:20:35 UTC 2023
Rodrigo Mesquita pushed to branch wip/romes/template-haskell-quote-strictness at Glasgow Haskell Compiler / GHC
Commits:
dc8751dc by romes at 2023-02-28T19:20:13+00:00
fix: Consider strictness annotation in rep_bind
Fixes #23036
- - - - -
4 changed files:
- compiler/GHC/HsToCore/Quote.hs
- + testsuite/tests/th/T23036.hs
- + testsuite/tests/th/T23036.stderr
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -1899,12 +1899,18 @@ rep_bind (L loc (FunBind
fun_matches = MG { mg_alts
= (L _ [L _ (Match
{ m_pats = []
- , m_grhss = GRHSs _ guards wheres }
- )]) } }))
+ , m_grhss = GRHSs _ guards wheres
+ -- For a variable declaration I'm pretty
+ -- sure we always have a FunRhs
+ , m_ctxt = FunRhs { mc_strictness = strictessAnn }
+ } )]) } }))
= do { (ss,wherecore) <- repBinds wheres
; guardcore <- addBinds ss (repGuards guards)
; fn' <- lookupNBinder fn
- ; p <- repPvar fn'
+ ; p <- repPvar fn' >>= case strictessAnn of
+ SrcLazy -> repPtilde
+ SrcStrict -> repPbang
+ NoSrcStrict -> pure
; ans <- repVal p guardcore wherecore
; ans' <- wrapGenSyms ss ans
; return (locA loc, ans') }
=====================================
testsuite/tests/th/T23036.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T23036 where
+
+import Language.Haskell.TH
+
+a, b, c :: ()
+a = $([|let x = undefined in ()|])
+b = $([|let !x = undefined in ()|])
+c = $([|let ~x = undefined in ()|])
=====================================
testsuite/tests/th/T23036.stderr
=====================================
@@ -0,0 +1,6 @@
+T23036.hs:7:6-34: Splicing expression
+ [| let x = undefined in () |] ======> let x = undefined in ()
+T23036.hs:8:6-35: Splicing expression
+ [| let !x = undefined in () |] ======> let !x = undefined in ()
+T23036.hs:9:6-35: Splicing expression
+ [| let ~x = undefined in () |] ======> let ~x = undefined in ()
=====================================
testsuite/tests/th/all.T
=====================================
@@ -559,3 +559,4 @@ test('T22784', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T22818', normal, compile, ['-v0'])
test('T22819', normal, compile, ['-v0'])
test('TH_fun_par', normal, compile, [''])
+test('T23036', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc8751dcc482d94b9f57501a226aad7d4796b198
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dc8751dcc482d94b9f57501a226aad7d4796b198
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230228/33137718/attachment-0001.html>
More information about the ghc-commits
mailing list