Skip to content

Commit b2f5835

Browse files
committed
Replace mergeWithKey with merge
`Data.Map.Strict.mergeWithKey` is described as deprecated and users are told to prefer `Data.Map.Merge.Strict.merge`.
1 parent f441f4e commit b2f5835

File tree

4 files changed

+38
-36
lines changed

4 files changed

+38
-36
lines changed

src/Stack/Build/ConstructPlan.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module Stack.Build.ConstructPlan
1010

1111
import Control.Monad.RWS.Strict hiding ( (<>) )
1212
import qualified Data.List as L
13-
import qualified Data.Map.Strict as M
13+
import qualified Data.Map.Merge.Strict as Map
1414
import qualified Data.Map.Strict as Map
1515
import Data.Monoid.Map ( MonoidMap(..) )
1616
import qualified Data.Set as Set
@@ -93,10 +93,10 @@ combineSourceInstalled ps (location, installed) =
9393
type CombinedMap = Map PackageName PackageInfo
9494

9595
combineMap :: Map PackageName PackageSource -> InstalledMap -> CombinedMap
96-
combineMap = Map.mergeWithKey
97-
(\_ s i -> Just $ combineSourceInstalled s i)
98-
(fmap PIOnlySource)
99-
(fmap (uncurry PIOnlyInstalled))
96+
combineMap = Map.merge
97+
(Map.mapMissing (\_ s -> PIOnlySource s))
98+
(Map.mapMissing (\_ i -> uncurry PIOnlyInstalled i))
99+
(Map.zipWithMatched (\_ s i -> combineSourceInstalled s i))
100100

