diff options
author | Ömer Sinan Ağacan <omeragacan@gmail.com> | 2020-02-17 09:56:33 +0300 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-02-20 21:20:45 -0500 |
commit | 65b7256a88ae2bd878da5d026e4183cba6f6eedf (patch) | |
tree | feae01641c4fcbaa438dda9298d7d9ca2430eb85 /compiler | |
parent | c8439fc789ff00cfdd453d2425d2146df69e0729 (diff) | |
download | haskell-65b7256a88ae2bd878da5d026e4183cba6f6eedf.tar.gz |
Use concatMap(M) instead of `concat . map` and the monadic variant
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/GHC/ByteCode/Asm.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Cmm/Switch/Implement.hs | 3 | ||||
-rw-r--r-- | compiler/GHC/CoreToByteCode.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/HsToCore/PmCheck.hs | 3 | ||||
-rw-r--r-- | compiler/GHC/Iface/Load.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Runtime/Eval.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Stg/Stats.hs | 2 | ||||
-rw-r--r-- | compiler/main/DriverPipeline.hs | 4 | ||||
-rw-r--r-- | compiler/main/HscMain.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/ArchBase.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Liveness.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcBinds.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcClassDcl.hs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcRnExports.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcValidity.hs | 2 | ||||
-rw-r--r-- | compiler/utils/Digraph.hs | 2 | ||||
-rw-r--r-- | compiler/utils/GraphColor.hs | 2 |
17 files changed, 24 insertions, 22 deletions
diff --git a/compiler/GHC/ByteCode/Asm.hs b/compiler/GHC/ByteCode/Asm.hs index db5c14b806..95e728c2a6 100644 --- a/compiler/GHC/ByteCode/Asm.hs +++ b/compiler/GHC/ByteCode/Asm.hs @@ -101,7 +101,7 @@ assembleBCOs hsc_env proto_bcos tycons top_strs modbreaks = do return CompiledByteCode { bc_bcos = bcos' , bc_itbls = itblenv - , bc_ffis = concat (map protoBCOFFIs proto_bcos) + , bc_ffis = concatMap protoBCOFFIs proto_bcos , bc_strs = top_strs ++ ptrs , bc_breaks = modbreaks } diff --git a/compiler/GHC/Cmm/Switch/Implement.hs b/compiler/GHC/Cmm/Switch/Implement.hs index dfac116764..859fe81b8d 100644 --- a/compiler/GHC/Cmm/Switch/Implement.hs +++ b/compiler/GHC/Cmm/Switch/Implement.hs @@ -13,6 +13,7 @@ import GHC.Cmm.Utils import GHC.Cmm.Switch import UniqSupply import DynFlags +import MonadUtils (concatMapM) -- -- This module replaces Switch statements as generated by the Stg -> Cmm @@ -35,7 +36,7 @@ cmmImplementSwitchPlans dflags g -- Switch generation done by backend (LLVM/C) | targetSupportsSwitch (hscTarget dflags) = return g | otherwise = do - blocks' <- concat `fmap` mapM (visitSwitches dflags) (toBlockList g) + blocks' <- concatMapM (visitSwitches dflags) (toBlockList g) return $ ofBlockList (g_entry g) blocks' visitSwitches :: DynFlags -> CmmBlock -> UniqSM [CmmBlock] diff --git a/compiler/GHC/CoreToByteCode.hs b/compiler/GHC/CoreToByteCode.hs index 73a54fb3e2..318364fd7c 100644 --- a/compiler/GHC/CoreToByteCode.hs +++ b/compiler/GHC/CoreToByteCode.hs @@ -1116,7 +1116,7 @@ doCase d s p (_,scrut) bndr alts is_unboxed_tuple binds = Map.toList p -- NB: unboxed tuple cases bind the scrut binder to the same offset -- as one of the alt binders, so we have to remove any duplicates here: - rel_slots = nub $ map fromIntegral $ concat (map spread binds) + rel_slots = nub $ map fromIntegral $ concatMap spread binds spread (id, offset) | isFollowableArg (bcIdArgRep id) = [ rel_offset ] | otherwise = [] where rel_offset = trunc16W $ bytesToWords dflags (d - offset) diff --git a/compiler/GHC/HsToCore/PmCheck.hs b/compiler/GHC/HsToCore/PmCheck.hs index 4b1ff614d6..ce81b8b587 100644 --- a/compiler/GHC/HsToCore/PmCheck.hs +++ b/compiler/GHC/HsToCore/PmCheck.hs @@ -59,6 +59,7 @@ import Type import GHC.HsToCore.Utils (isTrueLHsExpr) import Maybes import qualified GHC.LanguageExtensions as LangExt +import MonadUtils (concatMapM) import Control.Monad (when, forM_, zipWithM) import Data.List (elemIndex) @@ -625,7 +626,7 @@ translateMatch _ _ (L _ (XMatch _)) = panic "translateMatch" translateLGRHS :: FamInstEnvs -> SrcSpan -> [LPat GhcTc] -> LGRHS GhcTc (LHsExpr GhcTc) -> DsM GrdTree translateLGRHS fam_insts match_loc pats (L _loc (GRHS _ gs _)) = -- _loc apparently points to the match separator that comes after the guards.. - mkGrdTreeRhs loc_sdoc . concat <$> mapM (translateGuard fam_insts . unLoc) gs + mkGrdTreeRhs loc_sdoc <$> concatMapM (translateGuard fam_insts . unLoc) gs where loc_sdoc | null gs = L match_loc (sep (map ppr pats)) diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs index 77eefc4c7b..c11d4b3e4f 100644 --- a/compiler/GHC/Iface/Load.hs +++ b/compiler/GHC/Iface/Load.hs @@ -751,9 +751,7 @@ loadDecls :: Bool -> [(Fingerprint, IfaceDecl)] -> IfL [(Name,TyThing)] loadDecls ignore_prags ver_decls - = do { thingss <- mapM (loadDecl ignore_prags) ver_decls - ; return (concat thingss) - } + = concatMapM (loadDecl ignore_prags) ver_decls loadDecl :: Bool -- Don't load pragmas into the decl pool -> (Fingerprint, IfaceDecl) diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs index 9686c7105c..666b80cc88 100644 --- a/compiler/GHC/Runtime/Eval.hs +++ b/compiler/GHC/Runtime/Eval.hs @@ -1158,7 +1158,7 @@ findMatchingInstances ty = do ies@(InstEnvs {ie_global = ie_global, ie_local = ie_local}) <- tcGetInstEnvs let allClasses = instEnvClasses ie_global ++ instEnvClasses ie_local - concat <$> mapM (\cls -> do + concatMapM (\cls -> do let (matches, _, _) = lookupInstEnv True ies cls [ty] return matches) allClasses diff --git a/compiler/GHC/Stg/Stats.hs b/compiler/GHC/Stg/Stats.hs index c70184e60b..8a4fa7561b 100644 --- a/compiler/GHC/Stg/Stats.hs +++ b/compiler/GHC/Stg/Stats.hs @@ -78,7 +78,7 @@ showStgStats :: [StgTopBinding] -> String showStgStats prog = "STG Statistics:\n\n" - ++ concat (map showc (Map.toList (gatherStgStats prog))) + ++ concatMap showc (Map.toList (gatherStgStats prog)) where showc (x,n) = (showString (s x) . shows n) "\n" diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 6fe8bc0d35..99a3ae9b70 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1534,7 +1534,7 @@ runPhase (RealPhase LlvmLlc) input_fn dflags then map SysTools.Option $ words llvmOpts else [] - defaultOptions = map SysTools.Option . concat . fmap words . snd + defaultOptions = map SysTools.Option . concatMap words . snd $ unzip (llvmOptions dflags) @@ -1948,7 +1948,7 @@ linkStaticLib dflags o_files dep_packages = do (when output_exists) $ removeFile full_output_fn pkg_cfgs <- getPreloadPackagesAnd dflags dep_packages - archives <- concat <$> mapM (collectArchives dflags) pkg_cfgs + archives <- concatMapM (collectArchives dflags) pkg_cfgs ar <- foldl mappend <$> (Archive <$> mapM loadObj modules) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 709999e06a..4ca05e9657 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1271,12 +1271,12 @@ markUnsafeInfer tcg_env whyUnsafe = do (vcat $ pprErrMsgBagWithLoc whyUnsafe) $+$ (vcat $ badInsts $ tcg_insts tcg_env) ] - badFlags df = concat $ map (badFlag df) unsafeFlagsForInfer + badFlags df = concatMap (badFlag df) unsafeFlagsForInfer badFlag df (str,loc,on,_) | on df = [mkLocMessage SevOutput (loc df) $ text str <+> text "is not allowed in Safe Haskell"] | otherwise = [] - badInsts insts = concat $ map badInst insts + badInsts insts = concatMap badInst insts checkOverlap (NoOverlap _) = False checkOverlap _ = True diff --git a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs index 634e61cb13..c38d998779 100644 --- a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs +++ b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs @@ -21,11 +21,13 @@ module RegAlloc.Graph.ArchBase ( bound, squeese ) where + import GhcPrelude import UniqSet import UniqFM import Unique +import MonadUtils (concatMapM) -- Some basic register classes. @@ -152,7 +154,7 @@ squeese regsOfClass regAlias classN countCs -- | powerset (for lists) powersetL :: [a] -> [[a]] -powersetL = map concat . mapM (\x -> [[],[x]]) +powersetL = concatMapM (\x -> [[],[x]]) -- | powersetLS (list of sets) diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index cf17d149e9..e1bbb467d0 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -719,7 +719,7 @@ sccBlocks blocks entries mcfg = map (fmap node_payload) sccs sccs = stronglyConnCompG g2 getOutEdges :: Instruction instr => [instr] -> [BlockId] - getOutEdges instrs = concat $ map jumpDestsOfInstr instrs + getOutEdges instrs = concatMap jumpDestsOfInstr instrs -- This is truly ugly, but I don't see a good alternative. -- Digraph just has the wrong API. We want to identify nodes diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index d848f76c2e..0f6eff4158 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -301,7 +301,7 @@ tcHsBootSigs :: [(RecFlag, LHsBinds GhcRn)] -> [LSig GhcRn] -> TcM [Id] -- signatures in it. The renamer checked all this tcHsBootSigs binds sigs = do { checkTc (null binds) badBootDeclErr - ; concat <$> mapM (addLocM tc_boot_sig) (filter isTypeLSig sigs) } + ; concatMapM (addLocM tc_boot_sig) (filter isTypeLSig sigs) } where tc_boot_sig (TypeSig _ lnames hs_ty) = mapM f lnames where diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 58af3647c6..60c5bd7d11 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -115,11 +115,11 @@ tcClassSigs :: Name -- Name of the class tcClassSigs clas sigs def_methods = do { traceTc "tcClassSigs 1" (ppr clas) - ; gen_dm_prs <- concat <$> mapM (addLocM tc_gen_sig) gen_sigs + ; gen_dm_prs <- concatMapM (addLocM tc_gen_sig) gen_sigs ; let gen_dm_env :: NameEnv (SrcSpan, Type) gen_dm_env = mkNameEnv gen_dm_prs - ; op_info <- concat <$> mapM (addLocM (tc_sig gen_dm_env)) vanilla_sigs + ; op_info <- concatMapM (addLocM (tc_sig gen_dm_env)) vanilla_sigs ; let op_names = mkNameSet [ n | (n,_,_) <- op_info ] ; sequence_ [ failWithTc (badMethodErr clas n) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index 19d8551f33..950b8572e8 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -256,7 +256,7 @@ exports_from_avail Nothing rdr_env _imports _this_mod exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod = do ie_avails <- accumExports do_litem rdr_items - let final_exports = nubAvails (concat (map snd ie_avails)) -- Combine families + let final_exports = nubAvails (concatMap snd ie_avails) -- Combine families return (Just ie_avails, final_exports) where do_litem :: ExportAccum -> LIE GhcPs diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index ba5216b93a..1cb4ee3dd1 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -2838,7 +2838,7 @@ fvType (CastTy ty _) = fvType ty fvType (CoercionTy {}) = [] fvTypes :: [Type] -> [TyVar] -fvTypes tys = concat (map fvType tys) +fvTypes tys = concatMap fvType tys sizeType :: Type -> Int -- Size of a type: the number of variables and constructors diff --git a/compiler/utils/Digraph.hs b/compiler/utils/Digraph.hs index 49ded1b23f..e7c838508c 100644 --- a/compiler/utils/Digraph.hs +++ b/compiler/utils/Digraph.hs @@ -422,7 +422,7 @@ type IntGraph = G.Graph -- Data.Tree has flatten for Tree, but nothing for Forest preorderF :: Forest a -> [a] -preorderF ts = concat (map flatten ts) +preorderF ts = concatMap flatten ts {- ------------------------------------------------------------ diff --git a/compiler/utils/GraphColor.hs b/compiler/utils/GraphColor.hs index 9ab2ad22af..70c3f7a7b3 100644 --- a/compiler/utils/GraphColor.hs +++ b/compiler/utils/GraphColor.hs @@ -324,7 +324,7 @@ selectColor colors graph u -- the prefs of our neighbors colors_neighbor_prefs = mkUniqSet - $ concat $ map nodePreference nsConflicts + $ concatMap nodePreference nsConflicts -- colors that are still valid for us colors_ok_ex = minusUniqSet colors_avail (nodeExclusions node) |