[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 21:37:05 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/template-haskell-quote-strictness at Glasgow Haskell Compiler / GHC


Commits:
e0708a02 by romes at 2023-02-28T21:36:54+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,16 @@
+{-# 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 ()|])
+
+-- Test strictness annotations are also correctly handled in function and pattern binders
+d, e, f:: ()
+d = $([|let !(x,y) = undefined in ()|])
+e = $([|let (!x,y,~z) = undefined in ()|])
+f = $([|let f !x ~y z = undefined in ()|])
+


=====================================
testsuite/tests/th/T23036.stderr
=====================================
@@ -0,0 +1,18 @@
+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 ()
+T23036.hs:13:6-39: Splicing expression
+    [| let !(x, y) = undefined in () |]
+  ======>
+    let !(x, y) = undefined in ()
+T23036.hs:14:6-42: Splicing expression
+    [| let (!x, y, ~z) = undefined in () |]
+  ======>
+    let (!x, y, ~z) = undefined in ()
+T23036.hs:15:6-42: Splicing expression
+    [| let f !x ~y z = undefined in () |]
+  ======>
+    let f !x ~y z = 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/e0708a02b525be9a97b4c4d99128b7f787c24c4b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0708a02b525be9a97b4c4d99128b7f787c24c4b
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/18a64ba8/attachment-0001.html>


More information about the ghc-commits mailing list