101101
data AddDepRes
102102
= ADRToInstall Task
@@ -243,29 +243,29 @@ constructPlan baseConfigOpts0 localDumpPkgs loadPackage0 sourceMap installedMap
243243
pathEnvVar' <- liftIO $ maybe mempty T.pack <$> lookupEnv "PATH"
244244
let ctx = mkCtx econfig globalCabalVersion sources mcur pathEnvVar'
245245
((), m, W efinals installExes dirtyReason warnings parents) <-
246-
liftIO $ runRWST inner ctx M.empty
246+
liftIO $ runRWST inner ctx Map.empty
247247
mapM_
248248
(prettyWarn . fromString . T.unpack . textDisplay) (warnings [])
249249
let toEither (_, Left e) = Left e
250250
toEither (k, Right v) = Right (k, v)
251-
(errlibs, adrs) = partitionEithers $ map toEither $ M.toList m
252-
(errfinals, finals) = partitionEithers $ map toEither $ M.toList efinals
251+
(errlibs, adrs) = partitionEithers $ map toEither $ Map.toList m
252+
(errfinals, finals) = partitionEithers $ map toEither $ Map.toList efinals
253253
errs = errlibs ++ errfinals
254254
if null errs
255255
then do
256256
let toTask (_, ADRFound _ _) = Nothing
257257
toTask (name, ADRToInstall task) = Just (name, task)
258-
tasks = M.fromList $ mapMaybe toTask adrs
258+
tasks = Map.fromList $ mapMaybe toTask adrs
259259
takeSubset =
260260
case boptsCLIBuildSubset $ bcoBuildOptsCLI baseConfigOpts0 of
261261
BSAll -> pure
262262
BSOnlySnapshot -> pure . stripLocals
263263
BSOnlyDependencies ->
264-
pure . stripNonDeps (M.keysSet $ smDeps sourceMap)
264+
pure . stripNonDeps (Map.keysSet $ smDeps sourceMap)
265265
BSOnlyLocals -> errorOnSnapshot
266266
takeSubset Plan
267267
{ planTasks = tasks
268-
, planFinals = M.fromList finals
268+
, planFinals = Map.fromList finals
269269
, planUnregisterLocal =
270270
mkUnregisterLocal tasks dirtyReason localDumpPkgs initialBuildSteps
271271
, planInstallExes =
@@ -794,9 +794,9 @@ packageBuildTypeConfig pkg = packageBuildType pkg == Configure
794794
-- error about cyclic dependencies, prefer the cyclic error.
795795
updateLibMap :: PackageName -> Either ConstructPlanException AddDepRes -> M ()
796796
updateLibMap name val = modify $ \mp ->
797-
case (M.lookup name mp, val) of
797+
case (Map.lookup name mp, val) of
798798
(Just (Left DependencyCycleDetected{}), Left _) -> mp
799-
_ -> M.insert name val mp
799+
_ -> Map.insert name val mp
800800

801801
addEllipsis :: Text -> Text
802802
addEllipsis t
@@ -935,7 +935,7 @@ addPackageDeps package = do
935935
-- Update the parents map, for later use in plan construction errors
936936
-- - see 'getShortestDepsPath'.
937937
addParent depname range mversion =
938-
tell mempty { wParents = MonoidMap $ M.singleton depname val }
938+
tell mempty { wParents = MonoidMap $ Map.singleton depname val }
939939
where
940940
val = (First mversion, [(packageIdentifier package, range)])
941941

@@ -1150,7 +1150,7 @@ stripNonDeps deps plan = plan
11501150
when (pid `elem` dependents) $
11511151
impureThrow $ TaskCycleBug pid
11521152
modify' (<> Set.singleton pid)
1153-
mapM_ (collectMissing (pid:dependents)) (fromMaybe mempty $ M.lookup pid missing)
1153+
mapM_ (collectMissing (pid:dependents)) (fromMaybe mempty $ Map.lookup pid missing)
11541154

11551155
-- | Is the given package/version combo defined in the snapshot or in the global
11561156
-- database?

src/Stack/Build/Execute.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ import qualified Data.List as L
4545
import Data.List.NonEmpty ( nonEmpty )
4646
import qualified Data.List.NonEmpty as NonEmpty ( toList )
4747
import Data.List.Split ( chunksOf )
48-
import qualified Data.Map.Strict as M
48+
import qualified Data.Map.Merge.Strict as Map
4949
import qualified Data.Map.Strict as Map
5050
import qualified Data.Set as Set
5151
import qualified Data.Text as T
@@ -726,15 +726,15 @@ executePlan' installedMap0 targets plan ee@ExecuteEnv {..} = do
726726
else Just <$> liftIO (newMVar ())
727727

728728
let actions = concatMap (toActions installedMap' mtestLock run ee) $
729-
Map.elems $ Map.mergeWithKey
730-
(\_ b f -> Just (Just b, Just f))
731-
(fmap (\b -> (Just b, Nothing)))
732-
(fmap (\f -> (Nothing, Just f)))
729+
Map.elems $ Map.merge
730+
(Map.mapMissing (\_ b -> (Just b, Nothing)))
731+
(Map.mapMissing (\_ f -> (Nothing, Just f)))
732+
(Map.zipWithMatched (\_ b f -> (Just b, Just f)))
733733
(planTasks plan)
734734
(planFinals plan)
735735
threads <- view $ configL.to configJobs
736736
let keepGoing =
737-
fromMaybe (not (M.null (planFinals plan))) (boptsKeepGoing eeBuildOpts)
737+
fromMaybe (not (Map.null (planFinals plan))) (boptsKeepGoing eeBuildOpts)
738738
terminal <- view terminalL
739739
errs <- liftIO $ runActions threads keepGoing actions $
740740
\doneVar actionsVar -> do
@@ -2103,7 +2103,7 @@ getExecutableBuildStatuses package pkgDir = do
21032103
distDir <- distDirFromDir pkgDir
21042104
platform <- view platformL
21052105
fmap
2106-
M.fromList
2106+
Map.fromList
21072107
(mapM (checkExeStatus platform distDir) (Set.toList (packageExes package)))
21082108

21092109
-- | Check whether the given executable is defined in the given dist directory.
@@ -2147,7 +2147,7 @@ checkForUnlistedFiles (TTLocalMutable lp) pkgDir = do
21472147
(lpCabalFile lp)
21482148
(lpComponents lp)
21492149
caches
2150-
forM_ (M.toList addBuildCache) $ \(component, newToCache) -> do
2150+
forM_ (Map.toList addBuildCache) $ \(component, newToCache) -> do
21512151
let cache = Map.findWithDefault Map.empty component caches
21522152
writeBuildCache pkgDir component $
21532153
Map.unions (cache : newToCache)
@@ -2279,7 +2279,7 @@ singleTest topts testsToRun ac ee task installedMap = do
22792279
<> display (unGhcPkgId ghcId)
22802280
<> "\n"
22812281
)
2282-
(pkgGhcIdList ++ thGhcId:M.elems allDepsMap)
2282+
(pkgGhcIdList ++ thGhcId:Map.elems allDepsMap)
22832283
writeFileUtf8Builder fp ghcEnv
22842284
menv <- liftIO $
22852285
setEnv fp =<< configProcessContextSettings config EnvSettings
@@ -2661,7 +2661,7 @@ exesToBuild executableBuildStatuses lp =
26612661

26622662
-- | Do the current executables satisfy Cabal's bugged out requirements?
26632663
cabalIsSatisfied :: Map k ExecutableBuildStatus -> Bool
2664-
cabalIsSatisfied = all (== ExecutableBuilt) . M.elems
2664+
cabalIsSatisfied = all (== ExecutableBuilt) . Map.elems
26652665

26662666
-- Test-suite and benchmark build components.
26672667
finalComponentOptions :: LocalPackage -> [String]

src/Stack/Build/Source.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Conduit ( ZipSink (..), withSourceFile )
1818
import Data.ByteString.Builder ( toLazyByteString )
1919
import qualified Data.List as L
2020
import qualified Data.Map as Map
21+
import qualified Data.Map.Merge.Lazy as Map
2122
import qualified Data.Map.Strict as M
2223
import qualified Data.Set as Set
2324
import qualified Distribution.PackageDescription as C
@@ -422,10 +423,10 @@ checkBuildCache oldCache files = do
422423
mdigest <- liftIO (getFileDigestMaybe (toFilePath fp))
423424
pure (toFilePath fp, mdigest)
424425
fmap (mconcat . Map.elems) $ sequence $
425-
Map.mergeWithKey
426-
(\fp mdigest fci -> Just (go fp mdigest (Just fci)))
427-
(Map.mapWithKey (\fp mdigest -> go fp mdigest Nothing))
428-
(Map.mapWithKey (\fp fci -> go fp Nothing (Just fci)))
426+
Map.merge
427+
(Map.mapMissing (\fp mdigest -> go fp mdigest Nothing))
428+
(Map.mapMissing (\fp fci -> go fp Nothing (Just fci)))
429+
(Map.zipWithMatched (\fp mdigest fci -> go fp mdigest (Just fci)))
429430
fileTimes
430431
oldCache
431432
where

src/Stack/FileWatch.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Stack.FileWatch
88
) where
99

