[Git][ghc/ghc][ghc-8.8] 8 commits: Set RELEASE=NO

Ben Gamari gitlab at gitlab.haskell.org
Thu May 28 16:49:14 UTC 2020



Ben Gamari pushed to branch ghc-8.8 at Glasgow Haskell Compiler / GHC


Commits:
ebc670a2 by Ben Gamari at 2020-05-27T22:29:40-04:00
Set RELEASE=NO

- - - - -
37c0dd8f by Alp Mestanogullari at 2020-05-27T22:47:06-04:00
Hadrian: track mingw, ship it in bindists, more robust install script

(cherry picked from commit 22c2713bcc30cea9da7d8b95f3ea99357d1551f7)

- - - - -
53b6bdee by Ben Gamari at 2020-05-27T22:47:11-04:00
Coverage: Don't produce ModBreaks if not HscInterpreted

emptyModBreaks contains a bottom and consequently it's important that we
don't use it unless necessary.

(cherry picked from commit f684a7d505f19bd78f178e01bbd8e4467aaa00ea)

- - - - -
5133f5c2 by Ben Gamari at 2020-05-27T23:14:28-04:00
iserv: Don't pass --export-dynamic on FreeBSD

This is definitely a hack but it's probably the best we can do for now.
Hadrian does the right thing here by passing --export-dynamic only to
the linker.

(cherry picked from commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9)

- - - - -
66de4d07 by Ben Gamari at 2020-05-27T23:14:28-04:00
hadrian: Use --export-dynamic when linking iserv

As noticed in #17962, the make build system currently does this (see
3ce0e0ba) but the change was never ported to Hadrian.

(cherry picked from commit eba58110538686d8fe57d5dd372624b50f1fa2b7)

