[Git][ghc/ghc][wip/fix-windows] 15 commits: gitlab-ci: Linters, don't allow to fail

Ben Gamari gitlab at gitlab.haskell.org
Sun Jun 9 14:49:44 UTC 2019



Ben Gamari pushed to branch wip/fix-windows at Glasgow Haskell Compiler / GHC


Commits:
07dc79c3 by Matthew Pickering at 2019-06-08T17:34:18Z
gitlab-ci: Linters, don't allow to fail

Ben disabled them in cd85f8a71bb56cff332560e1d571b3406789fb71 but didn't
say how or why they were broken.

- - - - -
fd840b64 by Matthew Pickering at 2019-06-08T17:34:18Z
gitlab-ci: Don't run two submodule checking jobs on Marge jobs

- - - - -
310d0c4c by Matthew Pickering at 2019-06-08T17:34:18Z
Fix two lint failures in rts/linker/MachO.c

- - - - -
fe965316 by Ben Gamari at 2019-06-08T17:34:18Z
gitlab-ci: Use --unshallow when fetching for linters

GitLab creates a shallow clone. However, this means that we may not have
the base commit of an MR when linting, causing `git merge-base` to fail.
Fix this by passing `--unshallow` to `git fetch`, ensuring that we have
the entire history.

- - - - -
f58234ea by Ben Gamari at 2019-06-08T17:34:18Z
gitlab-ci: Fix submodule linter

The job script didn't even try to compute the base commit to lint with
respect to.

- - - - -
c392f987 by Ben Gamari at 2019-06-08T17:34:18Z
gitlab-ci: A few clarifying comments

- - - - -
709290b0 by Matthew Pickering at 2019-06-08T17:38:15Z
Remove trailing whitespace

[skip ci]

