[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update Haddock submodule to fix #23368

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Aug 8 01:06:18 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
6c0e2247 by sheaf at 2023-08-07T13:31:21-04:00
Update Haddock submodule to fix #23368

This submodule update adds the following three commits:

bbf1c8ae - Check for puns
0550694e - Remove fake exports for (~), List, and Tuple<n>
5877bceb - Fix pretty-printing of Solo and MkSolo

These commits fix the issues with Haddock HTML rendering reported in
ticket #23368.

Fixes #23368

- - - - -
5b5be3ea by Matthew Pickering at 2023-08-07T13:32:00-04:00
Revert "Bump bytestring submodule to 0.11.5.1"

This reverts commit 43578d60bfc478e7277dcd892463cec305400025.

Fixes #23789

- - - - -
5dad1055 by Ben Gamari at 2023-08-07T21:06:11-04:00
configure: Derive library version from ghc-prim.cabal.in

Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon
it.

Closes #23726.

- - - - -
a130aaf7 by Ryan Scott at 2023-08-07T21:06:12-04:00
tcExpr: Push expected types for untyped TH splices inwards

In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much
simpler case that simply delegates to `tcApp`. Although this passed the test
suite at the time, this was actually an error, as the previous `tcExpr` case
was critically pushing the expected type inwards. This actually matters for
programs like the one in #23796, which GHC would not accept with type inference
alone—we need full-blown type _checking_ to accept these.

I have added back the previous `tcExpr` case for `HsUntypedSplice` and now
explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and
another in `splitHsApps`) in `Note [Looking through Template Haskell splices in
splitHsApps]` in `GHC.Tc.Gen.Head`.

Fixes #23796.

- - - - -


12 changed files:

- .gitlab-ci.yml
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Utils/Binary.hs
- configure.ac
- hadrian/src/Settings/Warnings.hs
- libraries/bytestring
- testsuite/tests/ghci/scripts/T9881.stdout
- testsuite/tests/ghci/scripts/ghci025.stdout
- + testsuite/tests/th/T23796.hs
- testsuite/tests/th/all.T
- utils/haddock


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -401,7 +401,7 @@ hadrian-multi:
     # workaround for docker permissions
     - sudo chown ghc:ghc -R .
   variables:
-    GHC_FLAGS: "-Werror -Wwarn=deprecations"
+    GHC_FLAGS: -Werror
     CONFIGURE_ARGS: --enable-bootstrap-with-devel-snapshot
   tags:
     - x86_64-linux


=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -195,7 +195,6 @@ tcExpr :: HsExpr GhcRn -> ExpRhoType -> TcM (HsExpr GhcTc)
 --   - ExprWithTySig   (e :: type)
 --   - HsRecSel        overloaded record fields
 --   - HsExpanded      renamer expansions
---   - HsUntypedSplice untyped Template Haskell splices
 --   - HsOpApp         operator applications
 --   - HsOverLit       overloaded literals
 -- These constructors are the union of
@@ -209,7 +208,6 @@ tcExpr e@(HsAppType {})          res_ty = tcApp e res_ty
 tcExpr e@(ExprWithTySig {})      res_ty = tcApp e res_ty
 tcExpr e@(HsRecSel {})           res_ty = tcApp e res_ty
 tcExpr e@(XExpr (HsExpanded {})) res_ty = tcApp e res_ty
-tcExpr e@(HsUntypedSplice {})    res_ty = tcApp e res_ty
 
 tcExpr e@(HsOverLit _ lit) res_ty
   = do { mb_res <- tcShortCutLit lit res_ty
@@ -579,6 +577,18 @@ tcExpr (HsTypedSplice ext splice)   res_ty = tcTypedSplice ext splice res_ty
 tcExpr e@(HsTypedBracket _ body)    res_ty = tcTypedBracket e body res_ty
 
 tcExpr e@(HsUntypedBracket ps body) res_ty = tcUntypedBracket e body ps res_ty
+tcExpr (HsUntypedSplice splice _)   res_ty
+  -- Since `tcApp` deals with `HsUntypedSplice` (in `splitHsApps`), you might
+  -- wonder why we don't delegate to `tcApp` as we do for `HsVar`, etc.
+  -- (See the initial block of equations for `tcExpr`.) But we can't do this
+  -- for `HsUntypedSplice`; to see why, read Wrinkle (UTS1) in
+  -- Note [Looking through Template Haskell splices in splitHsApps] in
+  -- GHC.Tc.Gen.Head.
+  = case splice of
+      HsUntypedSpliceTop mod_finalizers expr
+        -> do { addModFinalizersWithLclEnv mod_finalizers
+              ; tcExpr expr res_ty }
+      HsUntypedSpliceNested {} -> panic "tcExpr: invalid nested splice"
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -803,10 +803,20 @@ handles both of these. This is easy to accomplish, since all the real work in
 handling splices and quasiquotes has already been performed by the renamer by
 the time we get to `splitHsApps`.
 
-`tcExpr`, which typechecks expressions, handles `HsUntypedSplice` by simply
-delegating to `tcApp`, which in turn calls `splitHsApps`.  This means that
-`splitHsApps` is the unique part of the code that runs an `HsUntypedSplice`'s
-modFinalizers.
+Wrinkle (UTS1):
+  `tcExpr` has a separate case for `HsUntypedSplice`s that do not occur at the
+  head of an application. This is important to handle programs like this one:
+
+    foo :: (forall a. a -> a) -> b -> b
+    foo = $([| \g x -> g x |])
+
+  Here, it is vital that we push the expected type inwards so that `g` gets the
+  type `forall a. a -> a`, and the `tcExpr` case for `HsUntypedSplice` performs
+  this pushing. Without it, we would instead infer `g` to have type `b -> b`,
+  which isn't sufficiently general. Unfortunately, this does mean that there are
+  two different places in the code where an `HsUntypedSplice`'s modFinalizers can
+  be ran, depending on whether the splice appears at the head of an application
+  or not.
 -}
 
 {- *********************************************************************


=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -1240,13 +1240,13 @@ putBS :: BinHandle -> ByteString -> IO ()
 putBS bh bs =
   BS.unsafeUseAsCStringLen bs $ \(ptr, l) -> do
     put_ bh l
-    putPrim bh l (\op -> copyBytes op (castPtr ptr) l)
+    putPrim bh l (\op -> BS.memcpy op (castPtr ptr) l)
 
 getBS :: BinHandle -> IO ByteString
 getBS bh = do
   l <- get bh :: IO Int
   BS.create l $ \dest -> do
-    getPrim bh l (\src -> copyBytes dest src l)
+    getPrim bh l (\src -> BS.memcpy dest src l)
 
 instance Binary ByteString where
   put_ bh f = putBS bh f


=====================================
configure.ac
=====================================
@@ -1146,11 +1146,11 @@ dnl The packages below should include all packages needed by
 dnl doc/users_guide/ghc_config.py.in.
 LIBRARY_VERSION(base)
 LIBRARY_VERSION(Cabal, Cabal/Cabal/Cabal.cabal)
-dnl template-haskell.cabal is generated later
-dnl but the .in file already has the version
+dnl template-haskell.cabal and ghc-prim.cabal are generated later
+dnl by Hadrian but the .in files already have the version
 LIBRARY_VERSION(template-haskell, template-haskell/template-haskell.cabal.in)
 LIBRARY_VERSION(array)
-LIBRARY_VERSION(ghc-prim)
+LIBRARY_VERSION(ghc-prim, ghc-prim/ghc-prim.cabal.in)
 LIBRARY_VERSION(ghc-compact)
 LIBRARY_ghc_VERSION="$ProjectVersion"
 AC_SUBST(LIBRARY_ghc_VERSION)


=====================================
hadrian/src/Settings/Warnings.hs
=====================================
@@ -53,12 +53,10 @@ ghcWarningsArgs = do
         , package primitive    ? pure [ "-Wno-unused-imports"
                                       , "-Wno-deprecations" ]
         , package rts          ? pure [ "-Wcpp-undef" ]
-        , package text         ? pure [ "-Wno-deprecations" ]
         , package terminfo     ? pure [ "-Wno-unused-imports" ]
         , package transformers ? pure [ "-Wno-unused-matches"
                                       , "-Wno-unused-imports"
                                       , "-Wno-redundant-constraints"
                                       , "-Wno-orphans" ]
-        , package unix         ? pure [ "-Wno-deprecations" ]
         , package win32        ? pure [ "-Wno-trustworthy-safe" ]
         , package xhtml        ? pure [ "-Wno-unused-imports" ] ] ]


=====================================
libraries/bytestring
=====================================
@@ -1 +1 @@
-Subproject commit 602fd2f3470f180d64cb8baadf63e94baec66b60
+Subproject commit 9cab76dc861f651c3940e873ce921d9e09733cc8


=====================================
testsuite/tests/ghci/scripts/T9881.stdout
=====================================
@@ -19,19 +19,19 @@ instance Ord Data.ByteString.Lazy.ByteString
 
 type Data.ByteString.ByteString :: *
 data Data.ByteString.ByteString
-  = bytestring-0.11.5.1:Data.ByteString.Internal.Type.BS {-# UNPACK #-}(GHC.ForeignPtr.ForeignPtr
+  = bytestring-0.11.4.0:Data.ByteString.Internal.Type.BS {-# UNPACK #-}(GHC.ForeignPtr.ForeignPtr
                                                                           GHC.Word.Word8)
                                                          {-# UNPACK #-}Int
-  	-- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  	-- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Monoid Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Read Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Semigroup Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Show Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Eq Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’
 instance Ord Data.ByteString.ByteString
-  -- Defined in ‘bytestring-0.11.5.1:Data.ByteString.Internal.Type’
+  -- Defined in ‘bytestring-0.11.4.0:Data.ByteString.Internal.Type’


=====================================
testsuite/tests/ghci/scripts/ghci025.stdout
=====================================
@@ -54,7 +54,7 @@ Prelude.length :: Data.Foldable.Foldable t => t a -> GHC.Types.Int
 type T.Integer :: *
 data T.Integer = ...
 T.length ::
-  bytestring-0.11.5.1:Data.ByteString.Internal.Type.ByteString
+  bytestring-0.11.4.0:Data.ByteString.Internal.Type.ByteString
   -> GHC.Types.Int
 :browse! T
 -- defined locally


=====================================
testsuite/tests/th/T23796.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T23796 where
+
+good :: (forall a. a -> a) -> b -> b
+good = \g x -> g x
+
+bad :: (forall a. a -> a) -> b -> b
+bad = $([| \g x -> g x |])


=====================================
testsuite/tests/th/all.T
=====================================
@@ -582,3 +582,4 @@ test('T22559c', normal, compile_fail, [''])
 test('T23525', normal, compile, [''])
 test('CodeQ_HKD', normal, compile, [''])
 test('T23748', normal, compile, [''])
+test('T23796', normal, compile, [''])


=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit 1313adce47bbfe77fa526d469b67043c1adcd42d
+Subproject commit 5877bcebce88afad40ae9decb0f6029681c51848



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eedf468f9108d8ae27759f2785a7f55947449c71...a130aaf739958a0415366c255057598fe78460ed

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eedf468f9108d8ae27759f2785a7f55947449c71...a130aaf739958a0415366c255057598fe78460ed
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/20230807/d87d4cfb/attachment-0001.html>


More information about the ghc-commits mailing list