diff --git a/Cabal/Distribution/Compat/Binary/Class.hs b/Cabal/Distribution/Compat/Binary/Class.hs index 117c1d3b5ff38c3af7e13ebd6d9c32e4665f586e..833e080aa7ec78bbf78324ed883dd76c7b9586d6 100644 --- a/Cabal/Distribution/Compat/Binary/Class.hs +++ b/Cabal/Distribution/Compat/Binary/Class.hs @@ -36,8 +36,9 @@ import Foreign import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as L -import Data.Char (chr,ord) -import Data.List (unfoldr) +import Data.Char (chr,ord) +import Data.List (unfoldr) +import Data.Foldable (traverse_) -- And needed for the instances: import qualified Data.ByteString as B @@ -389,7 +390,7 @@ instance (Binary a, Binary b, Binary c, Binary d, Binary e, -- Container types instance Binary a => Binary [a] where - put l = put (length l) >> mapM_ put l + put l = put (length l) >> traverse_ put l get = do n <- get :: Get Int getMany n @@ -444,26 +445,26 @@ instance Binary ByteString where -- Maps and Sets instance (Binary a) => Binary (Set.Set a) where - put s = put (Set.size s) >> mapM_ put (Set.toAscList s) + put s = put (Set.size s) >> traverse_ put (Set.toAscList s) get = liftM Set.fromDistinctAscList get instance (Binary k, Binary e) => Binary (Map.Map k e) where - put m = put (Map.size m) >> mapM_ put (Map.toAscList m) + put m = put (Map.size m) >> traverse_ put (Map.toAscList m) get = liftM Map.fromDistinctAscList get instance Binary IntSet.IntSet where - put s = put (IntSet.size s) >> mapM_ put (IntSet.toAscList s) + put s = put (IntSet.size s) >> traverse_ put (IntSet.toAscList s) get = liftM IntSet.fromDistinctAscList get instance (Binary e) => Binary (IntMap.IntMap e) where - put m = put (IntMap.size m) >> mapM_ put (IntMap.toAscList m) + put m = put (IntMap.size m) >> traverse_ put (IntMap.toAscList m) get = liftM IntMap.fromDistinctAscList get ------------------------------------------------------------------------ -- Queues and Sequences instance (Binary e) => Binary (Seq.Seq e) where - put s = put (Seq.length s) >> Fold.mapM_ put s + put s = put (Seq.length s) >> Fold.traverse_ put s get = do n <- get :: Get Int rep Seq.empty n get where rep xs 0 _ = return $! xs @@ -496,7 +497,7 @@ instance (Binary i, Ix i, Binary e) => Binary (Array i e) where put a = do put (bounds a) put (rangeSize $ bounds a) -- write the length - mapM_ put (elems a) -- now the elems. + traverse_ put (elems a) -- now the elems. get = do bs <- get n <- get -- read the length @@ -510,7 +511,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher put a = do put (bounds a) put (rangeSize $ bounds a) -- now write the length - mapM_ put (elems a) + traverse_ put (elems a) get = do bs <- get n <- get diff --git a/Cabal/Distribution/Compat/Graph.hs b/Cabal/Distribution/Compat/Graph.hs index 3f5e24354a0d7a531994cf04f903564378b6e5ff..fcfd14aeaf932c53a72770c549380fd1fcb418b7 100644 --- a/Cabal/Distribution/Compat/Graph.hs +++ b/Cabal/Distribution/Compat/Graph.hs @@ -293,7 +293,7 @@ revNeighbors g k = do -- Requires amortized construction of graph. closure :: Graph a -> [Key a] -> Maybe [a] closure g ks = do - vs <- mapM (graphKeyToVertex g) ks + vs <- traverse (graphKeyToVertex g) ks return (decodeVertexForest g (G.dfs (graphForward g) vs)) -- | Compute the reverse closure of a graph from some set @@ -302,7 +302,7 @@ closure g ks = do -- Requires amortized construction of graph. revClosure :: Graph a -> [Key a] -> Maybe [a] revClosure g ks = do - vs <- mapM (graphKeyToVertex g) ks + vs <- traverse (graphKeyToVertex g) ks return (decodeVertexForest g (G.dfs (graphAdjoint g) vs)) flattenForest :: Tree.Forest a -> [a] diff --git a/Cabal/Distribution/PackageDescription/Check.hs b/Cabal/Distribution/PackageDescription/Check.hs index 8f8aa2f43afe29c5d5dccbdcbd0ced2ff95dbc9f..757ff7eff79c32a523f40b1faed27d7b2ffed28e 100644 --- a/Cabal/Distribution/PackageDescription/Check.hs +++ b/Cabal/Distribution/PackageDescription/Check.hs @@ -49,6 +49,7 @@ import Distribution.Text import Distribution.Simple.LocalBuildInfo hiding (compiler) import Language.Haskell.Extension +import Control.Monad (mapM) import Data.List (group) import qualified System.Directory as System ( doesFileExist, doesDirectoryExist ) diff --git a/Cabal/Distribution/PackageDescription/Parse.hs b/Cabal/Distribution/PackageDescription/Parse.hs index e1459f307bd195016e8442b63b2b7574b8e8b359..8dafc594df5c3603b5235abf30cd354b6ded4311 100644 --- a/Cabal/Distribution/PackageDescription/Parse.hs +++ b/Cabal/Distribution/PackageDescription/Parse.hs @@ -534,7 +534,7 @@ readAndParseFile withFileContents' parser verbosity fpath = do let (line, message) = locatedErrorMsg e dieWithLocation fpath line message ParseOk warnings x -> do - mapM_ (warn verbosity . showPWarning fpath) $ reverse warnings + traverse_ (warn verbosity . showPWarning fpath) $ reverse warnings return x readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo @@ -561,15 +561,15 @@ isStanzaHeader _ = False mapSimpleFields :: (Field -> ParseResult Field) -> [Field] -> ParseResult [Field] -mapSimpleFields f = mapM walk +mapSimpleFields f = traverse walk where walk fld@F{} = f fld walk (IfBlock l c fs1 fs2) = do - fs1' <- mapM walk fs1 - fs2' <- mapM walk fs2 + fs1' <- traverse walk fs1 + fs2' <- traverse walk fs2 return (IfBlock l c fs1' fs2') walk (Section ln n l fs1) = do - fs1' <- mapM walk fs1 + fs1' <- traverse walk fs1 return (Section ln n l fs1') -- prop_isMapM fs = mapSimpleFields return fs == return fs @@ -1053,7 +1053,7 @@ parsePackageDescription file = do condFlds = [ f | f@IfBlock{} <- allflds ] sections = [ s | s@Section{} <- allflds ] - mapM_ + traverse_ (\(Section l n _ _) -> lift . warning $ "Unexpected section '" ++ n ++ "' on line " ++ show l) sections @@ -1073,11 +1073,11 @@ parsePackageDescription file = do -- to check the CondTree, rather than grovel everywhere -- inside the conditional bits). deps <- liftM concat - . mapM (lift . parseConstraint) + . traverse (lift . parseConstraint) . filter isConstraint $ simplFlds - ifs <- mapM processIfs condFlds + ifs <- traverse processIfs condFlds return (CondNode a deps ifs) where @@ -1123,10 +1123,10 @@ parsePackageDescription file = do PM () checkForUndefinedFlags flags mlib sub_libs exes tests = do let definedFlags = map flagName flags - mapM_ (checkCondTreeFlags definedFlags) (maybeToList mlib) - mapM_ (checkCondTreeFlags definedFlags . snd) sub_libs - mapM_ (checkCondTreeFlags definedFlags . snd) exes - mapM_ (checkCondTreeFlags definedFlags . snd) tests + traverse_ (checkCondTreeFlags definedFlags) (maybeToList mlib) + traverse_ (checkCondTreeFlags definedFlags . snd) sub_libs + traverse_ (checkCondTreeFlags definedFlags . snd) exes + traverse_ (checkCondTreeFlags definedFlags . snd) tests checkCondTreeFlags :: [FlagName] -> CondTree ConfVar c a -> PM () checkCondTreeFlags definedFlags ct = do diff --git a/Cabal/Distribution/ParseUtils.hs b/Cabal/Distribution/ParseUtils.hs index ea29f22a5348180d28d93952604120ce67ef00a2..3d5e5e4b177e3b00e4634b07cbaa76a3253464c4 100644 --- a/Cabal/Distribution/ParseUtils.hs +++ b/Cabal/Distribution/ParseUtils.hs @@ -387,14 +387,14 @@ fName _ = error "fname: not a field or section" readFields :: String -> ParseResult [Field] readFields input = ifelse - =<< mapM (mkField 0) + =<< traverse (mkField 0) =<< mkTree tokens where ls = (lines . normaliseLineEndings) input tokens = (concatMap tokeniseLine . trimLines) ls readFieldsFlat :: String -> ParseResult [Field] -readFieldsFlat input = mapM (mkField 0) +readFieldsFlat input = traverse (mkField 0) =<< mkTree tokens where ls = (lines . normaliseLineEndings) input tokens = (concatMap tokeniseLineFlat . trimLines) ls @@ -568,7 +568,7 @@ mkField d (Node (n,_,l) ts) = case span (\c -> isAlphaNum c || c == '-') l of then tabsError n else return $ F n (map toLower name) (fieldValue rest' followingLines) - rest' -> do ts' <- mapM (mkField (d+1)) ts + rest' -> do ts' <- traverse (mkField (d+1)) ts return (Section n (map toLower name) rest' ts') where fieldValue firstLine followingLines = let firstLine' = trimLeading firstLine diff --git a/Cabal/Distribution/Simple.hs b/Cabal/Distribution/Simple.hs index 1cedbb0406c31e7067adf8b01b1cbba7e3bb164b..50cb2f4979006bbdfd1085235c32d377c8e89182 100644 --- a/Cabal/Distribution/Simple.hs +++ b/Cabal/Distribution/Simple.hs @@ -505,7 +505,7 @@ clean pkg_descr flags = do when exists (removeDirectoryRecursive distPref) -- Any extra files the user wants to remove - mapM_ removeFileOrDirectory (extraTmpFiles pkg_descr) + traverse_ removeFileOrDirectory (extraTmpFiles pkg_descr) -- If the user wanted to save the config, write it back traverse_ (writePersistBuildConfig distPref) maybeConfig diff --git a/Cabal/Distribution/Simple/Bench.hs b/Cabal/Distribution/Simple/Bench.hs index cfd3e6b6eadc257f6311a2b8dd3b947ad0e56a01..8a5d9b80fd3fb6a1307a6c77932b876114ef92aa 100644 --- a/Cabal/Distribution/Simple/Bench.hs +++ b/Cabal/Distribution/Simple/Bench.hs @@ -96,7 +96,7 @@ bench args pkg_descr lbi flags = do let totalBenchmarks = length bmsToRun notice verbosity $ "Running " ++ show totalBenchmarks ++ " benchmarks..." - exitcodes <- mapM doBench bmsToRun + exitcodes <- traverse doBench bmsToRun let allOk = totalBenchmarks == length (filter (== ExitSuccess) exitcodes) unless allOk exitFailure where diff --git a/Cabal/Distribution/Simple/BuildTarget.hs b/Cabal/Distribution/Simple/BuildTarget.hs index 7c6d51c2644abfd3bf93c086853cfbe847d79ecf..f0508680872b847be35f3c8487039b4382b47a68 100644 --- a/Cabal/Distribution/Simple/BuildTarget.hs +++ b/Cabal/Distribution/Simple/BuildTarget.hs @@ -139,7 +139,7 @@ readBuildTargets pkg targetStrs = do let (uproblems, utargets) = readUserBuildTargets targetStrs reportUserBuildTargetProblems uproblems - utargets' <- mapM checkTargetExistsAsFile utargets + utargets' <- traverse checkTargetExistsAsFile utargets let (bproblems, btargets) = resolveBuildTargets pkg utargets' reportBuildTargetProblems bproblems diff --git a/Cabal/Distribution/Simple/Compiler.hs b/Cabal/Distribution/Simple/Compiler.hs index 1eba7e3e617df27d311b2a1746c8ed9c90d536d9..ff78af85eaa9c15f59219f22e4d9fee18cd33f62 100644 --- a/Cabal/Distribution/Simple/Compiler.hs +++ b/Cabal/Distribution/Simple/Compiler.hs @@ -197,7 +197,7 @@ registrationPackageDB dbs = last dbs absolutePackageDBPaths :: PackageDBStack -> IO PackageDBStack -absolutePackageDBPaths = mapM absolutePackageDBPath +absolutePackageDBPaths = traverse absolutePackageDBPath absolutePackageDBPath :: PackageDB -> IO PackageDB absolutePackageDBPath GlobalPackageDB = return GlobalPackageDB diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 3cce1b564611433f9747d62fe6c5c79991003115..72bfd89eaa3ba8df744e6ff31efc572ec89efe69 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -1345,12 +1345,12 @@ configurePkgconfigPackages verbosity pkg_descr conf (_, _, conf') <- requireProgramVersion (lessVerbose verbosity) pkgConfigProgram (orLaterVersion $ Version [0,9,0] []) conf - mapM_ requirePkg allpkgs - mlib' <- mapM addPkgConfigBILib (library pkg_descr) - libs' <- mapM addPkgConfigBILib (subLibraries pkg_descr) - exes' <- mapM addPkgConfigBIExe (executables pkg_descr) - tests' <- mapM addPkgConfigBITest (testSuites pkg_descr) - benches' <- mapM addPkgConfigBIBench (benchmarks pkg_descr) + traverse_ requirePkg allpkgs + mlib' <- traverse addPkgConfigBILib (library pkg_descr) + libs' <- traverse addPkgConfigBILib (subLibraries pkg_descr) + exes' <- traverse addPkgConfigBIExe (executables pkg_descr) + tests' <- traverse addPkgConfigBITest (testSuites pkg_descr) + benches' <- traverse addPkgConfigBIBench (benchmarks pkg_descr) let pkg_descr' = pkg_descr { library = mlib', subLibraries = libs', executables = exes', testSuites = tests', benchmarks = benches' } @@ -2132,7 +2132,7 @@ checkPackageProblems verbosity gpkg pkg = do errors = [ e | PackageBuildImpossible e <- pureChecks ++ ioChecks ] warnings = [ w | PackageBuildWarning w <- pureChecks ++ ioChecks ] if null errors - then mapM_ (warn verbosity) warnings + then traverse_ (warn verbosity) warnings else die (intercalate "\n\n" errors) -- | Preform checks if a relocatable build is allowed @@ -2189,11 +2189,11 @@ checkRelocatable verbosity pkg lbi -- prefix of the package depsPrefixRelative = do pkgr <- GHC.pkgRoot verbosity lbi (last (withPackageDB lbi)) - mapM_ (doCheck pkgr) ipkgs + traverse_ (doCheck pkgr) ipkgs where doCheck pkgr ipkg | maybe False (== pkgr) (Installed.pkgRoot ipkg) - = mapM_ (\l -> when (isNothing $ stripPrefix p l) (die (msg l))) + = traverse_ (\l -> when (isNothing $ stripPrefix p l) (die (msg l))) (Installed.libraryDirs ipkg) | otherwise = return () diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index a10cffede5be0335f78f0f9eee7686aa18bc385a..47872918f436f5698263a353f0e122fb284be995 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -203,7 +203,7 @@ guessToolFromGhcPath tool ghcProg verbosity searchpath info verbosity $ "looking for tool " ++ toolname ++ " near compiler in " ++ given_dir debug verbosity $ "candidate locations: " ++ show guesses - exists <- mapM doesFileExist guesses + exists <- traverse doesFileExist guesses case [ file | (file, True) <- zip guesses exists ] of -- If we can't find it near ghc, fall back to the usual -- method. @@ -397,7 +397,7 @@ getInstalledPackages' :: Verbosity -> [PackageDB] -> ProgramConfiguration -> IO [(PackageDB, [InstalledPackageInfo])] getInstalledPackages' verbosity packagedbs conf | ghcVersion >= Version [6,9] [] = - sequence + sequenceA [ do pkgs <- HcPkg.dump (hcPkgInfo conf) verbosity packagedb return (packagedb, pkgs) | packagedb <- packagedbs ] @@ -415,11 +415,11 @@ getInstalledPackages' verbosity packagedbs conf = do (UserPackageDB, _global:_) -> return $ Nothing (SpecificPackageDB specific, _) -> return $ Just specific _ -> die "cannot read ghc-pkg package listing" - pkgFiles' <- mapM dbFile packagedbs - sequence [ withFileContents file $ \content -> do + pkgFiles' <- traverse dbFile packagedbs + sequenceA [ withFileContents file $ \content -> do pkgs <- readPackages file content return (db, pkgs) - | (db , Just file) <- zip packagedbs pkgFiles' ] + | (db , Just file) <- zip packagedbs pkgFiles' ] where -- Depending on the version of ghc we use a different type's Read -- instance to parse the package file and then convert. @@ -441,7 +441,7 @@ getInstalledPackagesMonitorFiles :: Verbosity -> Platform -> [PackageDB] -> IO [FilePath] getInstalledPackagesMonitorFiles verbosity platform progdb = - mapM getPackageDBPath + traverse getPackageDBPath where getPackageDBPath :: PackageDB -> IO FilePath getPackageDBPath GlobalPackageDB = @@ -659,17 +659,17 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do libInstallPath = libdir $ absoluteComponentInstallDirs pkg_descr lbi uid NoCopyDest sharedLibInstallPath = libInstallPath </> mkSharedLibName compiler_id uid - stubObjs <- catMaybes <$> sequence + stubObjs <- catMaybes <$> sequenceA [ findFileWithExtension [objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | ghcVersion < Version [7,2] [] -- ghc-7.2+ does not make _stub.o files , x <- libModules lib ] - stubProfObjs <- catMaybes <$> sequence + stubProfObjs <- catMaybes <$> sequenceA [ findFileWithExtension ["p_" ++ objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | ghcVersion < Version [7,2] [] -- ghc-7.2+ does not make _stub.o files , x <- libModules lib ] - stubSharedObjs <- catMaybes <$> sequence + stubSharedObjs <- catMaybes <$> sequenceA [ findFileWithExtension ["dyn_" ++ objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | ghcVersion < Version [7,2] [] -- ghc-7.2+ does not make _stub.o files diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs index 5be76b00929b04727bf0309ce6a5feb251552f7f..dc9e4d59e4eb5fb9ee2ec8dff9398f8878749825 100644 --- a/Cabal/Distribution/Simple/GHC/Internal.hs +++ b/Cabal/Distribution/Simple/GHC/Internal.hs @@ -349,7 +349,7 @@ getHaskellObjects _implInfo lib lbi pref wanted_obj_ext allow_split_objs let splitSuffix = "_" ++ wanted_obj_ext ++ "_split" dirs = [ pref </> (ModuleName.toFilePath x ++ splitSuffix) | x <- libModules lib ] - objss <- mapM getDirectoryContents dirs + objss <- traverse getDirectoryContents dirs let objs = [ dir </> obj | (objs',dir) <- zip objss dirs, obj <- objs', let obj_ext = takeExtension obj, diff --git a/Cabal/Distribution/Simple/GHCJS.hs b/Cabal/Distribution/Simple/GHCJS.hs index 3206819e2260b741610373abb3c2c18d1efa7afc..f59fb6b9cb1f180a29140b67035c990c63355004 100644 --- a/Cabal/Distribution/Simple/GHCJS.hs +++ b/Cabal/Distribution/Simple/GHCJS.hs @@ -161,7 +161,7 @@ guessToolFromGhcjsPath tool ghcjsProg verbosity searchpath guessNormal] info verbosity $ "looking for tool " ++ toolname ++ " near compiler in " ++ dir - exists <- mapM doesFileExist guesses + exists <- traverse doesFileExist guesses case [ file | (file, True) <- zip guesses exists ] of -- If we can't find it near ghc, fall back to the usual -- method. @@ -228,7 +228,7 @@ checkPackageDbStack _ = getInstalledPackages' :: Verbosity -> [PackageDB] -> ProgramConfiguration -> IO [(PackageDB, [InstalledPackageInfo])] getInstalledPackages' verbosity packagedbs conf = - sequence + sequenceA [ do pkgs <- HcPkg.dump (hcPkgInfo conf) verbosity packagedb return (packagedb, pkgs) | packagedb <- packagedbs ] diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index d47a3b76a0b3db4c113f61794bedc932e2698aad..e192b99e88671c05865ba7bb07438c924238b8d9 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -569,7 +569,7 @@ haddockPackagePaths :: [InstalledPackageInfo] -> Maybe (InstalledPackageInfo -> FilePath) -> IO ([(FilePath, Maybe FilePath)], Maybe String) haddockPackagePaths ipkgs mkHtmlPath = do - interfaces <- sequence + interfaces <- sequenceA [ case interfaceAndHtmlPath ipkg of Nothing -> return (Left (packageId ipkg)) Just (interface, html) -> do @@ -750,7 +750,7 @@ getExeSourceFiles lbi exe clbi = do getSourceFiles :: [FilePath] -> [ModuleName.ModuleName] -> IO [(ModuleName.ModuleName, FilePath)] -getSourceFiles dirs modules = flip mapM modules $ \m -> fmap ((,) m) $ +getSourceFiles dirs modules = flip traverse modules $ \m -> fmap ((,) m) $ findFileWithExtension ["hs", "lhs"] dirs (ModuleName.toFilePath m) >>= maybe (notFound m) (return . normalise) where diff --git a/Cabal/Distribution/Simple/Hpc.hs b/Cabal/Distribution/Simple/Hpc.hs index 9ba374e52be25a71cee8c65139956690d7ba0f14..5eb52f681e594aff070a5a47cd326f95d64e4478 100644 --- a/Cabal/Distribution/Simple/Hpc.hs +++ b/Cabal/Distribution/Simple/Hpc.hs @@ -124,7 +124,7 @@ markupPackage :: Verbosity -> IO () markupPackage verbosity lbi distPref libName suites = do let tixFiles = map (tixFilePath distPref way . testName) suites - tixFilesExist <- mapM doesFileExist tixFiles + tixFilesExist <- traverse doesFileExist tixFiles when (and tixFilesExist) $ do -- behaviour of 'markup' depends on version, so we need *a* version -- but no particular one diff --git a/Cabal/Distribution/Simple/Install.hs b/Cabal/Distribution/Simple/Install.hs index 794d549f7327ebb47acd6a038b7a47f491003780..d67be52da4440189513d08fc36e3cee65e747f32 100644 --- a/Cabal/Distribution/Simple/Install.hs +++ b/Cabal/Distribution/Simple/Install.hs @@ -228,7 +228,7 @@ copyComponent _ _ _ _ _ _ = return () -- installDataFiles :: Verbosity -> PackageDescription -> FilePath -> IO () installDataFiles verbosity pkg_descr destDataDir = - flip mapM_ (dataFiles pkg_descr) $ \ file -> do + flip traverse_ (dataFiles pkg_descr) $ \ file -> do let srcDataDir = dataDir pkg_descr files <- matchDirFileGlob srcDataDir file let dir = takeDirectory file @@ -243,7 +243,7 @@ installIncludeFiles :: Verbosity -> Library -> FilePath -> IO () installIncludeFiles verbosity lib destIncludeDir = do let relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi) lbi = libBuildInfo lib - incs <- mapM (findInc relincdirs) (installIncludes lbi) + incs <- traverse (findInc relincdirs) (installIncludes lbi) sequence_ [ do createDirectoryIfMissingVerbose verbosity True destDir installOrdinaryFile verbosity srcFile destFile diff --git a/Cabal/Distribution/Simple/LHC.hs b/Cabal/Distribution/Simple/LHC.hs index 69c1c7830769688f0adfba12382cbb648b0fc773..a6bde1c3de713aa7e1f83d3d533e48bf7221eb0b 100644 --- a/Cabal/Distribution/Simple/LHC.hs +++ b/Cabal/Distribution/Simple/LHC.hs @@ -225,7 +225,7 @@ getInstalledPackages' :: ConfiguredProgram -> Verbosity -> IO [(PackageDB, [InstalledPackageInfo])] getInstalledPackages' lhcPkg verbosity packagedbs conf = - sequence + sequenceA [ do str <- rawSystemProgramStdoutConf verbosity lhcPkgProgram conf ["dump", packageDbGhcPkgFlag packagedb] `catchExit` \_ -> die $ "ghc-pkg dump failed" @@ -348,15 +348,15 @@ buildLib verbosity pkg_descr lbi lib clbi = do sharedLibFilePath = libTargetDir </> mkSharedLibName cid lib_name ghciLibFilePath = libTargetDir </> mkGHCiLibName lib_name - stubObjs <- fmap catMaybes $ sequence + stubObjs <- fmap catMaybes $ sequenceA [ findFileWithExtension [objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | x <- libModules lib ] - stubProfObjs <- fmap catMaybes $ sequence + stubProfObjs <- fmap catMaybes $ sequenceA [ findFileWithExtension ["p_" ++ objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | x <- libModules lib ] - stubSharedObjs <- fmap catMaybes $ sequence + stubSharedObjs <- fmap catMaybes $ sequenceA [ findFileWithExtension ["dyn_" ++ objExtension] [libTargetDir] (ModuleName.toFilePath x ++"_stub") | x <- libModules lib ] @@ -538,7 +538,7 @@ getHaskellObjects lib lbi pref wanted_obj_ext allow_split_objs | splitObjs lbi && allow_split_objs = do let dirs = [ pref </> (ModuleName.toFilePath x ++ "_split") | x <- libModules lib ] - objss <- mapM getDirectoryContents dirs + objss <- traverse getDirectoryContents dirs let objs = [ dir </> obj | (objs',dir) <- zip objss dirs, obj <- objs', let obj_ext = takeExtension obj, @@ -719,7 +719,7 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do ifVanilla $ copyModuleFiles "hi" ifProf $ copyModuleFiles "p_hi" hcrFiles <- findModuleFiles (builtDir : hsSourceDirs (libBuildInfo lib)) ["hcr"] (libModules lib) - flip mapM_ hcrFiles $ \(srcBase, srcFile) -> runLhc ["--install-library", srcBase </> srcFile] + flip traverse_ hcrFiles $ \(srcBase, srcFile) -> runLhc ["--install-library", srcBase </> srcFile] -- copy the built library files over: ifVanilla $ copy builtDir targetDir vanillaLibName diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs index 45a61c65e4e1db9403d662e261c127a892128140..271820177e53987eb91eea035aee4f492fe669b8 100644 --- a/Cabal/Distribution/Simple/LocalBuildInfo.hs +++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs @@ -273,7 +273,7 @@ depLibraryPaths inplace relative lbi clbi = do allDepLibDirs = concatMap Installed.libraryDirs ipkgs allDepLibDirs' = internalLibs ++ allDepLibDirs - allDepLibDirsC <- mapM canonicalizePathNoFail allDepLibDirs' + allDepLibDirsC <- traverse canonicalizePathNoFail allDepLibDirs' let p = prefix installDirs prefixRelative l = isJust (stripPrefix p l) diff --git a/Cabal/Distribution/Simple/Program/Find.hs b/Cabal/Distribution/Simple/Program/Find.hs index 3f8eaffeb095d158cb9ee7693c18764a0badf60c..5e574704de2486fcab4ba151a9490c0f70d9e184 100644 --- a/Cabal/Distribution/Simple/Program/Find.hs +++ b/Cabal/Distribution/Simple/Program/Find.hs @@ -132,7 +132,7 @@ findProgramOnSearchPath verbosity searchpath prog = do -- algorithm looks at more than just the @%PATH%@. programSearchPathAsPATHVar :: ProgramSearchPath -> IO String programSearchPathAsPATHVar searchpath = do - ess <- mapM getEntries searchpath + ess <- traverse getEntries searchpath return (intercalate [searchPathSeparator] (concat ess)) where getEntries (ProgramSearchPathDir dir) = return [dir] diff --git a/Cabal/Distribution/Simple/Program/HcPkg.hs b/Cabal/Distribution/Simple/Program/HcPkg.hs index 489f5299c46b8534952b1a1cc4e06026b2d46159..868e1474372abeb4b1082f2f0dbd6e6a68346801 100644 --- a/Cabal/Distribution/Simple/Program/HcPkg.hs +++ b/Cabal/Distribution/Simple/Program/HcPkg.hs @@ -341,7 +341,7 @@ list hpi verbosity packagedb = do ++ programId (hcPkgProgram hpi) ++ " list'" where - parsePackageIds = sequence . map simpleParse . words + parsePackageIds = traverse simpleParse . words -------------------------- -- The program invocations diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index 216c64f0893c9e395ac8ea3d0a0d63f69ed79788..e5764f03d0c47f0e16617e0b9f08efe6f39d5cd6 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -117,7 +117,7 @@ register pkg_descr lbi flags = when (hasPublicLib pkg_descr) doRegister [] -> die "In --assume-deps-up-to-date mode you must specify a target" _ -> die "In --assume-deps-up-to-date mode you can only register a single target" else fmap catMaybes - . mapM maybeGenerateOne + . traverse maybeGenerateOne $ neededTargetsInBuildOrder' pkg_descr lbi (map nodeKey targets) registerAll pkg_descr lbi flags ipis return () diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index 591f5b5f654d49b0a44d0929feade347a1ab78e3..fbadd5d635dcc20110caf5bc6dd7e2abd80b6d34 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -430,7 +430,7 @@ configPrograms = maybe (error "FIXME: remove configPrograms") id . getLast' . co configAbsolutePaths :: ConfigFlags -> IO ConfigFlags configAbsolutePaths f = (\v -> f { configPackageDBs = v }) - `liftM` mapM (maybe (return Nothing) (liftM Just . absolutePackageDBPath)) + `liftM` traverse (maybe (return Nothing) (liftM Just . absolutePackageDBPath)) (configPackageDBs f) defaultConfigFlags :: ProgramConfiguration -> ConfigFlags diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs index 2630e447feacd0bd7abf3a32cd68d0f03e9ab2ee..54a2f3f4e18910abc305e038883654bc7efac297 100644 --- a/Cabal/Distribution/Simple/SrcDist.hs +++ b/Cabal/Distribution/Simple/SrcDist.hs @@ -79,8 +79,8 @@ sdist pkg mb_lbi flags mkTmpDir pps = case (sDistListSources flags) of Flag path -> withFile path WriteMode $ \outHandle -> do (ordinary, maybeExecutable) <- listPackageSources verbosity pkg pps - mapM_ (hPutStrLn outHandle) ordinary - mapM_ (hPutStrLn outHandle) maybeExecutable + traverse_ (hPutStrLn outHandle) ordinary + traverse_ (hPutStrLn outHandle) maybeExecutable notice verbosity $ "List of package sources written to file '" ++ path ++ "'" NoFlag -> do @@ -150,7 +150,7 @@ listPackageSourcesOrdinary :: Verbosity -> [PPSuffixHandler] -> IO [FilePath] listPackageSourcesOrdinary verbosity pkg_descr pps = - fmap concat . sequence $ + fmap concat . sequenceA $ [ -- Library sources. fmap concat @@ -218,7 +218,7 @@ listPackageSourcesOrdinary verbosity pkg_descr pps = . withAllLib $ \ l -> do let lbi = libBuildInfo l relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi) - mapM (fmap snd . findIncludeFile relincdirs) (installIncludes lbi) + traverse (fmap snd . findIncludeFile relincdirs) (installIncludes lbi) -- Setup script, if it exists. , fmap (maybe [] (\f -> [f])) $ findSetupFile "" @@ -230,10 +230,10 @@ listPackageSourcesOrdinary verbosity pkg_descr pps = where -- We have to deal with all libs and executables, so we have local -- versions of these functions that ignore the 'buildable' attribute: - withAllLib action = mapM action (allLibraries pkg_descr) - withAllExe action = mapM action (executables pkg_descr) - withAllTest action = mapM action (testSuites pkg_descr) - withAllBenchmark action = mapM action (benchmarks pkg_descr) + withAllLib action = traverse action (allLibraries pkg_descr) + withAllExe action = traverse action (executables pkg_descr) + withAllTest action = traverse action (testSuites pkg_descr) + withAllBenchmark action = traverse action (benchmarks pkg_descr) -- |Prepare a directory tree of source files. @@ -419,12 +419,12 @@ allSourcesBuildInfo :: BuildInfo -> IO [FilePath] allSourcesBuildInfo bi pps modules = do let searchDirs = hsSourceDirs bi - sources <- fmap concat $ sequence $ + sources <- fmap concat $ sequenceA $ [ let file = ModuleName.toFilePath module_ in findAllFilesWithExtension suffixes searchDirs file >>= nonEmpty (notFound module_) return | module_ <- modules ++ otherModules bi ] - bootFiles <- sequence + bootFiles <- sequenceA [ let file = ModuleName.toFilePath module_ fileExts = ["hs-boot", "lhs-boot"] in findFileWithExtension fileExts (hsSourceDirs bi) file diff --git a/Cabal/Distribution/Simple/Test.hs b/Cabal/Distribution/Simple/Test.hs index fd043ba27fff687a4941800fe3e27580141be305..65e23c852e7869a75ba1c12c960a6269d19329a7 100644 --- a/Cabal/Distribution/Simple/Test.hs +++ b/Cabal/Distribution/Simple/Test.hs @@ -86,7 +86,7 @@ test args pkg_descr lbi flags = do testsToRun <- case testNames of [] -> return $ zip enabledTests $ repeat Nothing - names -> flip mapM names $ \tName -> + names -> flip traverse names $ \tName -> let testMap = zip enabledNames enabledTests enabledNames = map (PD.testName . fst) enabledTests allNames = map PD.testName pkgTests @@ -102,11 +102,11 @@ test args pkg_descr lbi flags = do -- Delete ordinary files from test log directory. getDirectoryContents testLogDir >>= filterM doesFileExist . map (testLogDir </>) - >>= mapM_ removeFile + >>= traverse_ removeFile let totalSuites = length testsToRun notice verbosity $ "Running " ++ show totalSuites ++ " test suites..." - suites <- mapM doTest testsToRun + suites <- traverse doTest testsToRun let packageLog = (localPackageLog pkg_descr lbi) { testSuites = suites } packageLogFile = (</>) testLogDir $ packageLogPath machineTemplate pkg_descr lbi diff --git a/Cabal/Distribution/Simple/Test/LibV09.hs b/Cabal/Distribution/Simple/Test/LibV09.hs index 1e1916ed835ba7344a1f80c1cbec0e697551dff1..5ebcdf1ab54e91be6fa62f15eeefc8cf8ec9177d 100644 --- a/Cabal/Distribution/Simple/Test/LibV09.hs +++ b/Cabal/Distribution/Simple/Test/LibV09.hs @@ -225,7 +225,7 @@ stubMain tests = do -- by the calling Cabal process. stubRunTests :: [Test] -> IO TestLogs stubRunTests tests = do - logs <- mapM stubRunTests' tests + logs <- traverse stubRunTests' tests return $ GroupLogs "Default" logs where stubRunTests' (Test t) = do @@ -241,7 +241,7 @@ stubRunTests tests = do } finish (Progress _ next) = next >>= finish stubRunTests' g@(Group {}) = do - logs <- mapM stubRunTests' $ groupTests g + logs <- traverse stubRunTests' $ groupTests g return $ GroupLogs (groupName g) logs stubRunTests' (ExtraOptions _ t) = stubRunTests' t maybeDefaultOption opt = diff --git a/Cabal/Distribution/Simple/UHC.hs b/Cabal/Distribution/Simple/UHC.hs index ebc99a78f9930f80cdcbf02305526b238d2fbb56..6fc788ec22422de3c65b0bfb44d447d30265f067 100644 --- a/Cabal/Distribution/Simple/UHC.hs +++ b/Cabal/Distribution/Simple/UHC.hs @@ -98,7 +98,7 @@ getInstalledPackages verbosity comp packagedbs conf = do let pkgDirs = nub (concatMap (packageDbPaths userPkgDir systemPkgDir) packagedbs) -- putStrLn $ "pkgdirs: " ++ show pkgDirs pkgs <- liftM (map addBuiltinVersions . concat) $ - mapM (\ d -> getDirectoryContents d >>= filterM (isPkgDir (display compilerid) d)) + traverse (\ d -> getDirectoryContents d >>= filterM (isPkgDir (display compilerid) d)) pkgDirs -- putStrLn $ "pkgs: " ++ show pkgs let iPkgs = diff --git a/Cabal/Distribution/Simple/Utils.hs b/Cabal/Distribution/Simple/Utils.hs index 19641b28c90e8f71d20cfe6338b5ab1cfe19f1b2..fb0c1527e2ab793b2c7ee62732cd79b7f0fb65e3 100644 --- a/Cabal/Distribution/Simple/Utils.hs +++ b/Cabal/Distribution/Simple/Utils.hs @@ -646,7 +646,7 @@ xargs :: Int -> ([String] -> IO ()) xargs maxSize rawSystemFun fixedArgs bigArgs = let fixedArgSize = sum (map length fixedArgs) + length fixedArgs chunkSize = maxSize - fixedArgSize - in mapM_ (rawSystemFun . (fixedArgs ++)) (chunks chunkSize bigArgs) + in traverse_ (rawSystemFun . (fixedArgs ++)) (chunks chunkSize bigArgs) where chunks len = unfoldr $ \s -> if null s then Nothing @@ -733,7 +733,7 @@ findModuleFiles :: [FilePath] -- ^ build prefix (location of objects) -> [ModuleName] -- ^ modules -> IO [(FilePath, FilePath)] findModuleFiles searchPath extensions moduleNames = - mapM (findModuleFile searchPath extensions) moduleNames + traverse (findModuleFile searchPath extensions) moduleNames -- | Find the file corresponding to a Haskell module name. -- @@ -979,7 +979,7 @@ copyFilesWith doCopy verbosity targetDir srcFiles = do -- Create parent directories for everything let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles - mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs + traverse_ (createDirectoryIfMissingVerbose verbosity True) dirs -- Copy all the files sequence_ [ let src = srcBase </> srcFile