diff options
Diffstat (limited to 'compiler/GHC/Tc')
-rw-r--r-- | compiler/GHC/Tc/Errors.hs | 20 | ||||
-rw-r--r-- | compiler/GHC/Tc/Errors/Hole.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Errors/Hole/FitTypes.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Annotation.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Expr.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Pat.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Instance/Family.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Instance/FunDeps.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Tc/Solver.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/TyCl/PatSyn.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Tc/Types/Origin.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/TcMType.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Validity.hs | 6 |
13 files changed, 32 insertions, 32 deletions
diff --git a/compiler/GHC/Tc/Errors.hs b/compiler/GHC/Tc/Errors.hs index ae08f78443..be6524d1ba 100644 --- a/compiler/GHC/Tc/Errors.hs +++ b/compiler/GHC/Tc/Errors.hs @@ -477,7 +477,7 @@ warnRedundantConstraints ctxt env info ev_vars = do { msg <- mkErrorReport ctxt env (important doc) ; reportWarning (Reason Opt_WarnRedundantConstraints) msg } where - doc = text "Redundant constraint" <> plural redundant_evs <> colon + doc = text "Redundant" <+> plural "constraint" redundant_evs <> colon <+> pprEvVarTheta redundant_evs redundant_evs = @@ -1249,7 +1249,7 @@ mkIPErr ctxt cts givens = getUserGivens ctxt msg | null givens = addArising orig $ - sep [ text "Unbound implicit parameter" <> plural cts + sep [ text "Unbound implicit" <+> plural "parameter" cts , nest 2 (pprParendTheta preds) ] | otherwise = couldNotDeduce givens (preds, orig) @@ -1552,7 +1552,7 @@ mkTyVarEqErr' dflags ctxt report ct oriented tv1 ty2 , let esc_skols = filter (`elemVarSet` (tyCoVarsOfType ty2)) skols , not (null esc_skols) = do { let msg = important $ misMatchMsg ct oriented ty1 ty2 - esc_doc = sep [ text "because" <+> what <+> text "variable" <> plural esc_skols + esc_doc = sep [ text "because" <+> what <+> plural "variable" esc_skols <+> pprQuotedList esc_skols , text "would escape" <+> if isSingleton esc_skols then text "its scope" @@ -2361,7 +2361,7 @@ mk_dict_err ctxt@(CEC {cec_encl = implics}) (ct, (matches, unifiers, unsafe_over = vcat [ ppWhen lead_with_ambig $ text "Probable fix: use a type annotation to specify what" <+> pprQuotedList ambig_tvs <+> text "should be." - , text "These potential instance" <> plural unifiers + , text "These potential" <+> plural "instance" unifiers <+> text "exist:"] mb_patsyn_prov :: Maybe SDoc @@ -2737,8 +2737,8 @@ mkAmbigMsg prepend_msg ct msg | any isRuntimeUnkSkol ambig_kvs -- See Note [Runtime skolems] || any isRuntimeUnkSkol ambig_tvs - = vcat [ text "Cannot resolve unknown runtime type" - <> plural ambig_tvs <+> pprQuotedList ambig_tvs + = vcat [ text "Cannot resolve unknown runtime" + <+> plural "type" ambig_tvs <+> pprQuotedList ambig_tvs , text "Use :print or :force to determine these types"] | not (null ambig_tvs) @@ -2749,11 +2749,11 @@ mkAmbigMsg prepend_msg ct pp_ambig what tkvs | prepend_msg -- "Ambiguous type variable 't0'" - = text "Ambiguous" <+> what <+> text "variable" - <> plural tkvs <+> pprQuotedList tkvs + = text "Ambiguous" <+> what <+> plural "variable" tkvs + <+> pprQuotedList tkvs | otherwise -- "The type variable 't0' is ambiguous" - = text "The" <+> what <+> text "variable" <> plural tkvs + = text "The" <+> what <+> plural "variable" tkvs <+> pprQuotedList tkvs <+> isOrAre tkvs <+> text "ambiguous" pprSkols :: ReportErrCtxt -> [TcTyVar] -> SDoc @@ -2940,7 +2940,7 @@ warnDefaulting wanteds default_ty (loc, ppr_wanteds) = pprWithArising tidy_wanteds warn_msg = hang (hsep [ text "Defaulting the following" - , text "constraint" <> plural tidy_wanteds + , plural "constraint" tidy_wanteds , text "to type" , quotes (ppr default_ty) ]) 2 diff --git a/compiler/GHC/Tc/Errors/Hole.hs b/compiler/GHC/Tc/Errors/Hole.hs index 771765901c..4e7b02bad0 100644 --- a/compiler/GHC/Tc/Errors/Hole.hs +++ b/compiler/GHC/Tc/Errors/Hole.hs @@ -492,7 +492,7 @@ pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (HoleFit {..}) = Just (_, unfunned) -> unwrapTypeVars unfunned _ -> [] where (vars, unforalled) = splitForAllVarBndrs t - holeVs = sep $ map (parens . (text "_" <+> dcolon <+>) . ppr) hfMatches + holeVs = sep $ map (parens . ((text "_" <+> dcolon) <+>) . ppr) hfMatches holeDisp = if sMs then holeVs else sep $ replicate (length hfMatches) $ text "_" occDisp = pprPrefixOcc name diff --git a/compiler/GHC/Tc/Errors/Hole/FitTypes.hs b/compiler/GHC/Tc/Errors/Hole/FitTypes.hs index 8aabc615ce..bade5a28f9 100644 --- a/compiler/GHC/Tc/Errors/Hole/FitTypes.hs +++ b/compiler/GHC/Tc/Errors/Hole/FitTypes.hs @@ -98,7 +98,7 @@ instance Outputable HoleFit where ppr (HoleFit _ cand ty _ _ mtchs _) = hang (name <+> holes) 2 (text "where" <+> name <+> dcolon <+> (ppr ty)) where name = ppr $ getName cand - holes = sep $ map (parens . (text "_" <+> dcolon <+>) . ppr) mtchs + holes = sep $ map (parens . ((text "_" <+> dcolon) <+>) . ppr) mtchs -- We compare HoleFits by their name instead of their Id, since we don't -- want our tests to be affected by the non-determinism of `nonDetCmpVar`, diff --git a/compiler/GHC/Tc/Gen/Annotation.hs b/compiler/GHC/Tc/Gen/Annotation.hs index ef7168076f..98bf1a04bc 100644 --- a/compiler/GHC/Tc/Gen/Annotation.hs +++ b/compiler/GHC/Tc/Gen/Annotation.hs @@ -39,7 +39,7 @@ warnAnns :: [LAnnDecl GhcRn] -> TcM [Annotation] warnAnns [] = return [] warnAnns anns@(L loc _ : _) = do { setSrcSpan loc $ addWarnTc NoReason $ - (text "Ignoring ANN annotation" <> plural anns <> comma + (text "Ignoring ANN" <+> plural "annotation" anns <> comma <+> text "because this is a stage-1 compiler without -fexternal-interpreter or doesn't support GHCi") ; return [] } diff --git a/compiler/GHC/Tc/Gen/Expr.hs b/compiler/GHC/Tc/Gen/Expr.hs index 70201773b9..4d4e33edae 100644 --- a/compiler/GHC/Tc/Gen/Expr.hs +++ b/compiler/GHC/Tc/Gen/Expr.hs @@ -2657,8 +2657,8 @@ provided. badFieldTypes :: [(FieldLabelString,TcType)] -> SDoc badFieldTypes prs - = hang (text "Record update for insufficiently polymorphic field" - <> plural prs <> colon) + = hang (text "Record update for insufficiently polymorphic" + <+> plural "field" prs <> colon) 2 (vcat [ ppr f <+> dcolon <+> ppr ty | (f,ty) <- prs ]) badFieldsUpd diff --git a/compiler/GHC/Tc/Gen/Pat.hs b/compiler/GHC/Tc/Gen/Pat.hs index 2ae1f1cfb9..b7acc7e879 100644 --- a/compiler/GHC/Tc/Gen/Pat.hs +++ b/compiler/GHC/Tc/Gen/Pat.hs @@ -737,7 +737,7 @@ tcPatSig in_pat_bind sig res_ty patBindSigErr :: [(Name,TcTyVar)] -> SDoc patBindSigErr sig_tvs - = hang (text "You cannot bind scoped type variable" <> plural sig_tvs + = hang (text "You cannot bind scoped type" <+> plural "variable" sig_tvs <+> pprQuotedList (map fst sig_tvs)) 2 (text "in a pattern binding signature") diff --git a/compiler/GHC/Tc/Instance/Family.hs b/compiler/GHC/Tc/Instance/Family.hs index 68c894f2e4..c6d3010ff1 100644 --- a/compiler/GHC/Tc/Instance/Family.hs +++ b/compiler/GHC/Tc/Instance/Family.hs @@ -990,8 +990,8 @@ reportUnusedInjectiveVarsErr fam_tc tvs has_kinds undec_inst tyfamEqn (tyfamEqn :| []) in addErrAt loc (pprWithExplicitKindsWhen has_kinds doc) where - herald = sep [ what <+> text "variable" <> - pluralVarSet tvs <+> pprVarSet tvs (pprQuotedList . scopedSort) + herald = sep [ what <+> pluralVarSet "variable" tvs + <+> pprVarSet tvs (pprQuotedList . scopedSort) , text "cannot be inferred from the right-hand side." ] $$ extra diff --git a/compiler/GHC/Tc/Instance/FunDeps.hs b/compiler/GHC/Tc/Instance/FunDeps.hs index 40344af9ed..357c4fc5a2 100644 --- a/compiler/GHC/Tc/Instance/FunDeps.hs +++ b/compiler/GHC/Tc/Instance/FunDeps.hs @@ -414,14 +414,14 @@ checkInstCoverage be_liberal clas theta inst_taus <+> quotes (ppr clas) , nest 2 $ text "for functional dependency:" <+> quotes (pprFunDep fd) ] - , sep [ text "Reason: lhs type"<>plural ls <+> pprQuotedList ls + , sep [ text "Reason: lhs" <+> plural "type" ls <+> pprQuotedList ls , nest 2 $ (if isSingleton ls then text "does not" else text "do not jointly") - <+> text "determine rhs type"<>plural rs + <+> text "determine rhs" <+> plural "type" rs <+> pprQuotedList rs ] - , text "Un-determined variable" <> pluralVarSet undet_set <> colon + , text "Un-determined" <+> pluralVarSet "variable" undet_set <> colon <+> pprVarSet undet_set (pprWithCommas ppr) , ppWhen (not be_liberal && and (isEmptyVarSet <$> liberal_undet_tvs)) $ diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs index c060eac638..4d88056665 100644 --- a/compiler/GHC/Tc/Solver.hs +++ b/compiler/GHC/Tc/Solver.hs @@ -1165,8 +1165,8 @@ decideMonoTyVars infer_mode name_taus psigs candidates pp_bndrs = pprWithCommas (quotes . ppr . fst) name_taus mr_msg = - hang (sep [ text "The Monomorphism Restriction applies to the binding" - <> plural name_taus + hang (sep [ text "The Monomorphism Restriction applies to the" + <+> plural "binding" name_taus , text "for" <+> pp_bndrs ]) 2 (hsep [ text "Consider giving" , text (if isSingleton name_taus then "it" else "them") diff --git a/compiler/GHC/Tc/TyCl/PatSyn.hs b/compiler/GHC/Tc/TyCl/PatSyn.hs index 797ff2f594..02949968fe 100644 --- a/compiler/GHC/Tc/TyCl/PatSyn.hs +++ b/compiler/GHC/Tc/TyCl/PatSyn.hs @@ -227,8 +227,8 @@ dependentArgErr (arg, bad_cos) , hang (text "Pattern-bound variable") 2 (ppr arg <+> dcolon <+> ppr (idType arg)) , nest 2 $ - hang (text "has a type that mentions pattern-bound coercion" - <> plural bad_co_list <> colon) + hang (text "has a type that mentions pattern-bound" + <+> plural "coercion" bad_co_list <> colon) 2 (pprWithCommas ppr bad_co_list) , text "Hint: use -fprint-explicit-coercions to see the coercions" , text "Probable fix: add a pattern signature" ] @@ -368,7 +368,7 @@ tcCheckPatSynDecl psb@PSB{ psb_id = lname@(L _ name), psb_args = details ; checkTc (null bad_tvs) $ hang (sep [ text "The result type of the signature for" <+> quotes (ppr name) <> comma , text "namely" <+> quotes (ppr pat_ty) ]) - 2 (text "mentions existential type variable" <> plural bad_tvs + 2 (text "mentions existential type" <+> plural "variable" bad_tvs <+> pprQuotedList bad_tvs) -- See Note [The pattern-synonym signature splitting rule] in GHC.Tc.Gen.Sig diff --git a/compiler/GHC/Tc/Types/Origin.hs b/compiler/GHC/Tc/Types/Origin.hs index 86427853de..e86bdf4c19 100644 --- a/compiler/GHC/Tc/Types/Origin.hs +++ b/compiler/GHC/Tc/Types/Origin.hs @@ -243,7 +243,7 @@ pprSkolInfo :: SkolemInfo -> SDoc pprSkolInfo (SigSkol cx ty _) = pprSigSkolInfo cx ty pprSkolInfo (SigTypeSkol cx) = pprUserTypeCtxt cx pprSkolInfo (ForAllSkol doc) = quotes doc -pprSkolInfo (IPSkol ips) = text "the implicit-parameter binding" <> plural ips <+> text "for" +pprSkolInfo (IPSkol ips) = text "the implicit-parameter" <+> plural "binding" ips <+> text "for" <+> pprWithCommas ppr ips pprSkolInfo (DerivSkol pred) = text "the deriving clause for" <+> quotes (ppr pred) pprSkolInfo InstSkol = text "the instance declaration" @@ -254,7 +254,7 @@ pprSkolInfo (RuleSkol name) = text "the RULE" <+> pprRuleName name pprSkolInfo ArrowSkol = text "an arrow form" pprSkolInfo (PatSkol cl mc) = sep [ pprPatSkolInfo cl , text "in" <+> pprMatchContext mc ] -pprSkolInfo (InferSkol ids) = hang (text "the inferred type" <> plural ids <+> text "of") +pprSkolInfo (InferSkol ids) = hang (text "the inferred" <+> plural "type" ids <+> text "of") 2 (vcat [ ppr name <+> dcolon <+> ppr ty | (name,ty) <- ids ]) pprSkolInfo (UnifyForAllSkol ty) = text "the type" <+> ppr ty diff --git a/compiler/GHC/Tc/Utils/TcMType.hs b/compiler/GHC/Tc/Utils/TcMType.hs index d37b37efe3..27460b0882 100644 --- a/compiler/GHC/Tc/Utils/TcMType.hs +++ b/compiler/GHC/Tc/Utils/TcMType.hs @@ -2396,7 +2396,7 @@ naughtyQuantification orig_ty tv escapees orig_ty' = tidyType env orig_ty1 ppr_tidied = pprTyVars . map (tidyTyCoVarOcc env) doc = pprWithExplicitKindsWhen True $ - vcat [ sep [ text "Cannot generalise type; skolem" <> plural escapees' + vcat [ sep [ text "Cannot generalise type;" <+> plural "skolem" escapees' , quotes $ ppr_tidied escapees' , text "would escape" <+> itsOrTheir escapees' <+> text "scope" ] diff --git a/compiler/GHC/Tc/Validity.hs b/compiler/GHC/Tc/Validity.hs index 6e44a6c399..b5ba5feec9 100644 --- a/compiler/GHC/Tc/Validity.hs +++ b/compiler/GHC/Tc/Validity.hs @@ -1424,7 +1424,7 @@ constraintSynErr env kind dupPredWarn :: TidyEnv -> [NE.NonEmpty PredType] -> (TidyEnv, SDoc) dupPredWarn env dups = ( env - , text "Duplicate constraint" <> plural primaryDups <> text ":" + , text "Duplicate" <+> plural "constraint" primaryDups <> text ":" <+> pprWithCommas (ppr_tidy env) primaryDups ) where primaryDups = map NE.head dups @@ -1955,7 +1955,7 @@ smallerMsg what inst_head noMoreMsg :: [TcTyVar] -> SDoc -> SDoc -> SDoc noMoreMsg tvs what inst_head - = vcat [ hang (text "Variable" <> plural tvs1 <+> quotes (pprWithCommas ppr tvs1) + = vcat [ hang (plural "Variable" tvs1 <+> quotes (pprWithCommas ppr tvs1) <+> occurs <+> text "more often") 2 (sep [ text "in the" <+> what , text "than in the instance head" <+> quotes inst_head ]) @@ -2196,7 +2196,7 @@ checkFamPatBinders fam_tc qtvs pats rhs check_tvs tvs what what2 = unless (null tvs) $ addErrAt (getSrcSpan (head tvs)) $ - hang (text "Type variable" <> plural tvs <+> pprQuotedList tvs + hang (text "Type" <+> plural "variable" tvs <+> pprQuotedList tvs <+> isOrAre tvs <+> what <> comma) 2 (vcat [ text "but not" <+> what2 <+> text "the family instance" , mk_extra tvs ]) |