- - - - -
6507c2bf by Sylvain Henry at 2020-05-27T23:14:28-04:00
Rts: show errno on failure (#18033)

(cherry picked from commit 4875d419ba066e479f7ac07f8b39ebe10c855859)

- - - - -
286cf192 by Ben Gamari at 2020-05-27T23:14:28-04:00
rts: Make non-existent linker search path merely a warning

As noted in #18105, previously this resulted in a rather intrusive error
message. This is in contrast to the general expectation that search
paths are merely places to look, not places that must exist.

Fixes #18105.

(cherry picked from commit 24af9f30681444380c25465f555599da563713cb)

- - - - -
9037a2b6 by Sylvain Henry at 2020-05-27T23:14:28-04:00
RTS: workaround a Linux kernel bug in timerfd

Reading a timerfd may return 0: https://lkml.org/lkml/2019/8/16/335.

This is currently undocumented behavior and documentation "won't happen
anytime soon" (https://lkml.org/lkml/2020/2/13/295).

With this patch, we just ignore the result instead of crashing. It may
fix #18033 but we can't be sure because we don't have enough
information.

See also this discussion about the kernel bug:
https://github.com/Azure/sonic-swss-common/pull/302/files/1f070e7920c2e5d63316c0105bf4481e73d72dc9

(cherry picked from commit 12789d3ac30dd90f77593e99ef51e54b14fbf556)

- - - - -


11 changed files:

- compiler/deSugar/Coverage.hs
- configure.ac
- hadrian/src/Base.hs
- hadrian/src/Builder.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/Program.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Packages.hs
- rts/linker/PEi386.c
- rts/posix/itimer/Pthread.c
- utils/iserv/ghc.mk


Changes:

=====================================
compiler/deSugar/Coverage.hs
=====================================
@@ -111,7 +111,7 @@ addTicksToBinds hsc_env mod mod_loc exports tyCons binds
 
      dumpIfSet_dyn dflags Opt_D_dump_ticked "HPC" (pprLHsBinds binds1)
 
-     return (binds1, HpcInfo tickCount hashNo, Just modBreaks)
+     return (binds1, HpcInfo tickCount hashNo, modBreaks)
 
   | otherwise = return (binds, emptyHpcInfo False, Nothing)
 
@@ -128,23 +128,23 @@ guessSourceFile binds orig_file =
         _ -> orig_file
 
 
-mkModBreaks :: HscEnv -> Module -> Int -> [MixEntry_] -> IO ModBreaks
+mkModBreaks :: HscEnv -> Module -> Int -> [MixEntry_] -> IO (Maybe ModBreaks)
 mkModBreaks hsc_env mod count entries
-  | HscInterpreted <- hscTarget (hsc_dflags hsc_env) = do
+  | breakpointsEnabled (hsc_dflags hsc_env) = do
     breakArray <- GHCi.newBreakArray hsc_env (length entries)
     ccs <- mkCCSArray hsc_env mod count entries
     let
            locsTicks  = listArray (0,count-1) [ span  | (span,_,_,_)  <- entries ]
            varsTicks  = listArray (0,count-1) [ vars  | (_,_,vars,_)  <- entries ]
            declsTicks = listArray (0,count-1) [ decls | (_,decls,_,_) <- entries ]
-    return emptyModBreaks
+    return $ Just $ emptyModBreaks
                        { modBreaks_flags = breakArray
                        , modBreaks_locs  = locsTicks
                        , modBreaks_vars  = varsTicks
                        , modBreaks_decls = declsTicks
                        , modBreaks_ccs   = ccs
                        }
-  | otherwise = return emptyModBreaks
+  | otherwise = return Nothing
 
 mkCCSArray
   :: HscEnv -> Module -> Int -> [MixEntry_]
@@ -1038,7 +1038,7 @@ data TickishType = ProfNotes | HpcTicks | Breakpoints | SourceNotes
 
 coveragePasses :: DynFlags -> [TickishType]
 coveragePasses dflags =
-    ifa (hscTarget dflags == HscInterpreted) Breakpoints $
+    ifa (breakpointsEnabled dflags)          Breakpoints $
     ifa (gopt Opt_Hpc dflags)                HpcTicks $
     ifa (gopt Opt_SccProfilingOn dflags &&
          profAuto dflags /= NoProfAuto)      ProfNotes $
@@ -1046,6 +1046,10 @@ coveragePasses dflags =
   where ifa f x xs | f         = x:xs
                    | otherwise = xs
 
+-- | Should we produce 'Breakpoint' ticks?
+breakpointsEnabled :: DynFlags -> Bool
+breakpointsEnabled dflags = hscTarget dflags == HscInterpreted
+
 -- | Tickishs that only make sense when their source code location
 -- refers to the current file. This might not always be true due to
 -- LINE pragmas in the code - which would confuse at least HPC.


=====================================
configure.ac
=====================================
@@ -16,7 +16,7 @@ dnl
 AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.8.3], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
hadrian/src/Base.hs
=====================================
@@ -25,7 +25,7 @@ module Base (
     hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
     generatedDir, generatedPath, stageBinPath, stageLibPath, templateHscPath,
     ghcDeps, haddockDeps, relativePackageDbPath, packageDbPath, packageDbStamp,
-    ghcSplitPath
+    mingwStamp, ghcSplitPath
     ) where
 
 import Control.Applicative
@@ -137,3 +137,9 @@ templateHscPath stage = stageLibPath stage <&> (-/- "template-hsc.h")
 -- to the build root under which we will copy @ghc-split at .
 ghcSplitPath :: Stage -> FilePath
 ghcSplitPath stage = stageString stage -/- "bin" -/- "ghc-split"
+
+-- | We use this stamp file to track whether we've moved the mingw toolchain
+--   under the build root (to make it accessible to the GHCs we build on
+--   Windows). See "Rules.Program".
+mingwStamp :: FilePath
+mingwStamp = "mingw" -/- ".stamp"


=====================================
hadrian/src/Builder.hs
=====================================
@@ -184,6 +184,10 @@ instance H.Builder Builder where
                      , unlitPath ]
                   ++ ghcdeps
                   ++ [ touchyPath | win ]
+                  ++ [ root -/- mingwStamp | win ]
+                     -- proxy for the entire mingw toolchain that
+                     -- we have in inplace/mingw initially, and then at
+                     -- root -/- mingw.
 
         Hsc2Hs stage -> (\p -> [p]) <$> templateHscPath stage
         Make dir  -> return [dir -/- "Makefile"]


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -100,6 +100,7 @@ bindistRules = do
         targetPlatform <- setting TargetPlatformFull
         distDir        <- Context.distDir
         rtsDir         <- pkgIdentifier rts
