[Git][ghc/ghc][wip/slowtest] 21 commits: gitlab-ci: Disable shallow clones

Ben Gamari gitlab at gitlab.haskell.org
Sat Jun 8 18:15:50 UTC 2019



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


Commits:
b2f106f5 by Ben Gamari at 2019-06-08T18:02:02Z
gitlab-ci: Disable shallow clones

Previously we were passing `--unshallow` to `git fetch` in the linting
rules to ensure that the base commit which we were linting with respect
to was available. However, this breaks due to GitLab's re-use of
working directories since `git fetch --unshallow` fails on a repository
which is not currently shallow.

Given that `git fetch --unshallow` circumvents the efficiencies provided
by shallow clones anyways, let's just disable them entirely.

There is no documented way to do disable shallow clones but on checking
the GitLab implementation it seems that setting `GIT_DEPTH=0` should do
the trick.

- - - - -
608e1af6 by Ben Gamari at 2019-06-08T18:15:45Z
gitlab-ci: Test using slowtest in deb9-debug job

- - - - -
c9641703 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark hWaitForInput-accurate-stdin as broken in threaded ways

As noted in #16535.

- - - - -
4cfbef6c by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Make closureSize less sensitive to optimisation

- - - - -
c56b2c1a by Ben Gamari at 2019-06-08T18:15:45Z
process: Bump submodule

 * Skip process005 in ghci way
 * Mark process002 as fragile in threaded2

- - - - -
999ba652 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T13167 as fragile in threaded2

As noted in #16536.

- - - - -
f1214829 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T13910 as broken in optasm

Due to #16537.

- - - - -
8da062a8 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T14761c as broken in hpc and optasm ways

As noted in #16540.

- - - - -
48fb8dba by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T16180 as broken in ghci and ext-interp ways

As noted in #16541.

- - - - -
5256f023 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Omit tcrun022 in hpc way

As noted in #16542, the expected rule doesn't fire. However, this
doesn't seem terribly surpring given the circumstances.

- - - - -
2d530d3e by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark Overflow as broken in hpc way

As noted in #16543.

- - - - -
d8ec93f2 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark closure_size as broken in threaded2, optasm, dyn ways

As noted in #16531.

- - - - -
eed762a6 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T2783 as fragile in threaded1

It was previously marked as broken but it passes non-deterministically.
See #2783.

- - - - -
614fb91b by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Skip T7919 in ghci way

It times out pretty reliably. It's not clear that much is gained by
running this test in the ghci way anyways.

- - - - -
f2e47f71 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Fix fragile_for test modifier

- - - - -
816aa700 by Ben Gamari at 2019-06-08T18:15:45Z
Bump unix submodule

Marks posix002 as fragile in threaded2 way due to #16550.

- - - - -
d437a98c by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Fix omit_ways usage

omit_ways expects a list but this was broken in several cases.

- - - - -
ef82fe55 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark threadstatus-T9333 as fragile in ghci way

As noted in #16555.

- - - - -
a0778f41 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Omit profasm way for cc017

cc017 requires TH but we can't load dynamic profiled objects.

- - - - -
716c2095 by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Skip T493 in ghci way.

T493 tests #493, which is an FFI test. FFI tests should be skipped
in ghci way.

- - - - -
3d0857da by Ben Gamari at 2019-06-08T18:15:45Z
testsuite: Mark T16449_2 as broken due to #16742

- - - - -


20 changed files:

- .gitlab-ci.yml
- libraries/base/tests/all.T
- libraries/ghc-heap/tests/all.T
- libraries/ghc-heap/tests/closure_size.hs
- libraries/process
- libraries/unix
- testsuite/driver/testlib.py
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/concurrent/should_run/all.T
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/ffi/should_compile/all.T
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/lib/integer/all.T
- testsuite/tests/programs/barton-mangler-bug/test.T
- testsuite/tests/rts/all.T
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_run/all.T
- testsuite/tests/utils/should_run/all.T
- testsuite/tests/warnings/should_compile/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -8,6 +8,9 @@ variables:
   # .gitlab/win32-init.sh.
   WINDOWS_TOOLCHAIN_VERSION: 1
 
+  # Disable shallow clones; they break our linting rules
+  GIT_DEPTH: 0
+
 before_script:
   - python3 .gitlab/fix-submodules.py
   - git submodule sync --recursive