1010
import Control.Concurrent.STM ( check )
11+
import qualified Data.Map.Merge.Strict as Map
1112
import qualified Data.Map.Strict as Map
1213
import qualified Data.Set as Set
1314
import GHC.IO.Exception
@@ -56,10 +57,10 @@ fileWatchConf cfg inner =
5657
setWatched files = do
5758
atomically $ writeTVar allFiles $ Set.map toFilePath files
5859
watch0 <- readTVarIO watchVar
59-
let actions = Map.mergeWithKey
60-
keepListening
61-
stopListening
62-
startListening
60+
let actions = Map.merge
61+
(Map.mapMissing stopListening)
62+
(Map.mapMissing startListening)
63+
(Map.zipWithMatched keepListening)
6364
watch0
6465
newDirs
6566
watch1 <- forM (Map.toList actions) $ \(k, mmv) -> do
@@ -74,16 +75,16 @@ fileWatchConf cfg inner =
7475
$ Set.toList
7576
$ Set.map parent files
7677

77-
keepListening _dir listen () = Just $ pure $ Just listen
78-
stopListening = Map.map $ \f -> do
78+
keepListening _dir listen () = pure $ Just listen
79+
stopListening _ f = do
7980
() <- f `catch` \ioe ->
8081
-- Ignore invalid argument error - it can happen if
8182
-- the directory is removed.
8283
case ioe_type ioe of
8384
InvalidArgument -> pure ()
8485
_ -> throwIO ioe
8586
pure Nothing
86-
startListening = Map.mapWithKey $ \dir () -> do
87+
startListening dir () = do
8788
let dir' = fromString $ toFilePath dir
8889
listen <- watchDir manager dir' (const True) onChange
8990
pure $ Just listen

0 commit comments

Comments
 (0)