+        windows        <- windowsHost
 
         let ghcBuildDir      = root -/- stageString Stage1
             bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
@@ -115,6 +116,12 @@ bindistRules = do
         copyDirectory (rtsIncludeDir)         bindistFilesDir
         need ["docs"]
         copyDirectory (root -/- "docs") bindistFilesDir
+        when windows $ do
+          copyDirectory (root -/- "mingw") bindistFilesDir
+          -- we use that opportunity to delete the .stamp file that we use
+          -- as a proxy for the whole mingw toolchain, there's no point in
+          -- shipping it
+          removeFile (bindistFilesDir -/- mingwStamp)
 
         -- We copy the binary (<build root>/stage1/bin/haddock) to
         -- the bindist's bindir (<build root>/bindist/ghc-.../bin/).
@@ -132,7 +139,8 @@ bindistRules = do
                    , "runghc"]
 
         -- Finally, we create the archive <root>/bindist/ghc-X.Y.Z-platform.tar.xz
-        command [Cwd $ root -/- "bindist"] "tar"
+        tarPath <- builderPath (Tar Create)
+        cmd [Cwd $ root -/- "bindist"] tarPath
             [ "-c", "--xz", "-f"
             , ghcVersionPretty <.> "tar.xz"
             , ghcVersionPretty ]
@@ -224,19 +232,19 @@ bindistMakefile = unlines
     , "# to it. This implementation is a bit hacky and depends on consistency"
     , "# of program names. For hadrian build this will work as programs have a"
     , "# consistent naming procedure."
-    , "\trm -f $2"
-    , "\t$(CREATE_SCRIPT) $2"
-    , "\t at echo \"#!$(SHELL)\" >>  $2"
-    , "\t at echo \"exedir=\\\"$4\\\"\" >> $2"
-    , "\t at echo \"exeprog=\\\"$1\\\"\" >> $2"
-    , "\t at echo \"executablename=\\\"$5\\\"\" >> $2"
-    , "\t at echo \"bindir=\\\"$3\\\"\" >> $2"
-    , "\t at echo \"libdir=\\\"$6\\\"\" >> $2"
-    , "\t at echo \"docdir=\\\"$7\\\"\" >> $2"
-    , "\t at echo \"includedir=\\\"$8\\\"\" >> $2"
-    , "\t at echo \"\" >> $2 "
-    , "\tcat wrappers/$1 >> $2"
-    , "\t$(EXECUTABLE_FILE) $2 ;"
+    , "\trm -f '$2'"
+    , "\t$(CREATE_SCRIPT) '$2'"
+    , "\t at echo \"#!$(SHELL)\" >>  '$2'"
+    , "\t at echo \"exedir=\\\"$4\\\"\" >> '$2'"
+    , "\t at echo \"exeprog=\\\"$1\\\"\" >> '$2'"
+    , "\t at echo \"executablename=\\\"$5\\\"\" >> '$2'"
+    , "\t at echo \"bindir=\\\"$3\\\"\" >> '$2'"
+    , "\t at echo \"libdir=\\\"$6\\\"\" >> '$2'"
+    , "\t at echo \"docdir=\\\"$7\\\"\" >> '$2'"
+    , "\t at echo \"includedir=\\\"$8\\\"\" >> '$2'"
+    , "\t at echo \"\" >> '$2'"
+    , "\tcat wrappers/$1 >> '$2'"
+    , "\t$(EXECUTABLE_FILE) '$2' ;"
     , "endef"
     , ""
     , "# Hacky function to patch up the 'haddock-interfaces' and 'haddock-html'"
@@ -245,10 +253,10 @@ bindistMakefile = unlines
     , "# $1 = package name (ex: 'bytestring')"
     , "# $2 = path to .conf file"
     , "# $3 = Docs Directory"