@@ -52,13 +55,7 @@ ghc-linters:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
-    # Note [Unshallow clone for linting]
-    # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-    # GitLab creates a shallow clone which means that we may not have the base
-    # commit of the MR being tested (e.g. if the MR is quite old), causing `git
-    # merge-base` to fail.  Passing `--unshallow` to `git fetch` ensures that
-    # we have the entire history.
-    - git fetch --unshallow "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
+    - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
     - "echo Linting changes between $base..$CI_COMMIT_SHA"
     #    - validate-commit-msg .git $(git rev-list $base..$CI_COMMIT_SHA)
@@ -80,8 +77,7 @@ ghc-linters:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
-    # See Note [Unshallow clone for linting]
-    - git fetch --unshallow "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
+    - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
     - "echo Linting changes between $base..$CI_COMMIT_SHA"
     - submodchecker .git $(git rev-list $base..$CI_COMMIT_SHA)
@@ -464,6 +460,7 @@ validate-x86_64-linux-deb9-debug:
   stage: build
   variables:
     BUILD_FLAVOUR: validate
+    TEST_TYPE: slowtest
     TEST_ENV: "x86_64-linux-deb9-debug"
 
 validate-x86_64-linux-deb9-llvm:


=====================================
libraries/base/tests/all.T
=====================================
@@ -203,7 +203,7 @@ test('T8089',
      compile_and_run, [''])
 test('hWaitForInput-accurate-socket', reqlib('unix'), compile_and_run, [''])
 test('T8684', expect_broken(8684), compile_and_run, [''])
