[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: testsuite: Unmark T12971 as broken on Windows

Marge Bot gitlab at gitlab.haskell.org
Mon Sep 21 14:35:51 UTC 2020



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


Commits:
66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T12971 as broken on Windows

It's unclear why, but this no longer seems to fail.

Closes #17945.

- - - - -
816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Unmark T5975[ab] as broken on Windows

Sadly it's unclear *why* they have suddenly started working.

Closes #7305.

- - - - -
43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00
base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001

Only affected the Windows codepath.

- - - - -
ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Update expected output for outofmem on Windows

The error originates from osCommitMemory rather than getMBlocks.

- - - - -
ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00
testsuite: Mark some GHCi/Makefile tests as broken on Windows

See #18718.

- - - - -
caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Fix WinIO error message normalization

This wasn't being applied to stderr.

- - - - -
93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark tempfiles as broken on Win32 without WinIO

The old POSIX emulation appears to ignore the user-requested prefix.

- - - - -
9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00
testsuite: Mark TH_spliceE5_prof as broken on Windows

Due to #18721.

- - - - -
f727ef24 by Ryan Scott at 2020-09-21T10:35:39-04:00
Remove unused ThBrackCtxt and ResSigCtxt

Fixes #18715.

- - - - -
8a9e908e by Ryan Scott at 2020-09-21T10:35:39-04:00
Disallow constraints in KindSigCtxt

This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s
that can only refer to kind-level positions, which is important for
rejecting certain classes of programs. In particular, this patch:

* Introduces a new `TypeOrKindCtxt` data type and
  `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which
  determines whether a `UserTypeCtxt` can refer to type-level
  contexts, kind-level contexts, or both.
* Defines the existing `allConstraintsAllowed` and `vdqAllowed`
  functions in terms of `typeOrKindCtxt`, which avoids code
  duplication and ensures that they stay in sync in the future.

The net effect of this patch is that it fixes #18714, in which it was
discovered that `allConstraintsAllowed` incorrectly returned `True`
for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies
`KindSigCtxt` as a kind-level context, this bug no longer occurs.

- - - - -
629a10f1 by Ben Gamari at 2020-09-21T10:35:39-04:00
hadrian: Add extra-deps: happy-1.20 to stack.yaml

GHC now requires happy-1.20, which isn't available in LTS-16.14.

Fixes #18726.
- - - - -


18 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Validity.hs
- hadrian/stack.yaml
- libraries/base/tests/Concurrent/ThreadDelay001.hs
- libraries/base/tests/all.T
- testsuite/driver/testlib.py
- testsuite/tests/driver/all.T
- testsuite/tests/ghci/linking/dyn/all.T
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/rts/T12771/all.T
- testsuite/tests/rts/T13082/all.T
- testsuite/tests/rts/T14611/all.T
- testsuite/tests/rts/outofmem.stderr-x86_64-unknown-mingw32
- testsuite/tests/th/all.T
- + testsuite/tests/typecheck/should_fail/T18714.hs
- + testsuite/tests/typecheck/should_fail/T18714.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -2838,7 +2838,6 @@ expectedKindInCtxt :: UserTypeCtxt -> ContextKind
 -- Depending on the context, we might accept any kind (for instance, in a TH
 -- splice), or only certain kinds (like in type signatures).
 expectedKindInCtxt (TySynCtxt _)   = AnyKind
-expectedKindInCtxt ThBrackCtxt     = AnyKind
 expectedKindInCtxt (GhciCtxt {})   = AnyKind
 -- The types in a 'default' decl can have varying kinds
 -- See Note [Extended defaults]" in GHC.Tc.Utils.Env


=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -84,15 +84,12 @@ data UserTypeCtxt
                         --   or  (x::t, y) = e
   | RuleSigCtxt Name    -- LHS of a RULE forall
                         --    RULE "foo" forall (x :: a -> a). f (Just x) = ...
-  | ResSigCtxt          -- Result type sig
-                        --      f x :: t = ....
   | ForSigCtxt Name     -- Foreign import or export signature
   | DefaultDeclCtxt     -- Types in a default declaration
   | InstDeclCtxt Bool   -- An instance declaration
                         --    True:  stand-alone deriving
                         --    False: vanilla instance declaration
   | SpecInstCtxt        -- SPECIALISE instance pragma
-  | ThBrackCtxt         -- Template Haskell type brackets [t| ... |]
   | GenSigCtxt          -- Higher-rank or impredicative situations
                         -- e.g. (f e) where f has a higher-rank type
                         -- We might want to elaborate this
@@ -136,9 +133,7 @@ pprUserTypeCtxt (StandaloneKindSigCtxt n) = text "a standalone kind signature fo
 pprUserTypeCtxt TypeAppCtxt       = text "a type argument"
 pprUserTypeCtxt (ConArgCtxt c)    = text "the type of the constructor" <+> quotes (ppr c)
 pprUserTypeCtxt (TySynCtxt c)     = text "the RHS of the type synonym" <+> quotes (ppr c)
-pprUserTypeCtxt ThBrackCtxt       = text "a Template Haskell quotation [t|...|]"
 pprUserTypeCtxt PatSigCtxt        = text "a pattern type signature"
-pprUserTypeCtxt ResSigCtxt        = text "a result type signature"
 pprUserTypeCtxt (ForSigCtxt n)    = text "the foreign declaration for" <+> quotes (ppr n)
 pprUserTypeCtxt DefaultDeclCtxt   = text "a type in a `default' declaration"
 pprUserTypeCtxt (InstDeclCtxt False) = text "an instance declaration"


=====================================
compiler/GHC/Tc/Validity.hs
=====================================
@@ -348,7 +348,6 @@ checkValidType ctxt ty
              rank
                = case ctxt of
                  DefaultDeclCtxt-> MustBeMonoType
-                 ResSigCtxt     -> MustBeMonoType
                  PatSigCtxt     -> rank0
                  RuleSigCtxt _  -> rank1
                  TySynCtxt _    -> rank0
@@ -372,7 +371,6 @@ checkValidType ctxt ty
 
                  ForSigCtxt _   -> rank1
                  SpecInstCtxt   -> rank1
-                 ThBrackCtxt    -> rank1
                  GhciCtxt {}    -> ArbitraryRank
 
                  TyVarBndrKindCtxt _ -> rank0
@@ -472,18 +470,81 @@ forAllAllowed ArbitraryRank             = True
 forAllAllowed (LimitedRank forall_ok _) = forall_ok
 forAllAllowed _                         = False
 
+-- | Indicates whether a 'UserTypeCtxt' represents type-level contexts,
+-- kind-level contexts, or both.
+data TypeOrKindCtxt
+  = OnlyTypeCtxt
+    -- ^ A 'UserTypeCtxt' that only represents type-level positions.
+  | OnlyKindCtxt
+    -- ^ A 'UserTypeCtxt' that only represents kind-level positions.
+  | BothTypeAndKindCtxt
+    -- ^ A 'UserTypeCtxt' that can represent both type- and kind-level positions.
+  deriving Eq
+
+instance Outputable TypeOrKindCtxt where
+  ppr ctxt = text $ case ctxt of
+    OnlyTypeCtxt        -> "OnlyTypeCtxt"
+    OnlyKindCtxt        -> "OnlyKindCtxt"
+    BothTypeAndKindCtxt -> "BothTypeAndKindCtxt"
+
+-- | Determine whether a 'UserTypeCtxt' can represent type-level contexts,
+-- kind-level contexts, or both.
+typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt
+typeOrKindCtxt (FunSigCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (InfSigCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (ExprSigCtxt {})     = OnlyTypeCtxt
+typeOrKindCtxt (TypeAppCtxt {})     = OnlyTypeCtxt
+typeOrKindCtxt (PatSynCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (PatSigCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (RuleSigCtxt {})     = OnlyTypeCtxt
+typeOrKindCtxt (ForSigCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (DefaultDeclCtxt {}) = OnlyTypeCtxt
+typeOrKindCtxt (InstDeclCtxt {})    = OnlyTypeCtxt
+typeOrKindCtxt (SpecInstCtxt {})    = OnlyTypeCtxt
+typeOrKindCtxt (GenSigCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (ClassSCCtxt {})     = OnlyTypeCtxt
+typeOrKindCtxt (SigmaCtxt {})       = OnlyTypeCtxt
+typeOrKindCtxt (DataTyCtxt {})      = OnlyTypeCtxt
+typeOrKindCtxt (DerivClauseCtxt {}) = OnlyTypeCtxt
+typeOrKindCtxt (ConArgCtxt {})      = OnlyTypeCtxt
+  -- Although data constructors can be promoted with DataKinds, we always
+  -- validity-check them as though they are the types of terms. We may need
+  -- to revisit this decision if we ever allow visible dependent quantification
+  -- in the types of data constructors.
+
+typeOrKindCtxt (KindSigCtxt {})           = OnlyKindCtxt
+typeOrKindCtxt (StandaloneKindSigCtxt {}) = OnlyKindCtxt
+typeOrKindCtxt (TyVarBndrKindCtxt {})     = OnlyKindCtxt
+typeOrKindCtxt (DataKindCtxt {})          = OnlyKindCtxt
+typeOrKindCtxt (TySynKindCtxt {})         = OnlyKindCtxt
+typeOrKindCtxt (TyFamResKindCtxt {})      = OnlyKindCtxt
+
+typeOrKindCtxt (TySynCtxt {}) = BothTypeAndKindCtxt
+  -- Type synonyms can have types and kinds on their RHSs
+typeOrKindCtxt (GhciCtxt {})  = BothTypeAndKindCtxt
+  -- GHCi's :kind command accepts both types and kinds
+
+-- | Returns 'True' if the supplied 'UserTypeCtxt' is unambiguously not the
+-- context for a kind of a type, where the arbitrary use of constraints is
+-- currently disallowed.
+-- (See @Note [Constraints in kinds]@ in "GHC.Core.TyCo.Rep".)
+-- If the 'UserTypeCtxt' can refer to both types and kinds, this function
+-- conservatively returns 'True'.
+--
+-- An example of something that is unambiguously the kind of a type is the
+-- @Show a => a -> a@ in @type Foo :: Show a => a -> a at . On the other hand, the
+-- same type in @foo :: Show a => a -> a@ is unambiguously the type of a term,
+-- not the kind of a type, so it is permitted.
 allConstraintsAllowed :: UserTypeCtxt -> Bool
--- We don't allow arbitrary constraints in kinds
-allConstraintsAllowed (TyVarBndrKindCtxt {}) = False
-allConstraintsAllowed (DataKindCtxt {})      = False
-allConstraintsAllowed (TySynKindCtxt {})     = False
-allConstraintsAllowed (TyFamResKindCtxt {})  = False
-allConstraintsAllowed (StandaloneKindSigCtxt {}) = False
-allConstraintsAllowed _ = True
+allConstraintsAllowed ctxt = case typeOrKindCtxt ctxt of
+  OnlyTypeCtxt        -> True
+  OnlyKindCtxt        -> False
+  BothTypeAndKindCtxt -> True
 
 -- | Returns 'True' if the supplied 'UserTypeCtxt' is unambiguously not the
 -- context for the type of a term, where visible, dependent quantification is
--- currently disallowed.
+-- currently disallowed. If the 'UserTypeCtxt' can refer to both types and
+-- kinds, this function conservatively returns 'True'.
 --
 -- An example of something that is unambiguously the type of a term is the
 -- @forall a -> a -> a@ in @foo :: forall a -> a -> a at . On the other hand, the
@@ -496,40 +557,10 @@ allConstraintsAllowed _ = True
 -- @testsuite/tests/dependent/should_fail/T16326_Fail*.hs@ (for places where
 -- VDQ is disallowed).
 vdqAllowed :: UserTypeCtxt -> Bool
--- Currently allowed in the kinds of types...
-vdqAllowed (KindSigCtxt {}) = True
-vdqAllowed (StandaloneKindSigCtxt {}) = True
-vdqAllowed (TySynCtxt {}) = True
-vdqAllowed (ThBrackCtxt {}) = True
-vdqAllowed (GhciCtxt {}) = True
-vdqAllowed (TyVarBndrKindCtxt {}) = True
-vdqAllowed (DataKindCtxt {}) = True
-vdqAllowed (TySynKindCtxt {}) = True
-vdqAllowed (TyFamResKindCtxt {}) = True
--- ...but not in the types of terms.
-vdqAllowed (ConArgCtxt {}) = False
-  -- We could envision allowing VDQ in data constructor types so long as the
-  -- constructor is only ever used at the type level, but for now, GHC adopts
-  -- the stance that VDQ is never allowed in data constructor types.
-vdqAllowed (FunSigCtxt {}) = False
-vdqAllowed (InfSigCtxt {}) = False
-vdqAllowed (ExprSigCtxt {}) = False
-vdqAllowed (TypeAppCtxt {}) = False
-vdqAllowed (PatSynCtxt {}) = False
-vdqAllowed (PatSigCtxt {}) = False
-vdqAllowed (RuleSigCtxt {}) = False
-vdqAllowed (ResSigCtxt {}) = False
-vdqAllowed (ForSigCtxt {}) = False
-vdqAllowed (DefaultDeclCtxt {}) = False
--- We count class constraints as "types of terms". All of the cases below deal
--- with class constraints.
-vdqAllowed (InstDeclCtxt {}) = False
-vdqAllowed (SpecInstCtxt {}) = False
-vdqAllowed (GenSigCtxt {}) = False
-vdqAllowed (ClassSCCtxt {}) = False
-vdqAllowed (SigmaCtxt {}) = False
-vdqAllowed (DataTyCtxt {}) = False
-vdqAllowed (DerivClauseCtxt {}) = False
+vdqAllowed ctxt = case typeOrKindCtxt ctxt of
+  OnlyTypeCtxt        -> False
+  OnlyKindCtxt        -> True
+  BothTypeAndKindCtxt -> True
 
 {-
 Note [Correctness and performance of type synonym validity checking]
@@ -1329,11 +1360,9 @@ okIPCtxt (InfSigCtxt {})        = True
 okIPCtxt ExprSigCtxt            = True
 okIPCtxt TypeAppCtxt            = True
 okIPCtxt PatSigCtxt             = True
-okIPCtxt ResSigCtxt             = True
 okIPCtxt GenSigCtxt             = True
 okIPCtxt (ConArgCtxt {})        = True
 okIPCtxt (ForSigCtxt {})        = True  -- ??
-okIPCtxt ThBrackCtxt            = True
 okIPCtxt (GhciCtxt {})          = True
 okIPCtxt SigmaCtxt              = True
 okIPCtxt (DataTyCtxt {})        = True


=====================================
hadrian/stack.yaml
=====================================
@@ -12,3 +12,6 @@ nix:
    - git
    - ncurses
    - perl
+
+extra-deps:
+- happy-1.20.0


=====================================
libraries/base/tests/Concurrent/ThreadDelay001.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
 
 -- Test that threadDelay actually sleeps for (at least) as long as we
 -- ask it


=====================================
libraries/base/tests/all.T
=====================================
@@ -17,7 +17,10 @@ test('readFloat', exit_code(1), compile_and_run, [''])
 test('enumDouble', normal, compile_and_run, [''])
 test('enumRatio', normal, compile_and_run, [''])
 test('enumNumeric', normal, compile_and_run, [''])
-test('tempfiles', normal, compile_and_run, [''])
+# N.B. the tempfile format is slightly different than this test expects on
+# Windows *except* if using WinIO. The `when` clause below can be removed
+# after WinIO becomes the default.
+test('tempfiles', when(opsys('mingw32'), only_ways(['winio'])), compile_and_run, [''])
 test('fixed', normal, compile_and_run, [''])
 test('quotOverflow', normal, compile_and_run, [''])
 test('assert', exit_code(1), compile_and_run, ['-fno-ignore-asserts'])


=====================================
testsuite/driver/testlib.py
=====================================
@@ -751,22 +751,24 @@ def normalise_win32_io_errors(name, opts):
     slightly in the error messages that they provide. Normalise these
     differences away, preferring the new WinIO errors.
 
-    This can be dropped when the old IO manager is removed.
+    This normalization can be dropped when the old IO manager is removed.
     """
 
     SUBS = [
-        ('Bad file descriptor', 'The handle is invalid'),
+        ('Bad file descriptor', 'The handle is invalid.'),
         ('Permission denied', 'Access is denied.'),
         ('No such file or directory', 'The system cannot find the file specified.'),
     ]
 
-    def f(s: str):
+    def normalizer(s: str) -> str:
         for old,new in SUBS:
             s = s.replace(old, new)
 
         return s
 
-    return when(opsys('mingw32'), normalise_fun(f))
+    if opsys('mingw32'):
+        _normalise_fun(name, opts, normalizer)
+        _normalise_errmsg_fun(name, opts, normalizer)
 
 def normalise_version_( *pkgs ):
     def normalise_version__( str ):


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -258,7 +258,7 @@ test('T12752pass', normal, compile, ['-DSHOULD_PASS=1 -Wcpp-undef'])
 
 test('T12955', normal, makefile_test, [])
 
-test('T12971', [when(opsys('mingw32'), expect_broken(17945)), ignore_stdout], makefile_test, [])
+test('T12971', ignore_stdout, makefile_test, [])
 test('json', normal, compile_fail, ['-ddump-json'])
 test('json2', normalise_version('base','ghc-prim'), compile, ['-ddump-types -ddump-json'])
 test('T16167', exit_code(1), run_command, 


=====================================
testsuite/tests/ghci/linking/dyn/all.T
=====================================
@@ -30,10 +30,12 @@ test('T10458',
      ghci_script, ['T10458.script'])
 
 test('T11072gcc', [extra_files(['A.c', 'T11072.hs']),
+                   expect_broken(18718),
                    unless(doing_ghci, skip), unless(opsys('mingw32'), skip)],
      makefile_test, ['compile_libAS_impl_gcc'])
 
 test('T11072msvc', [extra_files(['A.c', 'T11072.hs', 'libAS.def', 'i686/', 'x86_64/']),
+                    expect_broken(18718),
                     unless(doing_ghci, skip), unless(opsys('mingw32'), skip)],
      makefile_test, ['compile_libAS_impl_msvc'])
 


=====================================
testsuite/tests/ghci/scripts/all.T
=====================================
@@ -142,10 +142,10 @@ test('T5979',
      normalise_version("transformers")],
     ghci_script, ['T5979.script'])
 test('T5975a',
-     [pre_cmd('touch föøbàr1.hs'), when(opsys('mingw32'), expect_broken(7305))],
+     pre_cmd('touch föøbàr1.hs'),
      ghci_script, ['T5975a.script'])
 test('T5975b',
-     [pre_cmd('touch föøbàr2.hs'), extra_hc_opts('föøbàr2.hs'), when(opsys('mingw32'), expect_broken(7305))],
+     [pre_cmd('touch föøbàr2.hs'), extra_hc_opts('föøbàr2.hs')],
      ghci_script, ['T5975b.script'])
 test('T6027ghci', normal, ghci_script, ['T6027ghci.script'])
 


=====================================
testsuite/tests/rts/T12771/all.T
=====================================
@@ -1,4 +1,5 @@
 test('T12771',
      [extra_files(['foo.c', 'main.hs', 'foo_dll.c']),
+      expect_broken(18718),
       unless(opsys('mingw32'), skip)],
      makefile_test, ['T12771'])


=====================================
testsuite/tests/rts/T13082/all.T
=====================================
@@ -16,6 +16,7 @@ def normalise_search_dirs (str):
 #--------------------------------------
 test('T13082_good',
      [extra_files(['foo.c', 'main.hs', 'foo_dll.c']),
+      expect_broken(18718),
       unless(opsys('mingw32'), skip)],
      makefile_test, ['T13082_good'])
 


=====================================
testsuite/tests/rts/T14611/all.T
=====================================
@@ -1,4 +1,5 @@
 test('T14611',
      [extra_files(['foo.c', 'main.hs', 'foo_dll.c']),
+      expect_broken(18718),
       unless(opsys('mingw32'), skip)],
      makefile_test, ['T14611'])


=====================================
testsuite/tests/rts/outofmem.stderr-x86_64-unknown-mingw32
=====================================
@@ -1 +1 @@
-outofmem.exe: getMBlocks: VirtualAlloc MEM_COMMIT failed: The paging file is too small for this operation to complete.
+outofmem.exe: osCommitMemory: VirtualAlloc MEM_COMMIT failed: The paging file is too small for this operation to complete.


=====================================
testsuite/tests/th/all.T
=====================================
@@ -51,7 +51,8 @@ test('TH_NestedSplices', [], multimod_compile,
 # normal way first, which is why the work is done by a Makefile rule.
 test('TH_spliceE5_prof',
      [req_profiling, only_ways(['normal']),
-      when(ghc_dynamic(), expect_broken(11495))],
+      when(ghc_dynamic(), expect_broken(11495)),
+      when(opsys('mingw32'), expect_broken(18271))],
      makefile_test, ['TH_spliceE5_prof'])
 
 test('TH_spliceE5_prof_ext', [req_profiling, only_ways(['normal'])],


=====================================
testsuite/tests/typecheck/should_fail/T18714.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+module T18714 where
+
+import GHC.Exts
+
+type Id a = a
+
+type F = Id (Any :: forall a. Show a => a -> a)


=====================================
testsuite/tests/typecheck/should_fail/T18714.stderr
=====================================
@@ -0,0 +1,7 @@
+
+T18714.hs:11:14: error:
+    • Illegal constraint in a kind: forall a. Show a => a -> a
+    • In the first argument of ‘Id’, namely
+        ‘(Any :: forall a. Show a => a -> a)’
+      In the type ‘Id (Any :: forall a. Show a => a -> a)’
+      In the type declaration for ‘F’


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -579,3 +579,4 @@ test('T18357a', normal, compile_fail, [''])
 test('T18357b', normal, compile_fail, [''])
 test('T18455', normal, compile_fail, [''])
 test('T18534', normal, compile_fail, [''])
+test('T18714', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5aea7e6ce54caa7687af88c5dabb5caf16da874...629a10f189a5ebf06cc5d34a872f22830cb2593e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5aea7e6ce54caa7687af88c5dabb5caf16da874...629a10f189a5ebf06cc5d34a872f22830cb2593e
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/20200921/40a9118e/attachment-0001.html>


More information about the ghc-commits mailing list