-    , "\tcat $2 | sed 's|haddock-interfaces.*|haddock-interfaces: $3/html/libraries/$1/$1.haddock|' \\"
-    , "\t       | sed 's|haddock-html.*|haddock-html: $3/html/libraries/$1|' \\"
-    , "\t       > $2.copy"
-    , "\tmv $2.copy $2"
+    , "\tcat '$2' | sed 's|haddock-interfaces.*|haddock-interfaces: $3/html/libraries/$1/$1.haddock|' \\"
+    , "\t         | sed 's|haddock-html.*|haddock-html: $3/html/libraries/$1|' \\"
+    , "\t       > '$2.copy'"
+    , "\tmv '$2.copy' '$2'"
     , "endef"
     , ""
     , "# QUESTION : should we use shell commands?"
@@ -257,7 +265,7 @@ bindistMakefile = unlines
     , ".PHONY: install"
     , "install: install_lib install_bin install_includes"
     , "install: install_docs install_wrappers install_ghci"
-    , "install: update_package_db"
+    , "install: install_mingw update_package_db"
     , ""
     , "ActualBinsDir=${ghclibdir}/bin"
     , "WrapperBinsDir=${bindir}"
@@ -273,10 +281,10 @@ bindistMakefile = unlines
     , ""
     , "install_ghci:"
     , "\t at echo \"Copying and installing ghci\""
-    , "\t$(CREATE_SCRIPT) $(WrapperBinsDir)/ghci"
-    , "\t at echo \"#!$(SHELL)\" >>  $(WrapperBinsDir)/ghci"
-    , "\tcat wrappers/ghci-script >> $(WrapperBinsDir)/ghci"
-    , "\t$(EXECUTABLE_FILE) $(WrapperBinsDir)/ghci"
+    , "\t$(CREATE_SCRIPT) '$(WrapperBinsDir)/ghci'"
+    , "\t at echo \"#!$(SHELL)\" >>  '$(WrapperBinsDir)/ghci'"
+    , "\tcat wrappers/ghci-script >> '$(WrapperBinsDir)/ghci'"
+    , "\t$(EXECUTABLE_FILE) '$(WrapperBinsDir)/ghci'"
     , ""
     , "LIBRARIES = $(wildcard ./lib/*)"
     , "install_lib:"
@@ -302,7 +310,7 @@ bindistMakefile = unlines
     , "\t\tcp -R $$i \"$(docdir)/\"; \\"
     , "\tdone"
     , ""
-    , "BINARY_NAMES=$(shell ls ./bin/)"
+    , "BINARY_NAMES=$(shell ls ./wrappers/)"
     , "install_wrappers:"
     , "\t at echo \"Installing Wrapper scripts\""
     , "\t$(INSTALL_DIR) \"$(WrapperBinsDir)\""
@@ -318,8 +326,16 @@ bindistMakefile = unlines
     , "\t\t$(call patchpackageconf," ++
       "$(shell echo $(notdir $p) | sed 's/-\\([0-9]*[0-9]\\.\\)*conf//g')," ++
       "$p,$(docdir)))"
-    , "\t$(WrapperBinsDir)/ghc-pkg recache"
+    , "\t'$(WrapperBinsDir)/ghc-pkg' recache"
     , ""
+    , "# The 'foreach' that copies the mingw directory will only trigger a copy"
+    , "# when the wildcard matches, therefore only on Windows."
+    , "MINGW = $(wildcard ./mingw)"
+    , "install_mingw:"
+    , "\t at echo \"Installing MingGW\""
+    , "\t$(INSTALL_DIR) \"$(prefix)/mingw\""
+    , "\t$(foreach d, $(MINGW),\\"
+    , "\t\tcp -R ./mingw \"$(prefix)\")"
     , "# END INSTALL"
     , "# ----------------------------------------------------------------------"
     ]
@@ -385,3 +401,19 @@ ghciScriptWrapper = unlines
     [ "DIR=`dirname \"$0\"`"
     , "executable=\"$DIR/ghc\""
     , "exec $executable --interactive \"$@\"" ]
+
+-- | When not on Windows, we want to ship the 3 flavours of the iserv program
+--   in binary distributions. This isn't easily achievable by just asking for
+--   the package to be built, since here we're generating 3 different
+--   executables out of just one package, so we need to specify all 3 contexts
+--   explicitly and 'need' the result of building them.
+needIservBins :: Action ()
+needIservBins = do
+    windows <- windowsHost
+    when (not windows) $ do
+        rtsways <- interpretInContext (vanillaContext Stage1 ghc) getRtsWays
+        need =<< traverse programPath
+                   [ Context Stage1 iserv w
+                   | w <- [vanilla, profiling, dynamic]
+                   , w `elem` rtsways
+                   ]