This should really be caught by the linters! (#16711)

- - - - -
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.

- - - - -
4a72259d by Ben Gamari at 2019-06-08T18:40:55Z
gitlab-ci: Fix submodule linting of commits

There is no notion of a base commit when we aren't checking a merge
request. Just check the HEAD commit.

- - - - -
87540029 by Ben Gamari at 2019-06-08T20:44:55Z
gitlab-ci: Ensure that all commits on a branch are submodule-linted

The previous commit reworked things such that the submodule linter would
only run on the head commit. However, the linter only checks the
submodules which are touched by the commits it is asked to lint.
Consequently it would be possible for a bad submodule to sneak through.

Thankfully, we can use the handy CI_COMMIT_BEFORE_SHA attribute to
find the base commit of the push.

- - - - -
d882c74f by Ben Gamari at 2019-06-09T14:49:14Z
testsuite: Skip dynamicToo006 when dynamic linking is not available

This was previously failling on Windows.

- - - - -
1eb57514 by Ben Gamari at 2019-06-09T14:49:33Z
testsuite: Mark T3372 as fragile on Windows

On Windows we must lock package databases even when opening for
read-only access. This means that concurrent GHC sessions are very
likely to fail with file lock contention.

See #16773.

- - - - -
2a8c28c9 by Ben Gamari at 2019-06-09T14:49:36Z
testsuite: Add stderr output for UnsafeInfered02 on Windows

This test uses TemplateHaskell causing GHC to build dynamic objects on
platforms where dynamic linking is available. However, Windows doesn't support
dynamic linking. Consequently the test would fail on Windows with:

```patch
--- safeHaskell/safeInfered/UnsafeInfered02.run/UnsafeInfered02.stderr.normalised	2019-06-04 15:10:10.521594200 +0000
+++ safeHaskell/safeInfered/UnsafeInfered02.run/UnsafeInfered02.comp.stderr.normalised	2019-06-04 15:10:10.523546200 +0000
@@ -1,5 +1,5 @@
-[1 of 2] Compiling UnsafeInfered02_A ( UnsafeInfered02_A.hs, UnsafeInfered02_A.o, UnsafeInfered02_A.dyn_o )
-[2 of 2] Compiling UnsafeInfered02  ( UnsafeInfered02.hs, UnsafeInfered02.o, UnsafeInfered02.dyn_o )
+[1 of 2] Compiling UnsafeInfered02_A ( UnsafeInfered02_A.hs, UnsafeInfered02_A.o )
+[2 of 2] Compiling UnsafeInfered02  ( UnsafeInfered02.hs, UnsafeInfered02.o )

 UnsafeInfered02.hs:4:1:
     UnsafeInfered02_A: Can't be safely imported!
```

The other approach I considered for this issue is to pass `-v0` to GHC.
However, I felt we should probably do this consistently for all of the tests in
this directory and this would take more time than I currently have.

- - - - -
fa6a0a05 by Ben Gamari at 2019-06-09T14:49:36Z
gitlab-ci: Don't allow Windows make job to fail

While linking is still slow (#16084) all of the correctness issues which were
preventing us from being able to enforce testsuite-green on Windows are now
resolved.

- - - - -
51226024 by Ben Gamari at 2019-06-09T14:49:36Z
testsuite: Mark OldModLocation as broken on Windows

Strangely the path it emits contains duplicate path delimiters (#16772),
```patch
--- ghc-api/downsweep/OldModLocation.run/OldModLocation.stderr.normalised	2019-06-04 14:40:26.326075000 +0000
+++ ghc-api/downsweep/OldModLocation.run/OldModLocation.run.stderr.normalised	2019-06-04 14:40:26.328029200 +0000
@@ -1 +1 @@
-[Just "A.hs",Just "mydir/B.hs"]
+[Just "A.hs",Just "mydir//B.hs"]
```

- - - - -


14 changed files:

- .gitlab-ci.yml
- compiler/cmm/MkGraph.hs
- compiler/codeGen/StgCmmForeign.hs
- compiler/ghci/LinkerTypes.hs
- compiler/main/HscTypes.hs
- compiler/main/Packages.hs
- compiler/specialise/Specialise.hs
- compiler/stgSyn/StgSyn.hs
- libraries/ghc-boot/GHC/PackageDb.hs
- rts/linker/MachO.c
- testsuite/tests/driver/dynamicToo/dynamicToo006/all.T
- testsuite/tests/ghc-api/downsweep/all.T
- testsuite/tests/ghci/linking/dyn/all.T
- + testsuite/tests/safeHaskell/safeInfered/UnsafeInfered02.stderr-mingw32


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
@@ -49,13 +52,12 @@ stages:
 ############################################################
 
 ghc-linters:
-  allow_failure: true
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
     - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
     - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
-    - "echo Merge base $base"
+    - "echo Linting changes between $base..$CI_COMMIT_SHA"
     #    - validate-commit-msg .git $(git rev-list $base..$CI_COMMIT_SHA)
     - validate-whitespace .git $(git rev-list $base..$CI_COMMIT_SHA)
     - .gitlab/linters/check-makefiles.py $base $CI_COMMIT_SHA
@@ -75,18 +77,14 @@ ghc-linters:
   stage: lint
   image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV"
   script:
+    - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME
+    - base="$(git merge-base FETCH_HEAD $CI_COMMIT_SHA)"
+    - "echo Linting submodule changes between $base..$CI_COMMIT_SHA"
     - submodchecker .git $(git rev-list $base..$CI_COMMIT_SHA)
   dependencies: []
   tags:
     - lint
 
-lint-submods:
-  extends: .lint-submods
-  only:
-    refs:
-      - master
-      - /ghc-[0-9]+\.[0-9]+/
-
 lint-submods-marge:
   extends: .lint-submods
   only:
@@ -97,10 +95,25 @@ lint-submods-marge:
 
 lint-submods-mr:
   extends: .lint-submods
+  # Allow failure since any necessary submodule patches may not be upstreamed
+  # yet.
   allow_failure: true
   only:
     refs:
       - merge_requests
+  except:
+    variables:
+      - $CI_MERGE_REQUEST_LABELS =~ /.*wip/marge_bot_batch_merge_job.*/
+
+lint-submods-branch:
+  extends: .lint-submods
+  script:
+    - "echo Linting submodule changes between $CI_COMMIT_BEFORE_SHA..$CI_COMMIT_SHA"
+    - submodchecker .git $(git rev-list $CI_COMMIT_BEFORE_SHA..$CI_COMMIT_SHA)
+  only:
+    refs:
+      - master
+      - /ghc-[0-9]+\.[0-9]+/
 
 .lint-changelogs:
   stage: lint
@@ -117,6 +130,7 @@ lint-submods-mr:
 
 lint-changelogs:
   extends: .lint-changelogs
+  # Allow failure since this isn't a final release.
   allow_failure: true
   only:
     refs:
@@ -640,8 +654,6 @@ nightly-i386-windows-hadrian:
 .build-windows-make:
   extends: .build-windows
   stage: full-build
-  # due to #16084
-  allow_failure: true
   variables:
     BUILD_FLAVOUR: "quick"
     GHC_VERSION: "8.6.5"


=====================================
compiler/cmm/MkGraph.hs
=====================================
@@ -335,8 +335,8 @@ copyIn dflags conv area formals extra_stk
           local = CmmLocal reg
           width = cmmRegWidth dflags local
           expr  = CmmMachOp (MO_XX_Conv (wordWidth dflags) width) [stack_slot]
-        in CmmAssign local expr 
-         
+        in CmmAssign local expr
+
       | otherwise =
          CmmAssign (CmmLocal reg) (CmmLoad (CmmStackSlot area off) ty)
          where ty = localRegType reg


=====================================
compiler/codeGen/StgCmmForeign.hs
=====================================
@@ -526,7 +526,7 @@ closureField dflags off = off + fixedHdrSize dflags
 -- demonstrated that this leads to bad behavior in the presence
 -- of unsafeCoerce#. Returning to the above example, suppose the
 -- Haskell call looked like
---   foo (unsafeCoerce# p) 
+--   foo (unsafeCoerce# p)
 -- where the types of expressions comprising the arguments are
 --   p :: (Any :: TYPE 'UnliftedRep)
 --   i :: Int#
@@ -591,7 +591,7 @@ add_shim dflags ty expr = case ty of
 -- the offset of each argument when used as a C FFI argument.
 -- See Note [Unlifted boxed arguments to foreign calls]
 collectStgFArgTypes :: Type -> [StgFArgType]
-collectStgFArgTypes = go [] 
+collectStgFArgTypes = go []
   where
     -- Skip foralls
     go bs (ForAllTy _ res) = go bs res


=====================================
compiler/ghci/LinkerTypes.hs
=====================================
@@ -28,7 +28,7 @@ import NameEnv                 ( NameEnv )
 import Name                    ( Name )
 import GHCi.RemoteTypes        ( ForeignHValue )
 
-type ClosureEnv = NameEnv (Name, ForeignHValue) 
+type ClosureEnv = NameEnv (Name, ForeignHValue)
 
 newtype DynLinker =
   DynLinker { dl_mpls :: MVar (Maybe PersistentLinkerState) }


=====================================
compiler/main/HscTypes.hs
=====================================
@@ -443,7 +443,7 @@ data HscEnv
                 -- time it is needed.
 
         , hsc_dynLinker :: DynLinker
-                -- ^ dynamic linker. 
+                -- ^ dynamic linker.
 
  }
 


=====================================
compiler/main/Packages.hs
=====================================
@@ -1470,8 +1470,8 @@ mkPackageState dflags dbs preload0 = do
             _  -> unit'
       addIfMorePreferable m unit = addToUDFM_C preferLater m (fsPackageName unit) unit
       -- This is the set of maximally preferable packages. In fact, it is a set of
-      -- most preferable *units* keyed by package name, which act as stand-ins in 
-      -- for "a package in a database". We use units here because we don't have 
+      -- most preferable *units* keyed by package name, which act as stand-ins in
+      -- for "a package in a database". We use units here because we don't have
       -- "a package in a database" as a type currently.
       mostPreferablePackageReps = if gopt Opt_HideAllPackages dflags
                     then emptyUDFM
@@ -1481,7 +1481,7 @@ mkPackageState dflags dbs preload0 = do
       -- with the most preferable unit for package. Being equi-preferable means that
       -- they must be in the same database, with the same version, and the same pacakge name.
       --
-      -- We must take care to consider all these units and not just the most 
+      -- We must take care to consider all these units and not just the most
       -- preferable one, otherwise we can end up with problems like #16228.
       mostPreferable u =
         case lookupUDFM mostPreferablePackageReps (fsPackageName u) of


=====================================
compiler/specialise/Specialise.hs
=====================================
@@ -938,7 +938,7 @@ tryWarnMissingSpecs dflags callers fn calls_for_fn
   | otherwise                             = return ()
   where
     allCallersInlined = all (isAnyInlinePragma . idInlinePragma) callers
-    doWarn reason = 
+    doWarn reason =
       warnMsg reason
         (vcat [ hang (text ("Could not specialise imported function") <+> quotes (ppr fn))
                 2 (vcat [ text "when specialising" <+> quotes (ppr caller)


=====================================
compiler/stgSyn/StgSyn.hs
=====================================
@@ -686,7 +686,7 @@ data StgOp
 
   | StgPrimCallOp PrimCall
 
-  | StgFCallOp ForeignCall Type Unique 
+  | StgFCallOp ForeignCall Type Unique
         -- The Unique is occasionally needed by the C pretty-printer
         -- (which lacks a unique supply), notably when generating a
         -- typedef for foreign-export-dynamic. The Type, which is


=====================================
libraries/ghc-boot/GHC/PackageDb.hs
=====================================
@@ -387,6 +387,8 @@ decodeFromFile :: FilePath -> DbOpenMode mode t -> Get pkgs ->
                   IO (pkgs, DbOpenMode mode PackageDbLock)
 decodeFromFile file mode decoder = case mode of
   DbOpenReadOnly -> do
+  -- Note [Locking package database on Windows]
+  -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
   -- When we open the package db in read only mode, there is no need to acquire
   -- shared lock on non-Windows platform because we update the database with an
   -- atomic rename, so readers will always see the database in a consistent


=====================================
rts/linker/MachO.c
=====================================
@@ -1220,7 +1220,7 @@ ocGetNames_MachO(ObjectCode* oc)
     IF_DEBUG(linker, debugBelch("ocGetNames_MachO: will load %d sections\n",
                                 oc->n_sections));
 
-#if defined (ios_HOST_OS)
+#if defined(ios_HOST_OS)
     for(int i=0; i < oc->n_sections; i++)
     {
         MachOSection * section = &oc->info->macho_sections[i];
@@ -1645,7 +1645,7 @@ ocResolve_MachO(ObjectCode* oc)
     {
         IF_DEBUG(linker, debugBelch("ocResolve_MachO: relocating section %d\n", i));
 
-#if defined aarch64_HOST_ARCH
+#if defined(aarch64_HOST_ARCH)
         if (!relocateSectionAarch64(oc, &oc->sections[i]))
             return 0;
 #else


=====================================
testsuite/tests/driver/dynamicToo/dynamicToo006/all.T
=====================================
@@ -1,2 +1,3 @@
-test('dynamicToo006', [normalise_slashes, extra_files(['Main.hs'])],
+test('dynamicToo006',
+     [normalise_slashes, extra_files(['Main.hs']), unless(have_dynamic(), skip)],
      run_command, ['$MAKE -s main --no-print-director'])


=====================================
testsuite/tests/ghc-api/downsweep/all.T
=====================================
@@ -9,6 +9,7 @@ test('PartialDownsweep',
 
 test('OldModLocation',
      [ extra_run_opts('"' + config.libdir + '"')
+     , when(opsys('mingw32'), expect_broken(16772))
      ],
      compile_and_run,
      ['-package ghc'])


=====================================
testsuite/tests/ghci/linking/dyn/all.T
=====================================
@@ -45,5 +45,11 @@ test('big-obj', [extra_files(['big-obj-c.c', 'big-obj.hs']),
                     unless(doing_ghci, skip), unless(opsys('mingw32'), skip)],
      makefile_test, ['big-obj'])
 
-test('T3372', [unless(doing_ghci, skip), extra_run_opts('"' + config.libdir + '"')],
+test('T3372',
+     [unless(doing_ghci, skip),
+      extra_run_opts('"' + config.libdir + '"'),
+      # Concurrent GHC sessions is fragile on Windows since we must lock the
+      # package database even for read-only access.
+      # See Note [Locking package database on Windows] in GHC.PackageDb
+      when(opsys('mingw32'), fragile(16773))],
      compile_and_run, ['-package ghc'])


=====================================
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered02.stderr-mingw32
=====================================
@@ -0,0 +1,7 @@
+[1 of 2] Compiling UnsafeInfered02_A ( UnsafeInfered02_A.hs, UnsafeInfered02_A.o )
+[2 of 2] Compiling UnsafeInfered02  ( UnsafeInfered02.hs, UnsafeInfered02.o )
+
+UnsafeInfered02.hs:4:1: error:
+    UnsafeInfered02_A: Can't be safely imported!
+    The module itself isn't safe.
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/dbf6998290783650558623cd30370807aa3dce94...51226024b2004304f4eac921e2aef72eaa501114

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/dbf6998290783650558623cd30370807aa3dce94...51226024b2004304f4eac921e2aef72eaa501114
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/20190609/efca924b/attachment-0001.html>


More information about the ghc-commits mailing list