[Git][ghc/ghc][master] 3 commits: gitlab-ci: Bump docker images

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Feb 10 08:22:21 UTC 2025



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
a566da92 by Ben Gamari at 2025-02-10T03:21:49-05:00
gitlab-ci: Bump docker images

Closes #25693.

- - - - -
a7e23f01 by Ben Gamari at 2025-02-10T03:21:49-05:00
hadrian: Drop uses of head/tail

To silence warnings with GHC 9.10

- - - - -
12752f0c by Ben Gamari at 2025-02-10T03:21:49-05:00
hadrian: Disable x-data-list-nonempty-unzip warning

- - - - -


5 changed files:

- .gitlab-ci.yml
- hadrian/src/Hadrian/Utilities.hs
- hadrian/src/Oracles/ModuleFiles.hs
- hadrian/src/Rules/Dependencies.hs
- hadrian/src/Settings/Parser.hs


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
   GIT_SSL_NO_VERIFY: "1"
 
   # Commit of ghc/ci-images repository from which to pull Docker images
-  DOCKER_REV: eb4d3389fd62e4f7321a0c8799014ec1f4da0708
+  DOCKER_REV: 94df7d589f0ded990826bc7a4d7f5a40d6055a4f
 
   # Sequential version number of all cached things.
   # Bump to invalidate GitLab CI cache.


=====================================
hadrian/src/Hadrian/Utilities.hs
=====================================
@@ -149,7 +149,10 @@ as /c/foo, while it occasionally falls over on paths of the form C:\foo.
 --
 -- See Note [Absolute paths and MSYS].
 (-/-) :: FilePath -> FilePath -> FilePath
-_  -/- b | isAbsolute b && not (isAbsolute $ tail b) = b
+_  -/- b
+    | isAbsolute b
+    , _:b' <- b
+    , not (isAbsolute b') = b
 "" -/- b = b
 a  -/- b
     | last a == '/' = a ++       b
@@ -636,7 +639,8 @@ renderLibrary name lib synopsis = renderBox $
 -- | ipsum    |
 -- \----------/
 renderBox :: [String] -> String
-renderBox ls = tail $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot])
+renderBox ls =
+    drop 1 $ concatMap ('\n' :) (boxTop : map renderLine ls ++ [boxBot])
   where
     -- Minimum total width of the box in characters
     minimumBoxWidth = 32


=====================================
hadrian/src/Oracles/ModuleFiles.hs
=====================================
@@ -169,10 +169,12 @@ moduleFilesOracle = void $ do
 
         let pairs = sort $ mainpairs ++ [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ]
             multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ]
-        unless (null multi) $ do
-            let (m, f1, f2) = head multi
-            error $ "Module " ++ m ++ " has more than one source file: "
-                ++ f1 ++ " and " ++ f2 ++ "."
+
+        case multi of
+            [] -> return ()
+            (m, f1, f2) : _ ->
+              fail $ "Module " ++ m ++ " has more than one source file: "
+                  ++ f1 ++ " and " ++ f2 ++ "."
         return $ lookupAll modules pairs
 
     -- Optimisation: we discard Haskell files here, because they are never used


=====================================
hadrian/src/Rules/Dependencies.hs
=====================================
@@ -1,4 +1,5 @@
 {-# OPTIONS_GHC -Wno-deprecations #-}
+{-# OPTIONS_GHC -Wno-x-data-list-nonempty-unzip #-}
 
 module Rules.Dependencies (buildPackageDependencies) where
 


=====================================
hadrian/src/Settings/Parser.hs
=====================================
@@ -184,14 +184,11 @@ instance Match SettingsM where
 matchStringSettingsM :: String -> SettingsM ()
 matchStringSettingsM s = do
   ks <- State.get
-  if null ks
-    then throwError $ "expected " ++ show s ++ ", got nothing"
-    else go (head ks)
-
-  where go k
-          | k == s = State.modify tail
-          | otherwise = throwError $
-              "expected " ++ show s ++ ", got " ++ show k
+  case ks of
+    []            -> throwError $ "expected " ++ show s ++ ", got nothing"
+    k:_
+      | k == s    -> State.modify (drop 1)
+      | otherwise -> throwError $ "expected " ++ show s ++ ", got " ++ show k
 
 matchOneOfSettingsM :: [SettingsM a] -> SettingsM a
 matchOneOfSettingsM acts = StateT $ \k -> do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52b6539b5fbce27e0e8b4181bea333895e42128c...12752f0cfd8072cd6235f011bb22a5d3d6bc7dc6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52b6539b5fbce27e0e8b4181bea333895e42128c...12752f0cfd8072cd6235f011bb22a5d3d6bc7dc6
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/20250210/8c5cce49/attachment-0001.html>


More information about the ghc-commits mailing list