[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Fix #16603 by documenting some important changes in changelogs

Marge Bot gitlab at gitlab.haskell.org
Wed May 8 06:38:23 UTC 2019



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


Commits:
786e665b by Ryan Scott at 2019-05-08T05:55:45Z
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.

- - - - -
0eeb4cfa by Ryan Scott at 2019-05-08T06:01:54Z
Fix #16632 by using the correct SrcSpan in checkTyClHdr

`checkTyClHdr`'s case for `HsTyVar` was grabbing the wrong `SrcSpan`,
which lead to error messages pointing to the wrong location. Easily
fixed.

- - - - -
daa1307f by Kevin Buhr at 2019-05-08T06:38:13Z
stg_floatToWord32zh: zero-extend the Word32 (#16617)

The primop stgFloatToWord32 was sign-extending the 32-bit word, resulting
in weird negative Word32s.  Zero-extend them instead.

Closes #16617.

- - - - -
8cc0bb0e by Richard Eisenberg at 2019-05-08T06:38:15Z
Regression test for #16627.

test: typecheck/should_fail/T16627

- - - - -
cf19bd9e by John Ericson at 2019-05-08T06:38:16Z
Purge TargetPlatform_NAME and cTargetPlatformString

- - - - -
3a48afa6 by Vladislav Zavialov at 2019-05-08T06:38:16Z
Add a regression test for #14548

- - - - -


23 changed files:

- compiler/ghc.mk
- compiler/main/DynFlags.hs
- compiler/main/SysTools.hs
- compiler/parser/RdrHsSyn.hs
- compiler/utils/Panic.hs
- docs/users_guide/8.8.1-notes.rst
- hadrian/src/Rules/Generate.hs
- includes/Cmm.h
- includes/ghc.mk
- libraries/base/cbits/CastFloatWord.cmm
- libraries/base/changelog.md
- + testsuite/tests/codeGen/should_run/T16617.hs
- + testsuite/tests/codeGen/should_run/T16617.stdout
- testsuite/tests/codeGen/should_run/all.T
- + testsuite/tests/indexed-types/should_compile/T16632.hs
- + testsuite/tests/indexed-types/should_compile/T16632.stderr
- testsuite/tests/indexed-types/should_compile/all.T
- + testsuite/tests/rename/should_fail/T14548.hs
- + testsuite/tests/rename/should_fail/T14548.stderr
- testsuite/tests/rename/should_fail/all.T
- + testsuite/tests/typecheck/should_fail/T16627.hs
- + testsuite/tests/typecheck/should_fail/T16627.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/ghc.mk
=====================================
@@ -63,8 +63,6 @@ compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/.
 	@echo 'cBuildPlatformString = BuildPlatform_NAME'                   >> $@
 	@echo 'cHostPlatformString :: String'                               >> $@
 	@echo 'cHostPlatformString = HostPlatform_NAME'                     >> $@
-	@echo 'cTargetPlatformString :: String'                             >> $@
-	@echo 'cTargetPlatformString = TargetPlatform_NAME'                 >> $@
 	@echo                                                               >> $@
 	@echo 'cProjectName          :: String'                             >> $@
 	@echo 'cProjectName          = "$(ProjectName)"'                    >> $@
@@ -150,7 +148,6 @@ compiler/stage1/$(PLATFORM_H) : mk/config.mk mk/project.mk | $$(dir $$@)/.
 	@echo                                                    >> $@
 	@echo "#define BuildPlatform_NAME  \"$(BUILDPLATFORM)\""  >> $@
 	@echo "#define HostPlatform_NAME   \"$(HOSTPLATFORM)\""   >> $@
-	@echo "#define TargetPlatform_NAME \"$(TARGETPLATFORM)\"" >> $@
 	@echo                                                     >> $@
 	@echo "#define $(BuildPlatform_CPP)_BUILD 1"              >> $@
 	@echo "#define $(HostPlatform_CPP)_HOST 1"                >> $@
@@ -192,7 +189,6 @@ compiler/stage2/$(PLATFORM_H) : mk/config.mk mk/project.mk | $$(dir $$@)/.
 	@echo                                                     >> $@
 	@echo "#define BuildPlatform_NAME  \"$(HOSTPLATFORM)\""   >> $@
 	@echo "#define HostPlatform_NAME   \"$(TARGETPLATFORM)\"" >> $@
-	@echo "#define TargetPlatform_NAME \"$(TARGETPLATFORM)\"" >> $@
 	@echo                                                     >> $@
 	@echo "#define $(HostPlatform_CPP)_BUILD 1"               >> $@
 	@echo "#define $(TargetPlatform_CPP)_HOST 1"              >> $@


=====================================
compiler/main/DynFlags.hs
=====================================
@@ -1356,6 +1356,7 @@ data Settings = Settings {
   sPlatformConstants     :: PlatformConstants,
 
   -- Formerly Config.hs, target specific
+  sTargetPlatformString :: String, -- TODO Recalculate string from richer info?
   sTablesNextToCode :: Bool
  }
 
@@ -5616,7 +5617,7 @@ compilerInfo dflags
        ("Stage",                       cStage),
        ("Build platform",              cBuildPlatformString),
        ("Host platform",               cHostPlatformString),
-       ("Target platform",             cTargetPlatformString),
+       ("Target platform",             sTargetPlatformString $ settings dflags),
        ("Have interpreter",            cGhcWithInterpreter),
        ("Object splitting supported",  showBool False),
        ("Have native code generator",  cGhcWithNativeCodeGen),


=====================================
compiler/main/SysTools.hs
=====================================
@@ -177,6 +177,7 @@ initSysTools top_dir
                                  Nothing -> pgmError ("Failed to read " ++ show key ++ " value " ++ show xs)
                              Nothing -> pgmError ("No entry for " ++ show key ++ " in " ++ show settingsFile)
        crossCompiling <- getBooleanSetting "cross compiling"
+       targetPlatformString <- getSetting "target platform string"
        targetArch <- readSetting "target arch"
        targetOS <- readSetting "target os"
        targetWordSize <- readSetting "target word size"
@@ -305,6 +306,7 @@ initSysTools top_dir
                     sOpt_lc      = [],
                     sOpt_i       = [],
                     sPlatformConstants = platformConstants,
+                    sTargetPlatformString = targetPlatformString,
                     sTablesNextToCode = tablesNextToCode
              }
 


=====================================
compiler/parser/RdrHsSyn.hs
=====================================
@@ -955,8 +955,8 @@ checkTyClHdr is_cls ty
            ; let name = mkOccName tcClsName (starSym isUni)
            ; return (cL l (Unqual name), acc, fix, (ann ++ mkParensApiAnn lp)) }
 