-test('hWaitForInput-accurate-stdin', normal, compile_and_run, [''])
+test('hWaitForInput-accurate-stdin', [expect_broken_for(16535, ['threaded1', 'threaded2']), omit_ways(['ghci'])], compile_and_run, [''])
 test('hWaitForInput-accurate-pipe', reqlib('unix'), compile_and_run, [''])
 test('T9826',normal, compile_and_run,[''])
 test('T9848',
@@ -234,6 +234,6 @@ test('T3474',
 test('T14425', normal, compile_and_run, [''])
 test('T10412', normal, compile_and_run, [''])
 test('T13896', normal, compile_and_run, [''])
-test('T13167', normal, compile_and_run, [''])
+test('T13167', fragile_for(16536, ['threaded2']), compile_and_run, [''])
 test('T15349', [exit_code(1), expect_broken_for(15349, 'ghci')], compile_and_run, [''])
 test('T16111', exit_code(1), compile_and_run, [''])


=====================================
libraries/ghc-heap/tests/all.T
=====================================
@@ -7,5 +7,5 @@ test('heap_all',
      ],
      compile_and_run, [''])
 test('closure_size',
-     omit_ways(['ghci', 'hpc', 'prof']),
+     [omit_ways(['ghci', 'hpc', 'prof']), expect_broken_for(16544, ['dyn', 'optasm', 'threaded2'])],
      compile_and_run, [''])


=====================================
libraries/ghc-heap/tests/closure_size.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash #-}
 
 import Control.Monad
 import Type.Reflection
@@ -17,12 +18,17 @@ assertSize !x expected = do
     putStrLn $ prettyCallStack callStack
 {-# NOINLINE assertSize #-}
 
-pap :: Int -> Char -> Int
+pap :: Int -> Maybe Char -> Int
 pap x _ = x
 {-# NOINLINE pap #-}
 
 main :: IO ()
 main = do
+  -- Ensure that GHC can't turn PAP into a FUN (see #16531)
+  let x :: Int
+      x = 42
+      {-# NOINLINE x #-}
+
   assertSize 'a' 2
   assertSize (Just ()) 2
   assertSize (Nothing :: Maybe ()) 2
@@ -30,5 +36,5 @@ main = do
   assertSize ((1,2,3) :: (Int,Int,Int)) 4
   assertSize (id :: Int -> Int) 1
   assertSize (fst :: (Int,Int) -> Int) 1
-  assertSize (pap 1) 2
+  assertSize (pap x) 2
 


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit d860209e53c1b40b7c251fc8378886bbcb394402
+Subproject commit 5c81524694ceaf8523a1846718a7a7c3f402124f


=====================================
libraries/unix
=====================================
@@ -1 +1 @@
-Subproject commit a102df29c107e8f853129dd40fbbb487e1818149
+Subproject commit a67b5e9e70a2a0c438d4f186fda9f38409ff1435


=====================================
testsuite/driver/testlib.py
=====================================
@@ -257,14 +257,14 @@ def fragile( bug ):
 
     return helper
 
-def fragile_for( name, opts, bug, ways ):
+def fragile_for( bug, ways ):
     """
     Indicates that the test should be skipped due to fragility in the given
     test ways as documented in the given ticket.
     """
     def helper( name, opts, bug=bug, ways=ways ):
         record_broken(name, opts, bug)
-        opts.omit_ways = ways
+        opts.omit_ways += ways
 
     return helper
 
@@ -274,7 +274,8 @@ def omit_ways( ways ):
     return lambda name, opts, w=ways: _omit_ways( name, opts, w )
 
 def _omit_ways( name, opts, ways ):
-    opts.omit_ways = ways
+    assert ways.__class__ is list
+    opts.omit_ways += ways
 
 # -----
 
@@ -1432,7 +1433,6 @@ def simple_run(name, way, prog, extra_run_opts):
         return failBecause('bad stderr')
     if not (opts.ignore_stdout or stdout_ok(name, way)):
         return failBecause('bad stdout')
-
     check_hp = '-h' in my_rts_flags and opts.check_hp
     check_prof = '-p' in my_rts_flags
 


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -195,4 +195,4 @@ test('T15892',
         extra_run_opts('+RTS -G1 -A32k -RTS') ],
      compile_and_run, ['-O'])
 test('T16617', normal, compile_and_run, [''])
-test('T16449_2', exit_code(1), compile_and_run, [''])
+test('T16449_2', [expect_broken_for(16742, ['dyn', 'ghci', 'optasm', 'threaded2']), exit_code(1)], compile_and_run, [''])


=====================================
testsuite/tests/concurrent/should_run/all.T
=====================================
@@ -88,7 +88,7 @@ test('T7970', normal, compile_and_run, [''])
 test('AtomicPrimops', normal, compile_and_run, [''])
 
 # test uses 2 threads and yield, scheduling can vary with threaded2
-test('threadstatus-9333', [omit_ways(['threaded2'])], compile_and_run, [''])
+test('threadstatus-9333', [fragile_for(16555, ['ghci']), omit_ways(['threaded2'])], compile_and_run, [''])
 
 test('T9379', normal, compile_and_run, [''])
 
@@ -239,7 +239,7 @@ test('conc067', ignore_stdout, compile_and_run, [''])
 
 # omit threaded2, the behaviour of this test is non-deterministic with more
 # than one CPU.
-test('conc068', [ omit_ways('threaded2'), exit_code(1) ], compile_and_run, [''])
+test('conc068', [ omit_ways(['threaded2']), exit_code(1) ], compile_and_run, [''])
 
 test('setnumcapabilities001',
      [ only_ways(['threaded1','threaded2']),


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -40,7 +40,7 @@ test('T12742', normal, compile, [''])
 #       (1) Use -fexternal-interpreter, or
 #       (2) Build the program twice: once with -dynamic, and then
 #           with -prof using -osuf to set a different object file suffix.
-test('T13910', omit_ways(['profasm']), compile, [''])
+test('T13910', [expect_broken_for(16537, ['optasm']), omit_ways(['profasm'])], compile, [''])
 test('T13938', [extra_files(['T13938a.hs'])], makefile_test, ['T13938'])
 test('T14556', normal, compile, [''])
 test('T14720', normal, compile, [''])


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -35,7 +35,8 @@ test('T11983', [omit_ways(['ghci'])], compile, ['T11983.c'])
 test('T14125', normal, compile, [''])
 test(
     'cc017',
-    normal,
+    # We need TH but can't load profiled dynamic objects
+    when(ghc_dynamic(), omit_ways(['profasm'])),
     compile,
     [
         '-optc=-DC -optcxx=-DCXX -optcxx=-std=c++11'


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -207,4 +207,4 @@ test('PrimFFIInt16', [omit_ways(['ghci'])], compile_and_run, ['PrimFFIInt16_c.c'
 
 test('PrimFFIWord16', [omit_ways(['ghci'])], compile_and_run, ['PrimFFIWord16_c.c'])
 
-test('T493', [], compile_and_run, ['T493_c.c'])
+test('T493', [omit_ways(['ghci'])], compile_and_run, ['T493_c.c'])


=====================================
testsuite/tests/lib/integer/all.T
=====================================
@@ -1,8 +1,8 @@
 test('integerBits', normal, compile_and_run, [''])
 test('integerConversions', normal, compile_and_run, [''])
 # skip ghci as it doesn't support unboxed tuples
-test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways('ghci')], compile_and_run, [''])
-test('plusMinusInteger', [omit_ways('ghci')], compile_and_run, [''])
+test('integerGmpInternals', [reqlib('integer-gmp'), omit_ways(['ghci'])], compile_and_run, [''])
+test('plusMinusInteger', [omit_ways(['ghci'])], compile_and_run, [''])
 test('integerConstantFolding', normal, makefile_test, ['integerConstantFolding'])
 test('fromToInteger', [], makefile_test, ['fromToInteger'])
 test('IntegerConversionRules', [], makefile_test, ['IntegerConversionRules'])


=====================================
testsuite/tests/programs/barton-mangler-bug/test.T
=====================================
@@ -8,7 +8,7 @@ test('barton-mangler-bug',
                    'Plot.hi',              'Plot.o',
                    'PlotExample.hi',       'PlotExample.o',
                    'TypesettingTricks.hi', 'TypesettingTricks.o']),
-      omit_ways('debug') # Fails for debug way due to annotation linting timeout
+      omit_ways(['debug']) # Fails for debug way due to annotation linting timeout
       ],
      multimod_compile_and_run, ['Main', ''])
 


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -73,7 +73,7 @@ test('T2047', [ignore_stdout, extra_run_opts('+RTS -c -RTS')],
 # Blackhole-detection test.
 # Skip GHCi due to #2786
 test('T2783', [ omit_ways(['ghci']), exit_code(1)
-              , expect_broken_for(2783, ['threaded1'])
+              , fragile_for(2783, ['threaded1'])
               ], compile_and_run, [''])
 
 # Test the work-stealing deque implementation.  We run this test in
@@ -93,7 +93,7 @@ test('stack002', [extra_files(['stack001.hs']),
 
 # run this test with very small stack chunks to exercise the stack
 # overflow/underflow machinery.
-test('stack003', [ omit_ways('ghci'), # uses unboxed tuples
+test('stack003', [ omit_ways(['ghci']), # uses unboxed tuples
                    extra_run_opts('500000 +RTS -kc1k -kb100 -K96m -RTS') ],
                  compile_and_run, [''])
 
@@ -214,7 +214,8 @@ test('T7815', [ multi_cpu_race,
 test('ffishutdown', [ignore_stderr, only_ways(['threaded1','threaded2'])],
      compile_and_run, [''])
 
-test('T7919', [when(fast(), skip), omit_ways(prof_ways)], compile_and_run,
+# Times out in ghci way
+test('T7919', [when(fast(), skip), omit_ways(['ghci'] + prof_ways)], compile_and_run,
      [config.ghc_th_way_flags])
 
 test('T8035', normal, compile_and_run, [''])


=====================================
testsuite/tests/th/all.T
=====================================
@@ -13,7 +13,7 @@ if config.have_ext_interp :
        setTestOpts(extra_ways(['ext-interp']))
        setTestOpts(only_ways(['normal','ghci','ext-interp']))
 
-broken_tests = ["ClosedFam1TH","T10620","T10828","T11721_TH","T11797","T12045TH2","T12478_1","T12646","T13642","T14060","T15502","T15738","T15792","T15845","T1835","T3920","T4135","T4188","T5037","T5362","T7477","T7910","T8761","T8884","T8953","T9262","T9692","T9738","TH_Lift","TH_RichKinds","TH_RichKinds2","TH_Roles3","TH_TyInstWhere2","TH_implicitParams","TH_recursiveDo","TH_reifyDecl1","TH_reifyExplicitForAllFams","TH_reifyInstances","TH_reifyMkName","TH_repE2","TH_repGuard","TH_repPrim","TH_repPrim2","TH_repUnboxedTuples","TH_spliceE6","T16326_TH"]
+broken_tests = ["ClosedFam1TH","T10620","T10828","T11721_TH","T11797","T12045TH2","T12478_1","T12646","T13642","T14060","T15502","T15738","T15792","T15845","T16180","T1835","T3920","T4135","T4188","T5037","T5362","T7477","T7910","T8761","T8884","T8953","T9262","T9692","T9738","TH_Lift","TH_RichKinds","TH_RichKinds2","TH_Roles3","TH_TyInstWhere2","TH_implicitParams","TH_recursiveDo","TH_reifyDecl1","TH_reifyExplicitForAllFams","TH_reifyInstances","TH_reifyMkName","TH_repE2","TH_repGuard","TH_repPrim","TH_repPrim2","TH_repUnboxedTuples","TH_spliceE6","T16326_TH"]
 # ext-interp, integer-gmp and llvm is broken see #16087
 def broken_ext_interp(name, opts):
 	if name in broken_tests and config.ghc_built_by_llvm:
@@ -467,7 +467,10 @@ test('T15437', expect_broken(15437), multimod_compile,
 test('T15985', normal, compile, [''])
 test('T16133', normal, compile_fail, [''])
 test('T15471', normal, multimod_compile, ['T15471.hs', '-v0'])
-test('T16180', normal, compile_and_run, [''])
+test('T16180',
+     [when(llvm_build(), expect_broken_for(16541, ['ext-interp'])),
+      expect_broken_for(16541, ['ghci'])],
+     compile_and_run, ['-package ghc'])
 test('T16183', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T16195', normal, multimod_compile, ['T16195.hs', '-v0'])
 test('T16293b', normal, compile, [''])


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -659,7 +659,7 @@ test('T15586', normal, compile, [''])
 test('T15368', normal, compile, ['-fdefer-type-errors'])
 test('T15645', normal, compile, ['-Wwarn=missing-monadfail-instances'])
 test('T15778', normal, compile, [''])
-test('T14761c', normal, compile, [''])
+test('T14761c', expect_broken_for(16540, ['hpc', 'optasm']), compile, [''])
 test('T16008', normal, compile, [''])
 test('T16033', normal, compile, [''])
 test('T16141', normal, compile, ['-O'])


=====================================
testsuite/tests/typecheck/should_run/all.T
=====================================
@@ -35,7 +35,7 @@ test('tcrun018', normal, compile_and_run, [''])
 test('tcrun019', normal, compile_and_run, [''])
 test('tcrun020', normal, compile_and_run, [''])
 test('tcrun021', normal, compile_and_run, ['-package containers'])
-test('tcrun022', omit_ways(['ghci']), compile_and_run, ['-O'])
+test('tcrun022', omit_ways(['hpc', 'ghci']), compile_and_run, ['-O'])
 test('tcrun023', [when(doing_ghci(), extra_hc_opts('-fobject-code'))],
      compile_and_run, ['-O'])
 test('tcrun024', normal, compile_and_run, ['-O'])
@@ -96,7 +96,7 @@ test('T6117', normal, compile_and_run, [''])
 test('T5751', normal, compile_and_run, [''])
 test('T5913', normal, compile_and_run, [''])
 test('T7748', normal, compile_and_run, [''])
-test('T7861', [omit_ways('debug'), exit_code(1)], compile_and_run, [''])
+test('T7861', [omit_ways(['debug']), exit_code(1)], compile_and_run, [''])
 test('TcTypeNatSimpleRun', normal, compile_and_run, [''])
 test('TcTypeSymbolSimpleRun', normal, compile_and_run, [''])
 test('T8119', normal, ghci_script, ['T8119.script'])


=====================================
testsuite/tests/utils/should_run/all.T
=====================================
@@ -1,6 +1,6 @@
 test('T14854',
      [only_ways(threaded_ways),
-      omit_ways('ghci'),
+      omit_ways(['ghci']),
       reqlib('random'),
       ignore_stderr],
      compile_and_run,


=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -26,4 +26,4 @@ test('T16551', [extra_files(['T16551/'])], multimod_compile, ['T16551/A.hs T1655
 
 test('StarBinder', normal, compile, [''])
 
-test('Overflow', normal, compile, [''])
+test('Overflow', expect_broken_for(16543, ['hpc']), compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/dd9b918c5098b6d886213bf3f98424dc1c6d1016...3d0857da0d6114f881b8f9ca8eefc153bf523556

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/dd9b918c5098b6d886213bf3f98424dc1c6d1016...3d0857da0d6114f881b8f9ca8eefc153bf523556
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/20190608/c3d4aac4/attachment-0001.html>


More information about the ghc-commits mailing list