=====================================
hadrian/src/Rules/Program.hs
=====================================
@@ -8,6 +8,7 @@ import Context
 import Expression hiding (stage, way)
 import Oracles.Flag
 import Oracles.ModuleFiles
+import Oracles.Setting (topDirectory)
 import Packages
 import Settings
 import Settings.Default
@@ -19,6 +20,18 @@ import Flavour
 buildProgramRules :: [(Resource, Int)] -> Rules ()
 buildProgramRules rs = do
     root <- buildRootRules
+
+    -- Proxy rule for the whole mingw toolchain on Windows.
+    -- We 'need' configure  because that's when the inplace/mingw
+    -- folder gets filled with the toolchain. This "proxy" rule
+    -- is listed as a runtime dependency for stage >= 1 GHCs.
+    root -/- mingwStamp %> \stampPath -> do
+        top <- topDirectory
+        need [ top -/- "configure" ]
+        copyDirectory (top -/- "inplace" -/- "mingw") root
+        writeFile' stampPath "OK"
+
+    -- Rules for programs that are actually built by hadrian.
     forM_ [Stage0 ..] $ \stage ->
         [ root -/- stageString stage -/- "bin"     -/- "*"
         , root -/- stageString stage -/- "lib/bin" -/- "*" ] |%> \bin -> do


=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -16,6 +16,8 @@ cabalBuilderArgs = builder (Cabal Setup) ? do
     pkg       <- getPackage
     path      <- getContextPath
     stage     <- getStage
+    windows   <- expr windowsHost
+    let prefix = "${pkgroot}" ++ (if windows then "" else "/..")
     mconcat [ arg "configure"
             -- Don't strip libraries when cross compiling.
             -- TODO: We need to set @--with-strip=(stripCmdPath :: Action FilePath)@,
@@ -32,7 +34,7 @@ cabalBuilderArgs = builder (Cabal Setup) ? do
             , arg "--ipid"
             , arg "$pkg-$version"
             , arg "--prefix"
-            , arg "${pkgroot}/.."
+            , arg prefix
 
             -- NB: this is valid only because Hadrian puts the @docs@ and
             -- @libraries@ folders in the same relative position:


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -119,6 +119,14 @@ packageArgs = do
           [ notStage0 ? builder (Cabal Flags) ? arg "ghci"
           , flag CrossCompiling ? stage0 ? builder (Cabal Flags) ? arg "ghci" ]
 
+        --------------------------------- iserv --------------------------------
+        -- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that
+        -- refer to the RTS.  This is harmless if you don't use it (adds a bit
+        -- of overhead to startup and increases the binary sizes) but if you
+        -- need it there's no alternative.
+        , package iserv ? mconcat
+          [ builder (Ghc LinkHs) ? arg "-optl-Wl,--export-dynamic" ]
+
         -------------------------------- haddock -------------------------------
         , package haddock ?
           builder (Cabal Flags) ? arg "in-ghc-tree"


=====================================
rts/linker/PEi386.c
=====================================
@@ -769,12 +769,12 @@ HsPtr addLibrarySearchPath_PEi386(pathchar* dll_path)
     WCHAR* abs_path = malloc(sizeof(WCHAR) * init_buf_size);
     DWORD wResult = GetFullPathNameW(dll_path, bufsize, abs_path, NULL);
     if (!wResult){
-        sysErrorBelch("addLibrarySearchPath[GetFullPathNameW]: %" PATH_FMT " (Win32 error %lu)", dll_path, GetLastError());
+        IF_DEBUG(linker, debugBelch("addLibrarySearchPath[GetFullPathNameW]: %" PATH_FMT " (Win32 error %lu)", dll_path, GetLastError()));
     }
     else if (wResult > init_buf_size) {
         abs_path = realloc(abs_path, sizeof(WCHAR) * wResult);
         if (!GetFullPathNameW(dll_path, bufsize, abs_path, NULL)) {
-            sysErrorBelch("addLibrarySearchPath[GetFullPathNameW]: %" PATH_FMT " (Win32 error %lu)", dll_path, GetLastError());
+            IF_DEBUG(linker, debugBelch("addLibrarySearchPath[GetFullPathNameW]: %" PATH_FMT " (Win32 error %lu)", dll_path, GetLastError()));
         }
     }
 


