[Git][ghc/ghc][wip/T18550] 8 commits: testsuite: Add broken test for #18302

Ben Gamari gitlab at gitlab.haskell.org
Fri Sep 4 01:24:49 UTC 2020



Ben Gamari pushed to branch wip/T18550 at Glasgow Haskell Compiler / GHC


Commits:
b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00
testsuite: Add broken test for #18302

- - - - -
bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00
Turn on -XMonoLocalBinds by default (#18430)

And fix the resulting type errors.

Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com>

Metric Decrease:
    parsing001

- - - - -
c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00
Remove potential space leak from Data.List.transpose

Previously, `transpose` produced a list of heads
and a list of tails independently. This meant that
a function using only some heads, and only some tails,
could potentially leak space. Use `unzip` to work
around the problem by producing pairs and selector
thunks instead. Time and allocation behavior will
be worse, but there should be no more leak potential.
- - - - -
ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00
Remove outdated note

- - - - -
85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00
Bignum: add missing compat import/export functions

- - - - -
397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00
configure: Work around Raspbian's silly packaging decisions

See #17856.

- - - - -
4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00
expected-undocumented-flags remove kill flags

It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7
and can safely be removed here
- - - - -
34e0fa96 by GHC GitLab CI at 2020-09-03T19:55:29-04:00
configure: Avoid hard-coded ld path on Windows

The fix to #17962 ended up regressing on Windows as it failed to
replicate the logic responsible for overriding the toolchain paths on
Windows. This resulted in a hard-coded path to a directory that likely
doesn't exist on the user's system (#18550).

- - - - -


21 changed files:

- aclocal.m4
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Runtime/Linker.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/expected-undocumented-flags.txt
- hadrian/cfg/system.config.in
- hadrian/src/Builder.hs
- libraries/base/Data/OldList.hs
- libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
- mk/config.mk.in
- rules/build-package-way.mk
- + testsuite/tests/rename/should_compile/T18302A.hs
- + testsuite/tests/rename/should_compile/T18302B.hs
- testsuite/tests/rename/should_compile/all.T


Changes:

=====================================
aclocal.m4
=====================================
@@ -447,25 +447,40 @@ AC_DEFUN([GET_ARM_ISA],
                      #endif]
                 )],
                 [AC_DEFINE(arm_HOST_ARCH_PRE_ARMv7, 1, [ARM pre v7])
-                 ARM_ISA=ARMv6
-                 AC_COMPILE_IFELSE([
-                        AC_LANG_PROGRAM(
-                                [],
-                                [#if defined(__VFP_FP__)
-                                     return 0;
-                                #else
-                                     no vfp
-                                #endif]
-                        )],
-                        [changequote(, )dnl
-                         ARM_ISA_EXT="[VFPv2]"
-                         changequote([, ])dnl
-                        ],
-                        [changequote(, )dnl
-                         ARM_ISA_EXT="[]"
-                         changequote([, ])dnl
-                        ]
-                )],
+                 if grep -q Raspbian /etc/issue && uname -m | grep -q armv7; then
+                   # Raspbian unfortunately makes some extremely questionable
+                   # packaging decisions, configuring gcc to compile for ARMv6
+                   # despite the fact that the RPi4 is ARMv8. As ARMv8 doesn't
+                   # support all instructions supported by ARMv6 this can
+                   # break. Work around this by checking uname to verify
+                   # that we aren't running on armv7.
+                   # See #17856.
+                   AC_MSG_NOTICE([Found compiler which claims to target ARMv6 running on ARMv7, assuming this is ARMv7 on Raspbian (see T17856)])
+                   ARM_ISA=ARMv7
+                   changequote(, )dnl
+                   ARM_ISA_EXT="[VFPv2]"
+                   changequote([, ])dnl
+                 else
+                   ARM_ISA=ARMv6
+                   AC_COMPILE_IFELSE([
+                          AC_LANG_PROGRAM(
+                                  [],
+                                  [#if defined(__VFP_FP__)
+                                       return 0;
+                                  #else
+                                       no vfp
+                                  #endif]
+                          )],
+                          [changequote(, )dnl
+                           ARM_ISA_EXT="[VFPv2]"
+                           changequote([, ])dnl
+                          ],
+                          [changequote(, )dnl
+                           ARM_ISA_EXT="[]"
+                           changequote([, ])dnl
+                          ]
+                  )
+                fi],
                 [changequote(, )dnl
                  ARM_ISA=ARMv7
                  ARM_ISA_EXT="[VFPv3,NEON]"
@@ -517,6 +532,10 @@ AC_DEFUN([FP_SETTINGS],
         SettingsHaskellCPPCommand="${mingw_bin_prefix}gcc.exe"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsLdCommand="${mingw_bin_prefix}ld.exe"
+        # Overrides FIND_MERGE_OBJECTS in order to avoid hard-coding linker
+        # path on Windows (#18550).
+        SettingsMergeObjectsCommand="${SettingsLdCommand}"
+        SettingsMergeObjectsFlags="-r --oformat=pe-bigobj-x86-64"
         SettingsArCommand="${mingw_bin_prefix}ar.exe"
         SettingsRanlibCommand="${mingw_bin_prefix}ranlib.exe"
         SettingsDllWrapCommand="${mingw_bin_prefix}dllwrap.exe"
@@ -530,6 +549,8 @@ AC_DEFUN([FP_SETTINGS],
         SettingsHaskellCPPCommand="$(basename $HaskellCPPCmd)"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsLdCommand="$(basename $LdCmd)"
+        SettingsMergeObjectsCommand="$(basename $MergeObjsCmd)"
+        SettingsMergeObjectsFlags="$MergeObjsArgs"
         SettingsArCommand="$(basename $ArCmd)"
         SettingsDllWrapCommand="$(basename $DllWrapCmd)"
         SettingsWindresCommand="$(basename $WindresCmd)"
@@ -539,6 +560,8 @@ AC_DEFUN([FP_SETTINGS],
         SettingsHaskellCPPCommand="$HaskellCPPCmd"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsLdCommand="$LdCmd"
+        SettingsMergeObjectsCommand="$MergeObjsCmd"
+        SettingsMergeObjectsFlags="$MergeObjsArgs"
         SettingsArCommand="$ArCmd"
         SettingsRanlibCommand="$RanlibCmd"
         if test -z "$DllWrapCmd"
@@ -594,6 +617,8 @@ AC_DEFUN([FP_SETTINGS],
     AC_SUBST(SettingsCCompilerSupportsNoPie)
     AC_SUBST(SettingsLdCommand)
     AC_SUBST(SettingsLdFlags)
+    AC_SUBST(SettingsMergeObjectsCommand)
+    AC_SUBST(SettingsMergeObjectsFlags)
     AC_SUBST(SettingsArCommand)
     AC_SUBST(SettingsRanlibCommand)
     AC_SUBST(SettingsDllWrapCommand)
@@ -2610,7 +2635,7 @@ AC_DEFUN([CHECK_FOR_GOLD_T22266],[
         ])
 
         $CC -c -o conftest.a.o conftest.a.c || AC_MSG_ERROR([Failed to compile test])
-        $SettingsMergeObjectsCommand $SettingsMergeObjectsFlags -T conftest.t conftest.a.o -o conftest.ar.o || AC_MSG_ERROR([Failed to merge test object])
+        $MergeObjsCmd $MergeObjsArgs -T conftest.t conftest.a.o -o conftest.ar.o || AC_MSG_ERROR([Failed to merge test object])
 
         $CC -c -o conftest.main.o conftest.main.c || AC_MSG_ERROR([Failed to compile test driver])
         $CC conftest.ar.o conftest.main.o -o conftest || AC_MSG_ERROR([Failed to link test driver])
@@ -2630,33 +2655,30 @@ AC_DEFUN([CHECK_FOR_GOLD_T22266],[
 # ------------------
 # Find which linker to use to merge object files.
 #
+# See Note [Merging object files for GHCi] in GHC.Driver.Pipeline.
 AC_DEFUN([FIND_MERGE_OBJECTS],[
     AC_REQUIRE([FIND_LD])
 
-    if test -z "$SettingsMergeObjectsCommand"; then
-        SettingsMergeObjectsCommand="$LD"
+    if test -z "$MergeObjsCmd"; then
+        MergeObjsCmd="$LD"
     fi
-    if test -z "$SettingsMergeObjectsFlags"; then
-        SettingsMergeObjectsFlags="-r"
+    if test -z "$MergeObjsArgs"; then
+        MergeObjsArgs="-r"
     fi
 
-    CHECK_FOR_GOLD_T22266($SettingsMergeObjectsCommand)
+    CHECK_FOR_GOLD_T22266($MergeObjsCmd)
     if test "$result" = "1"; then
-        AC_MSG_NOTICE([$SettingsMergeObjectsCommand is broken due to binutils 22266, looking for another linker...])
-        SettingsMergeObjectsCommand=""
-        AC_CHECK_TARGET_TOOL([SettingsMergeObjectsCommand], [ld])
-        CHECK_FOR_GOLD_T22266($SettingsMergeObjectsCommand)
+        AC_MSG_NOTICE([$MergeObjsCmd is broken due to binutils 22266, looking for another linker...])
+        MergeObjsCmd=""
+        AC_CHECK_TARGET_TOOL([MergeObjsCmd], [ld])
+        CHECK_FOR_GOLD_T22266($MergeObjsCmd)
         if test "$result" = "1"; then
-            AC_MSG_ERROR([Linker is affected by binutils 22266 but couldn't find another unaffected linker. Please set the SettingsMergeObjectsCommand variable to a functional linker.])
+            AC_MSG_ERROR([Linker is affected by binutils 22266 but couldn't find another unaffected linker. Please set the MergeObjsCmd variable to a functional linker.])
         fi
     fi
 
-    if test "$windows" = YES -a "$EnableDistroToolchain" = "NO" -a "$WORD_SIZE" = 64; then
-        SettingsMergeObjectsFlags="$SettingsMergeObjectsFlags --oformat=pe-bigobj-x86-64"
-    fi
-
-    AC_SUBST(SettingsMergeObjectsCommand)
-    AC_SUBST(SettingsMergeObjectsFlags)
+    AC_SUBST([MergeObjsCmd])
+    AC_SUBST([MergeObjsArgs])
 ])
 
 # FIND_PYTHON


=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -116,35 +116,6 @@ known keys. See
 Note [One-tuples] (Wrinkle: Make boxed one-tuple names have known keys)
 in GHC.Builtin.Types.
 
-Note [The integer library]
-~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-Clearly, we need to know the names of various definitions of the integer
-library, e.g. the type itself, `mkInteger` etc. But there are two possible
-implementations of the integer library:
-
- * integer-gmp (fast, but uses libgmp, which may not be available on all
-   targets and is GPL licensed)
- * integer-simple (slow, but pure Haskell and BSD-licensed)
-
-We want the compiler to work with either one. The way we achieve this is:
-
- * When compiling the integer-{gmp,simple} library, we pass
-     -this-unit-id  integer-wired-in
-   to GHC (see the cabal file libraries/integer-{gmp,simple}.
- * This way, GHC can use just this UnitID (see Module.integerUnitId) when
-   generating code, and the linker will succeed.
-
-Unfortuately, the abstraction is not complete: When using integer-gmp, we
-really want to use the S# constructor directly. This is controlled by
-the `integerLibrary` field of `DynFlags`: If it is IntegerGMP, we use
-this constructor directly (see  CorePrep.lookupIntegerSDataConName)
-
-When GHC reads the package data base, it (internally only) pretends it has UnitId
-`integer-wired-in` instead of the actual UnitId (which includes the version
-number); just like for `base` and other packages, as described in
-Note [Wired-in units] in GHC.Unit.Module. This is done in
-GHC.Unit.State.findWiredInUnits.
 -}
 
 {-# LANGUAGE CPP #-}


=====================================
compiler/GHC/CmmToAsm/Reg/Linear.hs
=====================================
@@ -205,7 +205,7 @@ regAlloc _ (CmmProc _ _ _ _)
 --   an entry in the block map or it is the first block.
 --
 linearRegAlloc
-        :: Instruction instr
+        :: forall instr. Instruction instr
         => NCGConfig
         -> [BlockId] -- ^ entry points
         -> BlockMap RegSet
@@ -231,6 +231,8 @@ linearRegAlloc config entry_ids block_live sccs
       ArchJavaScript -> panic "linearRegAlloc ArchJavaScript"
       ArchUnknown    -> panic "linearRegAlloc ArchUnknown"
  where
+  go :: (FR regs, Outputable regs)
+     => regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
   go f = linearRegAlloc' config f entry_ids block_live sccs
   platform = ncgPlatform config
 
@@ -973,4 +975,3 @@ loadTemp vreg (ReadMem slot) hreg spills
 
 loadTemp _ _ _ spills =
    return spills
-


=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -2290,6 +2290,7 @@ lintCoercion this@(AxiomRuleCo ax cos)
            Nothing -> err "Malformed use of AxiomRuleCo" [ ppr this ]
            Just _  -> return (AxiomRuleCo ax cos') }
   where
+  err :: forall a. String -> [SDoc] -> LintM a
   err m xs  = failWithL $
               hang (text m) 2 $ vcat (text "Rule:" <+> ppr (coaxrName ax) : xs)
 


=====================================
compiler/GHC/Core/Opt/Simplify.hs
=====================================
@@ -1909,7 +1909,7 @@ completeCall env var cont
             log_inlining $
                 sep [text "Inlining done:", nest 4 (ppr var)]
       | otherwise
-      = liftIO $ log_inlining $
+      = log_inlining $
            sep [text "Inlining done: " <> ppr var,
                 nest 4 (vcat [text "Inlined fn: " <+> nest 2 (ppr unfolding),
                               text "Cont:  " <+> ppr cont])]


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1373,7 +1373,8 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags mHscMessage cleanup
 --
 -- There better had not be any cyclic groups here -- we check for them.
 upsweep
-    :: GhcMonad m
+    :: forall m
+     . GhcMonad m
     => Maybe Messager
     -> HomePackageTable            -- ^ HPT from last time round (pruned)
     -> StableModules               -- ^ stable modules (see checkStability)
@@ -1415,8 +1416,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
     return (Failed, done')
 
   upsweep'
-    :: GhcMonad m
-    => HomePackageTable
+    :: HomePackageTable
     -> ModuleGraph
     -> [SCC ModSummary]
     -> Int


=====================================
compiler/GHC/Runtime/Linker.hs
=====================================
@@ -1134,6 +1134,7 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..}  = do
       -- Note that we want to remove all *local*
       -- (i.e. non-isExternal) names too (these are the
       -- temporary bindings from the command line).
+      keep_name :: (Name, a) -> Bool
       keep_name (n,_) = isExternalName n &&
                         nameModule n `elemModuleSet` bcos_retained
 


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -137,7 +137,7 @@ initSettings top_dir = do
         as_args  = map Option cc_args
         ld_prog  = cc_prog
         ld_args  = map Option (cc_args ++ words cc_link_args_str)
-  ld_r_prog <- getSetting "Merge objects command"
+  ld_r_prog <- getToolSetting "Merge objects command"
   ld_r_args <- getSetting "Merge objects flags"
 
   llvmTarget <- getSetting "LLVM target"


=====================================
compiler/GHC/SysTools.hs
=====================================
@@ -138,15 +138,17 @@ lazyInitLlvmConfig :: String
                -> IO LlvmConfig
 lazyInitLlvmConfig top_dir
   = unsafeInterleaveIO $ do    -- see Note [LLVM configuration]
-      targets <- readAndParse "llvm-targets" mkLlvmTarget
-      passes <- readAndParse "llvm-passes" id
-      return $ LlvmConfig { llvmTargets = targets, llvmPasses = passes }
+      targets <- readAndParse "llvm-targets"
+      passes <- readAndParse "llvm-passes"
+      return $ LlvmConfig { llvmTargets = fmap mkLlvmTarget <$> targets,
+                            llvmPasses = passes }
   where
-    readAndParse name builder =
+    readAndParse :: Read a => String -> IO a
+    readAndParse name =
       do let llvmConfigFile = top_dir </> name
          llvmConfigStr <- readFile llvmConfigFile
          case maybeReadFuzzy llvmConfigStr of
-           Just s -> return (fmap builder <$> s)
+           Just s -> return s
            Nothing -> pgmError ("Can't parse " ++ show llvmConfigFile)
 
     mkLlvmTarget :: (String, String, String) -> LlvmTarget


=====================================
compiler/ghc.cabal.in
=====================================
@@ -153,6 +153,7 @@ Library
         NoImplicitPrelude
        ,BangPatterns
        ,ScopedTypeVariables
+       ,MonoLocalBinds
 
     Exposed-Modules:
         GHC.Iface.Ext.Types


=====================================
configure.ac
=====================================
@@ -449,6 +449,8 @@ then
     NM="${mingwbin}nm.exe"
     RANLIB="${mingwbin}ranlib.exe"
     OBJDUMP="${mingwbin}objdump.exe"
+    MergeObjsCmd="$LD"
+    MergeObjsArgs="-r --oformat=pe-bigobj-x86-64"
     fp_prog_ar="${mingwbin}ar.exe"
 
     AC_PATH_PROG([Genlib],[genlib])


=====================================
docs/users_guide/expected-undocumented-flags.txt
=====================================
@@ -101,8 +101,6 @@
 -fimplicit-params
 -fimplicit-prelude
 -firrefutable-tuples
--fkill-absence
--fkill-one-shot
 -fmax-errors
 -fmax-pmcheck-iterations
 -fmono-pat-binds


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -14,6 +14,7 @@ hs-cpp         = @HaskellCPPCmd@
 ld             = @LdCmd@
 make           = @MakeCmd@
 nm             = @NmCmd@
+merge-objects  = @MergeObjsCmd@
 objdump        = @ObjdumpCmd@
 ranlib         = @REAL_RANLIB_CMD@
 sphinx-build   = @SPHINXBUILD@
@@ -117,10 +118,10 @@ conf-ld-linker-args-stage1  = @CONF_LD_LINKER_OPTS_STAGE1@
 conf-ld-linker-args-stage2  = @CONF_LD_LINKER_OPTS_STAGE2@
 conf-ld-linker-args-stage3  = @CONF_LD_LINKER_OPTS_STAGE3@
 
-conf-merge-objects-args-stage0  = @SettingsMergeObjectsFlags@
-conf-merge-objects-args-stage1  = @SettingsMergeObjectsFlags@
-conf-merge-objects-args-stage2  = @SettingsMergeObjectsFlags@
-conf-merge-objects-args-stage3  = @SettingsMergeObjectsFlags@
+conf-merge-objects-args-stage0  = @MergeObjsArgs@
+conf-merge-objects-args-stage1  = @MergeObjsArgs@
+conf-merge-objects-args-stage2  = @MergeObjsArgs@
+conf-merge-objects-args-stage3  = @MergeObjsArgs@
 
 
 # Settings:


=====================================
hadrian/src/Builder.hs
=====================================
@@ -317,7 +317,7 @@ systemBuilderPath builder = case builder of
     Happy           -> fromKey "happy"
     HsCpp           -> fromKey "hs-cpp"
     Ld _            -> fromKey "ld"
-    MergeObjects _  -> fromKey "settings-merge-objects-command"
+    MergeObjects _  -> fromKey "merge-objects"
     Make _          -> fromKey "make"
     Makeinfo        -> fromKey "makeinfo"
     Nm              -> fromKey "nm"


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -550,7 +550,13 @@ intercalate xs xss = concat (intersperse xs xss)
 transpose               :: [[a]] -> [[a]]
 transpose []             = []
 transpose ([]   : xss)   = transpose xss
-transpose ((x:xs) : xss) = (x : [h | (h:_) <- xss]) : transpose (xs : [ t | (_:t) <- xss])
+transpose ((x:xs) : xss) = (x : hds) : transpose (xs : tls)
+  where
+    -- We tie the calculations of heads and tails together
+    -- to prevent heads from leaking into tails and vice versa.
+    -- unzip makes the selector thunk arrangements we need to
+    -- ensure everything gets cleaned up properly.
+    (hds, tls) = unzip [(hd, tl) | (hd:tl) <- xss]
 
 
 -- | The 'partition' function takes a predicate a list and returns


=====================================
libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
=====================================
@@ -57,9 +57,6 @@ module GHC.Integer.GMP.Internals
     , bigNatToInt
     , bigNatToWord
     , indexBigNat#
-    , importBigNatFromByteArray
-    , exportBigNatToMutableByteArray
-
 
       -- ** 'BigNat' arithmetic operations
     , plusBigNat
@@ -112,9 +109,17 @@ module GHC.Integer.GMP.Internals
 
       -- ** Export
     , exportBigNatToAddr
+    , exportIntegerToAddr
+
+    , exportBigNatToMutableByteArray
+    , exportIntegerToMutableByteArray
 
       -- ** Import
     , importBigNatFromAddr
+    , importIntegerFromAddr
+
+    , importBigNatFromByteArray
+    , importIntegerFromByteArray
     ) where
 
 import GHC.Integer
@@ -373,6 +378,18 @@ exportBigNatToAddr (BN# b) addr endian = IO \s ->
    case B.bigNatToAddr# b addr endian s of
       (# s', w #) -> (# s', W# w #)
 
+{-# DEPRECATED importIntegerFromAddr "Use integerFromAddr# instead" #-}
+importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer
+importIntegerFromAddr addr sz endian = IO \s ->
+   case I.integerFromAddr# sz addr endian s of
+      (# s', i #) -> (# s', i #)
+
+{-# DEPRECATED exportIntegerToAddr "Use integerToAddr# instead" #-}
+exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word
+exportIntegerToAddr i addr endian = IO \s ->
+   case I.integerToAddr# i addr endian s of
+      (# s', w #) -> (# s', W# w #)
+
 wordToBigNat :: Word# -> BigNat
 wordToBigNat w = BN# (B.bigNatFromWord# w)
 
@@ -398,3 +415,13 @@ importBigNatFromByteArray ba off sz endian = case runRW# (B.bigNatFromByteArray#
 exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
 exportBigNatToMutableByteArray (BN# ba) mba off endian = IO (\s -> case B.bigNatToMutableByteArray# ba mba off endian s of
    (# s', r #) -> (# s', W# r #))
+
+{-# DEPRECATED importIntegerFromByteArray "Use integerFromByteArray# instead" #-}
+importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer
+importIntegerFromByteArray ba off sz endian = case runRW# (I.integerFromByteArray# sz ba off endian) of
+   (# _, r #) -> r
+
+{-# DEPRECATED exportIntegerToMutableByteArray "Use integerToMutableByteArray# instead" #-}
+exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
+exportIntegerToMutableByteArray i mba off endian = IO (\s -> case I.integerToMutableByteArray# i mba off endian s of
+   (# s', r #) -> (# s', W# r #))


=====================================
mk/config.mk.in
=====================================
@@ -545,6 +545,16 @@ LD_STAGE1       = $(LD)
 LD_STAGE2       = $(LD)
 LD_STAGE3       = $(LD)
 
+MERGE_OBJS_STAGE0 = @MergeObjsCmd@
+MERGE_OBJS_STAGE1 = @MergeObjsCmd@
+MERGE_OBJS_STAGE2 = @MergeObjsCmd@
+MERGE_OBJS_STAGE3 = @MergeObjsCmd@
+
+MERGE_OBJS_STAGE0_FLAGS = @MergeObjsArgs@
+MERGE_OBJS_STAGE1_FLAGS = @MergeObjsArgs@
+MERGE_OBJS_STAGE2_FLAGS = @MergeObjsArgs@
+MERGE_OBJS_STAGE3_FLAGS = @MergeObjsArgs@
+
 # Cross-compiling options
 # See Note [CrossCompiling vs Stage1Only]
 CrossCompiling        = @CrossCompiling@


=====================================
rules/build-package-way.mk
=====================================
@@ -107,6 +107,7 @@ endif
 endif
 
 # Build the GHCi library
+# See Note [Merging object files for GHCi] in GHC.Driver.Pipeline.
 ifneq "$(filter $3, v p)" ""
 $1_$2_$3_GHCI_LIB = $1/$2/build/HS$$($1_$2_COMPONENT_ID).$$($3_osuf)
 ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES"
@@ -116,7 +117,7 @@ BINDIST_LIBS += $$($1_$2_$3_GHCI_LIB)
 endif
 endif
 $$($1_$2_$3_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT)
-	$$(call cmd,SettingsMergeObjectsCommand) $(SettingsMergeObjectsFlags) $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS)
+	$$(call cmd,MERGE_OBJS_STAGE$4) $(MERGE_OBJS_STAGE$4_FLAGS) $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS)
 ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES"
 # Don't bother making ghci libs for bootstrapping packages
 ifneq "$4" "0"


=====================================
testsuite/tests/rename/should_compile/T18302A.hs
=====================================
@@ -0,0 +1,4 @@
+module T18302A ( module GHC.Prim ) where
+
+import GHC.Prim
+


=====================================
testsuite/tests/rename/should_compile/T18302B.hs
=====================================
@@ -0,0 +1,8 @@
+-- | Check that TYPE and (->) are re-exportable.
+module T18302B where
+
+import T18302A
+
+type T = TYPE
+type F = (->)
+


=====================================
testsuite/tests/rename/should_compile/all.T
=====================================
@@ -176,3 +176,4 @@ test('T17832', [], multimod_compile, ['T17832M1', 'T17832M2'])
 test('T17837', normal, compile, [''])
 test('T18497', [], makefile_test, ['T18497'])
 test('T18264', [], makefile_test, ['T18264'])
+test('T18302', expect_broken(18302), compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d56b9fc1845a13d5eb3703f247d1f1fb043b0fe7...34e0fa963f35a77093fc7111a80c557fc6bd614f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d56b9fc1845a13d5eb3703f247d1f1fb043b0fe7...34e0fa963f35a77093fc7111a80c557fc6bd614f
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/20200903/f8757044/attachment-0001.html>


More information about the ghc-commits mailing list