summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorKrzysztof Gogolewski <krzysztof.gogolewski@tweag.io>2019-03-18 19:22:10 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-03-19 23:28:42 -0400
commit98ff1a5696dd10233229c790eb9642a26e13a9a3 (patch)
tree32414eba50d2c9fbe42607484d0a6be77b532128
parent89a201e88a9313ecff4f5659c38e40136cfc0b76 (diff)
downloadhaskell-98ff1a5696dd10233229c790eb9642a26e13a9a3.tar.gz
Replace nOfThem by replicate
-rw-r--r--compiler/hsSyn/HsUtils.hs2
-rw-r--r--compiler/prelude/TysWiredIn.hs6
-rw-r--r--compiler/typecheck/TcGenDeriv.hs4
-rw-r--r--compiler/typecheck/TcHsType.hs6
-rw-r--r--compiler/typecheck/TcMType.hs4
-rw-r--r--compiler/utils/Util.hs5
6 files changed, 12 insertions, 15 deletions
diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs
index fa8ec1416c..ea3c6aa197 100644
--- a/compiler/hsSyn/HsUtils.hs
+++ b/compiler/hsSyn/HsUtils.hs
@@ -456,7 +456,7 @@ nlNullaryConPat con = noLoc (ConPatIn (noLoc con) (PrefixCon []))
nlWildConPat :: DataCon -> LPat GhcPs
nlWildConPat con = noLoc (ConPatIn (noLoc (getRdrName con))
- (PrefixCon (nOfThem (dataConSourceArity con)
+ (PrefixCon (replicate (dataConSourceArity con)
nlWildPat)))
nlWildPat :: LPat GhcPs
diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs
index aaeb902754..5638b49f5d 100644
--- a/compiler/prelude/TysWiredIn.hs
+++ b/compiler/prelude/TysWiredIn.hs
@@ -870,7 +870,7 @@ mk_tuple Boxed arity = (tycon, tuple_con)
tycon = mkTupleTyCon tc_name tc_binders tc_res_kind tc_arity tuple_con
BoxedTuple flavour
- tc_binders = mkTemplateAnonTyConBinders (nOfThem arity liftedTypeKind)
+ tc_binders = mkTemplateAnonTyConBinders (replicate arity liftedTypeKind)
tc_res_kind = liftedTypeKind
tc_arity = arity
flavour = VanillaAlgTyCon (mkPrelTyConRepName tc_name)
@@ -895,7 +895,7 @@ mk_tuple Unboxed arity = (tycon, tuple_con)
-- See Note [Unboxed tuple RuntimeRep vars] in TyCon
-- Kind: forall (k1:RuntimeRep) (k2:RuntimeRep). TYPE k1 -> TYPE k2 -> #
- tc_binders = mkTemplateTyConBinders (nOfThem arity runtimeRepTy)
+ tc_binders = mkTemplateTyConBinders (replicate arity runtimeRepTy)
(\ks -> map tYPE ks)
tc_res_kind = unboxedTupleKind rr_tys
@@ -1015,7 +1015,7 @@ mk_sum arity = (tycon, sum_cons)
-- Unboxed sums are currently not Typeable due to efficiency concerns. See #13276.
rep_name = Nothing -- Just $ mkPrelTyConRepName tc_name
- tc_binders = mkTemplateTyConBinders (nOfThem arity runtimeRepTy)
+ tc_binders = mkTemplateTyConBinders (replicate arity runtimeRepTy)
(\ks -> map tYPE ks)
tyvars = binderVars tc_binders
diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs
index 4d731db15c..bb4b643e86 100644
--- a/compiler/typecheck/TcGenDeriv.hs
+++ b/compiler/typecheck/TcGenDeriv.hs
@@ -687,9 +687,9 @@ gen_Bounded_binds loc tycon
arity = dataConSourceArity data_con_1
min_bound_1con = mkHsVarBind loc minBound_RDR $
- nlHsVarApps data_con_1_RDR (nOfThem arity minBound_RDR)
+ nlHsVarApps data_con_1_RDR (replicate arity minBound_RDR)
max_bound_1con = mkHsVarBind loc maxBound_RDR $
- nlHsVarApps data_con_1_RDR (nOfThem arity maxBound_RDR)
+ nlHsVarApps data_con_1_RDR (replicate arity maxBound_RDR)
{-
************************************************************************
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 489a35c455..e0bf2552d3 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -889,9 +889,9 @@ tupKindSort_maybe k
tc_tuple :: HsType GhcRn -> TcTyMode -> TupleSort -> [LHsType GhcRn] -> TcKind -> TcM TcType
tc_tuple rn_ty mode tup_sort tys exp_kind
= do { arg_kinds <- case tup_sort of
- BoxedTuple -> return (nOfThem arity liftedTypeKind)
- UnboxedTuple -> mapM (\_ -> newOpenTypeKind) tys
- ConstraintTuple -> return (nOfThem arity constraintKind)
+ BoxedTuple -> return (replicate arity liftedTypeKind)
+ UnboxedTuple -> replicateM arity newOpenTypeKind
+ ConstraintTuple -> return (replicate arity constraintKind)
; tau_tys <- zipWithM (tc_lhs_type mode) tys arg_kinds
; finish_tuple rn_ty tup_sort tau_tys arg_kinds exp_kind }
where
diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs
index d6a753f76b..e46cb50d57 100644
--- a/compiler/typecheck/TcMType.hs
+++ b/compiler/typecheck/TcMType.hs
@@ -148,7 +148,7 @@ newMetaKindVar
; return (mkTyVarTy kv) }
newMetaKindVars :: Int -> TcM [TcKind]
-newMetaKindVars n = mapM (\ _ -> newMetaKindVar) (nOfThem n ())
+newMetaKindVars n = replicateM n newMetaKindVar
{-
************************************************************************
@@ -944,7 +944,7 @@ newFlexiTyVarTy kind = do
return (mkTyVarTy tc_tyvar)
newFlexiTyVarTys :: Int -> Kind -> TcM [TcType]
-newFlexiTyVarTys n kind = mapM newFlexiTyVarTy (nOfThem n kind)
+newFlexiTyVarTys n kind = replicateM n (newFlexiTyVarTy kind)
newOpenTypeKind :: TcM TcKind
newOpenTypeKind
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 673088159f..9e67a43bf5 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -26,7 +26,7 @@ module Util (
mapFst, mapSnd, chkAppend,
mapAndUnzip, mapAndUnzip3, mapAccumL2,
- nOfThem, filterOut, partitionWith,
+ filterOut, partitionWith,
dropWhileEndLE, spanEnd, last2, lastMaybe,
@@ -458,9 +458,6 @@ mapAccumL2 f s1 s2 xs = (s1', s2', ys)
(s1', s2', y) -> ((s1', s2'), y))
(s1, s2) xs
-nOfThem :: Int -> a -> [a]
-nOfThem n thing = replicate n thing
-
-- | @atLength atLen atEnd ls n@ unravels list @ls@ to position @n@. Precisely:
--
-- @