=====================================
rts/posix/itimer/Pthread.c
=====================================
@@ -109,22 +109,30 @@ static void *itimer_thread_func(void *_handle_tick)
 
     timerfd = timerfd_create(CLOCK_MONOTONIC, TFD_CLOEXEC);
     if (timerfd == -1) {
-        barf("timerfd_create");
+        barf("timerfd_create: %s", strerror(errno));
     }
     if (!TFD_CLOEXEC) {
         fcntl(timerfd, F_SETFD, FD_CLOEXEC);
     }
     if (timerfd_settime(timerfd, 0, &it, NULL)) {
-        barf("timerfd_settime");
+        barf("timerfd_settime: %s", strerror(errno));
     }
 #endif
 
     while (!exited) {
         if (USE_TIMERFD_FOR_ITIMER) {
-            if (read(timerfd, &nticks, sizeof(nticks)) != sizeof(nticks)) {
-                if (errno != EINTR) {
-                    barf("Itimer: read(timerfd) failed");
-                }
+            ssize_t r = read(timerfd, &nticks, sizeof(nticks));
+            if ((r == 0) && (errno == 0)) {
+               /* r == 0 is expected only for non-blocking fd (in which case
+                * errno should be EAGAIN) but we use a blocking fd.
+                *
+                * Due to a kernel bug (cf https://lkml.org/lkml/2019/8/16/335)
+                * on some platforms we could see r == 0 and errno == 0.
+                */
+               IF_DEBUG(scheduler, debugBelch("read(timerfd) returned 0 with errno=0. This is a known kernel bug. We just ignore it."));
+            }
+            else if (r != sizeof(nticks) && errno != EINTR) {
+               barf("Itimer: read(timerfd) failed with %s and returned %zd", strerror(errno), r);
             }
         } else {
             if (usleep(TimeToUS(itimer_interval)) != 0 && errno != EINTR) {
@@ -169,7 +177,7 @@ initTicker (Time interval, TickProc handle_tick)
         pthread_setname_np(thread, "ghc_ticker");
 #endif
     } else {
-        barf("Itimer: Failed to spawn thread");
+        barf("Itimer: Failed to spawn thread: %s", strerror(errno));
     }
 }
 
@@ -203,7 +211,7 @@ exitTicker (bool wait)
     // wait for ticker to terminate if necessary
     if (wait) {
         if (pthread_join(thread, NULL)) {
-            sysErrorBelch("Itimer: Failed to join");
+            sysErrorBelch("Itimer: Failed to join: %s", strerror(errno));
         }
         closeMutex(&mutex);
         closeCondition(&start_cond);


=====================================
utils/iserv/ghc.mk
=====================================
@@ -30,8 +30,9 @@ endif
 # refer to the RTS.  This is harmless if you don't use it (adds a bit
 # of overhead to startup and increases the binary sizes) but if you
 # need it there's no alternative.
+# Don't do this on FreeBSD to work around #17962.
 ifeq "$(TargetElf)" "YES"
-ifneq "$(TargetOS_CPP)" "solaris2"
+ifeq "$(findstring $(TargetOS_CPP), solaris2 freebsd)" ""
 # The Solaris linker does not support --export-dynamic option. It also
 # does not need it since it exports all dynamic symbols by default
 utils/iserv_stage2_MORE_HC_OPTS += -optl-Wl,--export-dynamic



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dade73c7849d05bc50d35e4c8411e2fdbba75f2a...9037a2b64ec78cc6d6946aae118622517c8163e2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dade73c7849d05bc50d35e4c8411e2fdbba75f2a...9037a2b64ec78cc6d6946aae118622517c8163e2
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/20200528/42ae94de/attachment-0001.html>


More information about the ghc-commits mailing list