-    go l (HsTyVar _ _ (dL->L _ tc)) acc ann fix
-      | isRdrTc tc               = return (cL l tc, acc, fix, ann)
+    go _ (HsTyVar _ _ ltc@(dL->L _ tc)) acc ann fix
+      | isRdrTc tc               = return (ltc, acc, fix, ann)
     go _ (HsOpTy _ t1 ltc@(dL->L _ tc) t2) acc ann _fix
       | isRdrTc tc               = return (ltc, HsValArg t1:HsValArg t2:acc, Infix, ann)
     go l (HsParTy _ ty)    acc ann fix = goL ty acc (ann ++mkParensApiAnn l) fix


=====================================
compiler/utils/Panic.hs
=====================================
@@ -160,13 +160,13 @@ showGhcException exception
     sorryMsg :: ShowS -> ShowS
     sorryMsg s =
         showString "sorry! (unimplemented feature or known bug)\n"
-      . showString ("  (GHC version " ++ cProjectVersion ++ " for " ++ TargetPlatform_NAME ++ "):\n\t")
+      . showString ("  (GHC version " ++ cProjectVersion ++ ":\n\t")
       . s . showString "\n"
 
     panicMsg :: ShowS -> ShowS
     panicMsg s =
         showString "panic! (the 'impossible' happened)\n"
-      . showString ("  (GHC version " ++ cProjectVersion ++ " for " ++ TargetPlatform_NAME ++ "):\n\t")
+      . showString ("  (GHC version " ++ cProjectVersion ++ ":\n\t")
       . s . showString "\n\n"
       . showString "Please report this as a GHC bug:  https://www.haskell.org/ghc/reportabug\n"
 


