Skip to content
Snippets Groups Projects
Commit 85fff514 authored by Ben Gamari's avatar Ben Gamari Committed by Cheng Shao
Browse files

hadrian: Drop uses of head/tail

To silence warnings with GHC 9.10

(cherry picked from commit a7e23f01)
(cherry picked from commit 1078f402)
parent b92a9da4
No related branches found
No related tags found
No related merge requests found
......@@ -138,7 +138,10 @@ unifyPath = toStandard . normaliseEx
-- | Combine paths with a forward slash regardless of platform.
(-/-) :: 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
......@@ -615,7 +618,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
......
......@@ -170,10 +170,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
......
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment