Silence hlint

This commit is contained in:
Julian Ospald 2022-02-05 19:39:00 +01:00
parent 6b978b42bc
commit 684953464b
Signed by: hasufell
GPG Key ID: 3786C5262ECB4A3F
2 changed files with 10 additions and 12 deletions

View File

@ -5,6 +5,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-|
@ -1252,7 +1253,7 @@ setHLS ver shls = do
-- not for legacy
SetHLS_XYZ -> liftE $ rmMinorHLSSymlinks ver
-- legacy and new
SetHLSOnly -> liftE $ rmPlainHLS
SetHLSOnly -> liftE rmPlainHLS
case shls of
-- not for legacy
@ -1267,7 +1268,6 @@ setHLS ver shls = do
else fname <> "~" <> T.unpack (prettyVer ver) <> exeExt
lift $ createLink destL (binDir </> target)
pure ()
-- legacy and new
SetHLSOnly -> do
-- set haskell-language-server-<ghcver> symlinks
@ -1287,8 +1287,6 @@ setHLS ver shls = do
lift warnAboutHlsCompatibility
pure ()
unsetHLS :: ( MonadMask m
, MonadReader env m
@ -2846,7 +2844,7 @@ rmHLSNoGHC = do
hlses <- fmap rights getInstalledHLSs
forM_ hlses $ \hls -> do
hlsGHCs <- fmap mkTVer <$> hlsGHCVersions' hls
let candidates = filter (`notElem` ghcs) $ hlsGHCs
let candidates = filter (`notElem` ghcs) hlsGHCs
if (length hlsGHCs - length candidates) <= 0
then rmHLSVer hls
else

View File

@ -251,7 +251,7 @@ rmPlainHLS = do
Dirs {..} <- lift getDirs
-- delete 'haskell-language-server-8.10.7'
hlsBins <- fmap (filter (\f -> not ("haskell-language-server-wrapper" `isPrefixOf` f) && not ('~' `elem` f)))
hlsBins <- fmap (filter (\f -> not ("haskell-language-server-wrapper" `isPrefixOf` f) && ('~' `notElem` f)))
$ liftIO $ handleIO (\_ -> pure []) $ findFiles
binDir
(makeRegexOpts compExtended execBlank ([s|^haskell-language-server-.*$|] :: ByteString))
@ -518,7 +518,7 @@ hlsInstalled ver = do
isLegacyHLS :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool
isLegacyHLS ver = do
bdir <- ghcupHLSDir ver
not <$> (liftIO $ doesDirectoryExist bdir)
not <$> liftIO (doesDirectoryExist bdir)
-- Return the currently set hls version, if any.
@ -620,8 +620,8 @@ hlsInternalServerScripts :: (MonadReader env m, HasDirs env, MonadIO m, MonadThr
hlsInternalServerScripts ver mghcVer = do
dir <- ghcupHLSDir ver
let bdir = dir </> "bin"
(fmap (bdir </>) . filter (\f -> maybe True (\gv -> ("-" <> T.unpack (prettyVer gv)) `isSuffixOf` f) mghcVer))
<$> (liftIO $ listDirectory bdir)
fmap (bdir </>) . filter (\f -> maybe True (\gv -> ("-" <> T.unpack (prettyVer gv)) `isSuffixOf` f) mghcVer)
<$> liftIO (listDirectory bdir)
-- | Get all binaries for a hls version from the ~/.ghcup/hls/<ver>/lib/haskell-language-server-<ver>/bin directory, if any.
-- Returns the full path.
@ -633,8 +633,8 @@ hlsInternalServerBinaries ver mghcVer = do
dir <- ghcupHLSDir ver
let regex = makeRegexOpts compExtended execBlank ([s|^haskell-language-server-.*$|] :: ByteString)
(Just bdir) <- fmap headMay $ liftIO $ expandFilePath [Left (dir </> "lib"), Right regex, Left "bin"]
(fmap (bdir </>) . filter (\f -> maybe True (\gv -> ("-" <> T.unpack (prettyVer gv)) `isSuffixOf` f) mghcVer))
<$> (liftIO $ listDirectory bdir)
fmap (bdir </>) . filter (\f -> maybe True (\gv -> ("-" <> T.unpack (prettyVer gv)) `isSuffixOf` f) mghcVer)
<$> liftIO (listDirectory bdir)
-- | Get all libraries for a hls version from the ~/.ghcup/hls/<ver>/lib/haskell-language-server-<ver>/lib/<ghc-ver>/
-- directory, if any.
@ -647,7 +647,7 @@ hlsInternalServerLibs ver ghcVer = do
dir <- ghcupHLSDir ver
let regex = makeRegexOpts compExtended execBlank ([s|^haskell-language-server-.*$|] :: ByteString)
(Just bdir) <- fmap headMay $ liftIO $ expandFilePath [Left (dir </> "lib"), Right regex, Left ("lib" </> T.unpack (prettyVer ghcVer))]
(fmap (bdir </>)) <$> (liftIO $ listDirectory bdir)
fmap (bdir </>) <$> liftIO (listDirectory bdir)
-- | Get the wrapper binary for an hls version, if any.