[Git][ghc/ghc][cherry-pick-e172a6d1] 3 commits: Fix #16603 by documenting some important changes in changelogs

Ben Gamari gitlab at gitlab.haskell.org
Tue Jun 4 03:41:38 UTC 2019



Ben Gamari pushed to branch cherry-pick-e172a6d1 at Glasgow Haskell Compiler / GHC


Commits:
334dd6da by Ryan Scott at 2019-05-08T13:31:22Z
Fix #16603 by documenting some important changes in changelogs

This addresses some glaring omissions from
`libraries/base/changelog.md` and
`docs/users_guide/8.8.1-notes.rst`, fixing #16603 in the process.

- - - - -
605869c7 by Vladislav Zavialov at 2019-06-03T21:28:12Z
Fix optSemi type in Parser.y

The definition of 'optSemi' claimed it had type

([Located a],Bool)

Note that its production actually returns ([Located Token],Bool):

  : ';' { ([$1],True) }   -- $1 :: Located Token

Due to an infelicity in the implementation of 'happy -c', it effectively
resulted in 'unsafeCoerce :: Token -> a'.
See https://github.com/simonmar/happy/pull/134

If any consumer of 'optSemi' tried to instantiate 'a' to something not
representationally equal to 'Token', they would experience a segfault.

In addition to that, this definition made it impossible to compile Parser.y
without the -c flag (as it's reliant on this bug to cast 'Token' to 'forall
a. a').

- - - - -
07131494 by Alp Mestanogullari at 2019-06-04T03:41:36Z
Enable external interpreter when TH is requested but no internal interpreter is available


(cherry picked from commit e172a6d127a65b945b31306ff7b6c43320debfb4)
- - - - -


4 changed files:

- compiler/main/DriverPipeline.hs
- compiler/parser/Parser.y
- docs/users_guide/8.8.1-notes.rst
- libraries/base/changelog.md


Changes:

=====================================
compiler/main/DriverPipeline.hs
=====================================
@@ -258,16 +258,23 @@ compileOne' m_tc_result mHscMessage
                   then gopt_set dflags0 Opt_BuildDynamicToo
                   else dflags0
 
+       -- #16331 - when no "internal interpreter" is available but we
+       -- need to process some TemplateHaskell or QuasiQuotes, we automatically
+       -- turn on -fexternal-interpreter.
+       dflags2 = if not internalInterpreter && needsLinker
+                 then gopt_set dflags1 Opt_ExternalInterpreter
+                 else dflags1
+
        basename = dropExtension input_fn
 
        -- We add the directory in which the .hs files resides) to the import
        -- path.  This is needed when we try to compile the .hc file later, if it
        -- imports a _stub.h file that we created here.
        current_dir = takeDirectory basename
-       old_paths   = includePaths dflags1
+       old_paths   = includePaths dflags2
        !prevailing_dflags = hsc_dflags hsc_env0
        dflags =
