Skip to content

Commit

Permalink
remove shadowing and unused imports
Browse files Browse the repository at this point in the history
  • Loading branch information
emilypi authored and ptkato committed May 3, 2021
1 parent f08a447 commit f6b4f65
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 6 deletions.
2 changes: 1 addition & 1 deletion cabal-install/main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ import Distribution.Client.Setup
, UploadFlags(..), uploadCommand
, ReportFlags(..), reportCommand
, runCommand
, InitFlags(initVerbosity, initHcPath, interactive), initCommand
, InitFlags(initVerbosity, initHcPath), initCommand
, ActAsSetupFlags(..), actAsSetupCommand
, UserConfigFlags(..), userConfigCommand
, reportCommand
Expand Down
4 changes: 2 additions & 2 deletions cabal-install/src/Distribution/Client/Init/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -361,9 +361,9 @@ instance Interactive PurePrompt where
input <- pop
return (ExitSuccess, input, "")
getEnvironment = fmap (map read) popList
listFilesInside pred !_ = do
listFilesInside pred' !_ = do
input <- map splitDirectories <$> popList
map joinPath <$> filterM (fmap and . traverse pred) input
map joinPath <$> filterM (fmap and . traverse pred') input
listFilesRecursive !_ = popList

putStr !_ = return ()
Expand Down
6 changes: 3 additions & 3 deletions cabal-install/src/Distribution/Client/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -428,19 +428,19 @@ listContents dir = do
-- | From Control.Monad.Extra
-- https://hackage.haskell.org/package/extra-1.7.9
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM b t f = do b <- b; if b then t else f
ifM b t f = do b' <- b; if b' then t else f

-- | From Control.Monad.Extra
-- https://hackage.haskell.org/package/extra-1.7.9
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
{-# INLINE concatMapM #-}
concatMapM op = foldr f (pure [])
where f x xs = do x <- op x; if null x then xs else do xs <- xs; pure $ x++xs
where f x xs = do x' <- op x; if null x' then xs else do xs' <- xs; pure $ x' ++ xs'

-- | From Control.Monad.Extra
-- https://hackage.haskell.org/package/extra-1.7.9
partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
partitionM f [] = pure ([], [])
partitionM _ [] = pure ([], [])
partitionM f (x:xs) = do
res <- f x
(as,bs) <- partitionM f xs
Expand Down

0 comments on commit f6b4f65

Please sign in to comment.