=====================================
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`.
@@ -143,6 +165,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.
 
 ``ghc-prim`` library
@@ -164,6 +193,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`).
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -292,6 +292,7 @@ generateSettings = do
         , ("libtool command", settingsFileSetting SettingsFileSetting_LibtoolCommand)
         , ("unlit command", ("$topdir/bin/" <>) . takeFileName <$> builderPath Unlit)
         , ("cross compiling", flag' CrossCompiling)
+        , ("target platform string", setting TargetPlatform)
         , ("target os", lookupValueOrError configFile "haskell-target-os")
         , ("target arch", lookupValueOrError configFile "haskell-target-arch")
         , ("target word size", lookupValueOrError configFile "target-word-size")
@@ -357,8 +358,6 @@ generateConfigHs = do
         , "cBuildPlatformString = BuildPlatform_NAME"
         , "cHostPlatformString :: String"
         , "cHostPlatformString = HostPlatform_NAME"
-        , "cTargetPlatformString :: String"
-        , "cTargetPlatformString = TargetPlatform_NAME"
         , ""
         , "cProjectName          :: String"
         , "cProjectName          = " ++ show cProjectName
@@ -452,7 +451,6 @@ generateGhcBootPlatformH = do
         , ""
         , "#define BuildPlatform_NAME  " ++ show buildPlatform
         , "#define HostPlatform_NAME   " ++ show hostPlatform
-        , "#define TargetPlatform_NAME " ++ show targetPlatform
         , ""
         , "#define " ++ cppify buildPlatform  ++ "_BUILD 1"
         , "#define " ++ cppify hostPlatform   ++ "_HOST 1"


=====================================
includes/Cmm.h
=====================================
@@ -159,14 +159,19 @@
 #define BYTES_TO_WDS(n) ((n) / SIZEOF_W)
 #define ROUNDUP_BYTES_TO_WDS(n) (((n) + SIZEOF_W - 1) / SIZEOF_W)
 
-/* TO_W_(n) converts n to W_ type from a smaller type */
+/*
+ * TO_W_(n) and TO_ZXW_(n) convert n to W_ type from a smaller type,
+ * with and without sign extension respectively
+ */
 #if SIZEOF_W == 4
 #define TO_I64(x) %sx64(x)
 #define TO_W_(x) %sx32(x)
+#define TO_ZXW_(x) %zx32(x)
 #define HALF_W_(x) %lobits16(x)
 #elif SIZEOF_W == 8
 #define TO_I64(x) (x)
 #define TO_W_(x) %sx64(x)
+#define TO_ZXW_(x) %zx64(x)
 #define HALF_W_(x) %lobits32(x)
 #endif
 


=====================================
includes/ghc.mk
=====================================
@@ -199,6 +199,7 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/.
 	@echo ',("libtool command", "$(SettingsLibtoolCommand)")' >> $@
 	@echo ',("unlit command", "$$topdir/bin/$(utils/unlit_dist_PROG)")' >> $@
 	@echo ',("cross compiling", "$(CrossCompiling)")' >> $@
+	@echo ',("target platform string", "$(TARGETPLATFORM)")' >> $@
 	@echo ',("target os", "$(HaskellTargetOs)")' >> $@
 	@echo ',("target arch", "$(HaskellTargetArch)")' >> $@
 	@echo ',("target word size", "$(TargetWordSize)")' >> $@


=====================================
libraries/base/cbits/CastFloatWord.cmm
=====================================
@@ -61,7 +61,8 @@ stg_floatToWord32zh(F_ f)
 
     reserve 1 = ptr {
         F_[ptr] = f;
-        w = TO_W_(I32[ptr]);
+        // Fix #16617: use zero-extending (TO_ZXW_) here
+        w = TO_ZXW_(I32[ptr]);
     }
 
     return (w);


=====================================
libraries/base/changelog.md
=====================================
@@ -8,6 +8,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)`.


=====================================
testsuite/tests/codeGen/should_run/T16617.hs
=====================================
@@ -0,0 +1,10 @@
+import GHC.Float
+
+main :: IO ()
+main = do
+  -- As per #16617, Word32s should be non-negative
+  print $ castFloatToWord32 (-1)
+  print $ toInteger (castFloatToWord32 (-1)) > 0
+  -- For completeness, so should Word64s
+  print $ castDoubleToWord64 (-1)
+  print $ toInteger (castDoubleToWord64 (-1)) > 0


=====================================
testsuite/tests/codeGen/should_run/T16617.stdout
=====================================
@@ -0,0 +1,4 @@
+3212836864
+True
+13830554455654793216
+True


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -194,3 +194,4 @@ test('T15892',
         # happen, so -G1 -A32k:
         extra_run_opts('+RTS -G1 -A32k -RTS') ],
      compile_and_run, ['-O'])
+test('T16617', normal, compile_and_run, [''])


=====================================
testsuite/tests/indexed-types/should_compile/T16632.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE TypeFamilies #-}
+module T16632 where
+
+type family F a b c
+type instance F Char b Int = ()


=====================================
testsuite/tests/indexed-types/should_compile/T16632.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T16632.hs:5:22: warning: [-Wunused-type-patterns]
+    Defined but not used on the right hand side: type variable ‘b’
+  |
+5 | type instance F Char b Int = ()
+  |                      ^


=====================================
testsuite/tests/indexed-types/should_compile/all.T
=====================================
@@ -286,3 +286,4 @@ test('T15711', normal, compile, ['-ddump-types'])
 test('T15852', normal, compile, ['-ddump-types'])
 test('T15764a', normal, compile, [''])
 test('T15740a', normal, compile, [''])
+test('T16632', normal, compile, ['-Wunused-type-patterns -fdiagnostics-show-caret'])


=====================================
testsuite/tests/rename/should_fail/T14548.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE ScopedTypeVariables, TypeApplications, PolyKinds #-}
+
+module T14548 where
+
+data Prox (a :: k) = MkProx
+
+-- fail
+f :: forall a. Prox (a :: k)
+f = MkProx @k @a
+
+-- fail
+g :: forall (a :: k). Prox (a :: k)
+g = MkProx @k @a
+
+-- ok
+h :: forall k (a :: k). Prox (a :: k)
+h = MkProx @k @a


=====================================
testsuite/tests/rename/should_fail/T14548.stderr
=====================================
@@ -0,0 +1,10 @@
+
+T14548.hs:8:27: error: Not in scope: type variable ‘k’
+
+T14548.hs:9:13: error: Not in scope: type variable ‘k’
+
+T14548.hs:12:19: error: Not in scope: type variable ‘k’
+
+T14548.hs:12:34: error: Not in scope: type variable ‘k’
+
+T14548.hs:13:13: error: Not in scope: type variable ‘k’


=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -149,3 +149,4 @@ test('ExplicitForAllRules2', normal, compile_fail, [''])
 test('T15957_Fail', normal, compile_fail, ['-Werror -Wall -Wno-missing-signatures'])
 test('T16385', normal, compile_fail, [''])
 test('T16504', normal, compile_fail, [''])
+test('T14548', normal, compile_fail, [''])


=====================================
testsuite/tests/typecheck/should_fail/T16627.hs
=====================================
@@ -0,0 +1,14 @@
+{-# language TypeInType, ScopedTypeVariables #-}
+module Silly where
+import Type.Reflection (Typeable, typeRep, TypeRep)
+import Type.Reflection.Unsafe (mkTrApp)
+import GHC.Exts (TYPE, RuntimeRep (..))
+import Data.Kind (Type)
+
+mkTrFun :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
+                  (a :: TYPE r1) (b :: TYPE r2).
+           TypeRep a -> TypeRep b -> TypeRep ((a -> b) :: Type)
+mkTrFun a b = typeRep `mkTrApp` a `mkTrApp` b
+
+-- originally reported that there was no (Typeable LiftedRep) instance,
+-- presumably to overeager RuntimeRep defaulting


=====================================
testsuite/tests/typecheck/should_fail/T16627.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T16627.hs:11:15: error:
+    • No instance for (Typeable r1) arising from a use of ‘typeRep’
+    • In the first argument of ‘mkTrApp’, namely ‘typeRep’
+      In the first argument of ‘mkTrApp’, namely ‘typeRep `mkTrApp` a’
+      In the expression: typeRep `mkTrApp` a `mkTrApp` b


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -514,3 +514,4 @@ test('T16255', normal, compile_fail, [''])
 test('T16204c', normal, compile_fail, [''])
 test('T16394', normal, compile_fail, [''])
 test('T16414', normal, compile_fail, [''])
+test('T16627', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/979108ca527367767b12decedd3697ae06891f7c...3a48afa68a71e3c917dd5e170540dede758c3175

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/979108ca527367767b12decedd3697ae06891f7c...3a48afa68a71e3c917dd5e170540dede758c3175
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/20190508/faf1e558/attachment-0001.html>


More information about the ghc-commits mailing list