-          dflags1 { includePaths = addQuoteInclude old_paths [current_dir]
+          dflags2 { includePaths = addQuoteInclude old_paths [current_dir]
                   , log_action = log_action prevailing_dflags }
                   -- use the prevailing log_action / log_finaliser,
                   -- not the one cached in the summary.  This is so


=====================================
compiler/parser/Parser.y
=====================================
@@ -1,4 +1,3 @@
-
 --                                                              -*-haskell-*-
 -- ---------------------------------------------------------------------------
 -- (c) The University of Glasgow 1997-2003
@@ -2586,7 +2585,7 @@ exp10 :: { LHsExpr GhcPs }
         | scc_annot exp        {% ams (sLL $1 $> $ HsSCC noExt (snd $ fst $ unLoc $1) (snd $ unLoc $1) $2)
                                       (fst $ fst $ unLoc $1) }
 
-optSemi :: { ([Located a],Bool) }
+optSemi :: { ([Located Token],Bool) }
         : ';'         { ([$1],True) }
         | {- empty -} { ([],False) }
 


=====================================
docs/users_guide/8.8.1-notes.rst
=====================================
@@ -23,6 +23,21 @@ Full details
 Language
 ~~~~~~~~
 
+- GHC now supports visible kind applications, as described in
+  `GHC proposal #15 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0015-type-level-type-applications.rst>`__. This extends the existing
+  :ref:`visible type applications <visible-type-application>` feature to permit
+  type applications at the type level (e.g., ``f :: Proxy ('Just @Bool 'True)``) in
+  addition to the term level (e.g., ``g = Just @Bool True``).
+
+- GHC now allows explicitly binding type variables in type family instances and
+  rewrite rules, as described in
+  `GHC proposal #7 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0007-instance-foralls.rst>`__. For instance: ::
+
+    type family G a b where
+      forall x y. G [x] (Proxy y) = Double
+      forall z.   G z   z         = Bool
+    {-# RULES "example" forall a. forall (x :: a). id x = x #-}
+
 - :extension:`ScopedTypeVariables`: The type variable that a type signature on
   a pattern can bring into scope can now stand for arbitrary types. Previously,
   they could only stand in for other type variables, but this restriction was deemed
@@ -76,6 +91,13 @@ Language
 Compiler
 ~~~~~~~~
 
+- The final phase of the ``MonadFail`` proposal has been implemented.
+  Accordingly, the ``MonadFailDesugaring`` language extension is now
+  deprecated, as its effects are always enabled. Similarly, the
+  ``-Wnoncanonical-monadfail-instances`` flag is also deprecated, as there is
+  no longer any way to define a "non-canonical" ``Monad`` or ``MonadFail``
+  instance.
+
 - New :ghc-flag:`-keep-hscpp-files` to keep the output of the CPP pre-processor.
 
 - The :ghc-flag:`-Wcompat` warning group now includes :ghc-flag:`-Wstar-is-type`.
@@ -134,6 +156,13 @@ Template Haskell
   longer included when reifying ``C``. It's possible that this may break some
   code which assumes the existence of ``forall a. C a =>``.
 
+- Template Haskell has been updated to support visible kind applications and
+  explicit ``foralls`` in type family instances and ``RULES``. These required
+  a couple of backwards-incompatible changes to the ``template-haskell`` API.
+  Please refer to the
+  `GHC 8.8 Migration Guide <https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.8#template-haskell-21500>`__
+  for more details.
+
 - Template Haskell now supports implicit parameters and recursive do.
 
 - Template Haskell splices can now embed assembler source (:ghc-ticket:`16180`)
@@ -156,6 +185,20 @@ Template Haskell
 ``base`` library
 ~~~~~~~~~~~~~~~~
 
+- The final phase of the ``MonadFail`` proposal has been implemented. As a
+  result of this change:
+
+  - The ``fail`` method of ``Monad`` has been removed in favor of the method of
+    the same name in the ``MonadFail`` class.
+
+  - ``MonadFail(fail)`` is now re-exported from the ``Prelude`` and
+    ``Control.Monad`` modules.
+
+  These are breaking changes that may require you to update your code. Please
+  refer to the
+  `GHC 8.8 Migration Guide <https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.8#base-41300>`__
+  for more details.
+
 - Support the characters from recent versions of Unicode (up to v. 12) in literals
     (see :ghc-ticket:`5518`).
 


=====================================
libraries/base/changelog.md
=====================================
@@ -3,6 +3,14 @@
 ## 4.13.0.0 *TBA*
   * Bundled with GHC *TBA*
 
+  * The final phase of the `MonadFail` proposal has been implemented:
+
+    * The `fail` method of `Monad` has been removed in favor of the method of
+      the same name in the `MonadFail` class.
+
+    * `MonadFail(fail)` is now re-exported from the `Prelude` and
+      `Control.Monad` modules.
+
   * Fix `Show` instance of `Data.Fixed`: Negative numbers are now parenthesized
     according to their surrounding context. I.e. `Data.Fixed.show` produces
     syntactically correct Haskell for expressions like `Just (-1 :: Fixed E2)`.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/0cf2cdbb5b5bd751b0f9c9a8fce4b432688c6db5...07131494e77f4c985c2cef369238dc8e83a98a90

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/0cf2cdbb5b5bd751b0f9c9a8fce4b432688c6db5...07131494e77f4c985c2cef369238dc8e83a98a90
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/20190603/654cf4d7/attachment-0001.html>


More information about the ghc-commits mailing list