diff options
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/deSugar/DsMonad.lhs | 2 | ||||
-rw-r--r-- | compiler/parser/Parser.y.pp | 10 | ||||
-rw-r--r-- | compiler/parser/RdrHsSyn.lhs | 18 | ||||
-rw-r--r-- | compiler/rename/RnBinds.lhs | 6 | ||||
-rw-r--r-- | compiler/rename/RnEnv.lhs | 8 | ||||
-rw-r--r-- | compiler/rename/RnExpr.lhs | 12 | ||||
-rw-r--r-- | compiler/rename/RnNames.lhs | 4 | ||||
-rw-r--r-- | compiler/rename/RnPat.lhs | 8 | ||||
-rw-r--r-- | compiler/rename/RnSource.lhs | 2 | ||||
-rw-r--r-- | compiler/rename/RnTypes.lhs | 12 | ||||
-rw-r--r-- | compiler/typecheck/TcDeriv.lhs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcErrors.lhs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcForeign.lhs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcHsType.lhs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcInstDcls.lhs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcPat.lhs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcTyClsDecls.lhs | 16 | ||||
-rw-r--r-- | compiler/typecheck/TcUnify.lhs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcValidity.lhs | 30 |
19 files changed, 75 insertions, 75 deletions
diff --git a/compiler/deSugar/DsMonad.lhs b/compiler/deSugar/DsMonad.lhs index bc0e2e14dc..dead3983e0 100644 --- a/compiler/deSugar/DsMonad.lhs +++ b/compiler/deSugar/DsMonad.lhs @@ -241,7 +241,7 @@ initDs hsc_env mod rdr_env type_env thing_inside _ -> pprPgmError "Unable to use Data Parallel Haskell (DPH):" err } } - paErr = ptext (sLit "To use -XParallelArrays,") <+> specBackend $$ hint1 $$ hint2 + paErr = ptext (sLit "To use ParallelArrays,") <+> specBackend $$ hint1 $$ hint2 veErr = ptext (sLit "To use -fvectorise,") <+> specBackend $$ hint1 $$ hint2 specBackend = ptext (sLit "you must specify a DPH backend package") hint1 = ptext (sLit "Look for packages named 'dph-lifted-*' with 'ghc-pkg'") diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index bd2bd0b922..f30072c5d0 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -1965,8 +1965,8 @@ tyvarop :: { Located RdrName } tyvarop : '`' tyvarid '`' { LL (unLoc $2) } | '.' {% parseErrorSDoc (getLoc $1) (vcat [ptext (sLit "Illegal symbol '.' in type"), - ptext (sLit "Perhaps you intended -XRankNTypes or similar flag"), - ptext (sLit "to enable explicit-forall syntax: forall <tvs>. <type>")]) + ptext (sLit "Perhaps you intended to use RankNTypes or a similar language"), + ptext (sLit "extension to enable explicit-forall syntax: forall <tvs>. <type>")]) } tyvarid :: { Located RdrName } @@ -2218,7 +2218,7 @@ hintMultiWayIf :: SrcSpan -> P () hintMultiWayIf span = do mwiEnabled <- liftM ((Opt_MultiWayIf `xopt`) . dflags) getPState unless mwiEnabled $ parseErrorSDoc span $ - text "Multi-way if-expressions need -XMultiWayIf turned on" + text "Multi-way if-expressions need MultiWayIf turned on" -- Hint about explicit-forall, assuming UnicodeSyntax is on hintExplicitForall :: SrcSpan -> P () @@ -2227,7 +2227,7 @@ hintExplicitForall span = do rulePrag <- extension inRulePrag unless (forall || rulePrag) $ parseErrorSDoc span $ vcat [ text "Illegal symbol '\x2200' in type" -- U+2200 FOR ALL - , text "Perhaps you intended -XRankNTypes or similar flag" - , text "to enable explicit-forall syntax: \x2200 <tvs>. <type>" + , text "Perhaps you intended to use RankNTypes or a similar language" + , text "extension to enable explicit-forall syntax: \x2200 <tvs>. <type>" ] } diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index fb5f43f5e9..1f3274997c 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -221,7 +221,7 @@ mkTyLit l = if allowed then return (HsTyLit `fmap` l) else parseErrorSDoc (getLoc l) - (text "Illegal literal in type (use -XDataKinds to enable):" <+> + (text "Illegal literal in type (use DataKinds to enable):" <+> ppr l) @@ -432,7 +432,7 @@ tyConToDataCon loc tc where msg = text "Not a data constructor:" <+> quotes (ppr tc) extra | tc == forall_tv_RDR - = text "Perhaps you intended to use -XExistentialQuantification" + = text "Perhaps you intended to use ExistentialQuantification" | otherwise = empty \end{code} @@ -484,7 +484,7 @@ checkDatatypeContext (Just (L loc c)) = do allowed <- extension datatypeContextsEnabled unless allowed $ parseErrorSDoc loc - (text "Illegal datatype context (use -XDatatypeContexts):" <+> + (text "Illegal datatype context (use DatatypeContexts):" <+> pprHsContext c) checkRecordSyntax :: Outputable a => Located a -> P (Located a) @@ -493,7 +493,7 @@ checkRecordSyntax lr@(L loc r) if allowed then return lr else parseErrorSDoc loc - (text "Illegal record syntax (use -XTraditionalRecordSyntax):" <+> + (text "Illegal record syntax (use TraditionalRecordSyntax):" <+> ppr r) checkTyClHdr :: LHsType RdrName @@ -585,7 +585,7 @@ checkAPat msg loc e0 = do | bang == bang_RDR -> do { bang_on <- extension bangPatEnabled ; if bang_on then checkLPat msg e >>= (return . BangPat) - else parseErrorSDoc loc (text "Illegal bang-pattern (use -XBangPatterns):" $$ ppr e0) } + else parseErrorSDoc loc (text "Illegal bang-pattern (use BangPatterns):" $$ ppr e0) } ELazyPat e -> checkLPat msg e >>= (return . LazyPat) EAsPat n e -> checkLPat msg e >>= (return . AsPat n) @@ -713,9 +713,9 @@ checkValSig lhs@(L l _) ty $$ text hint) where hint = if foreign_RDR `looks_like` lhs - then "Perhaps you meant to use -XForeignFunctionInterface?" + then "Perhaps you meant to use ForeignFunctionInterface?" else if default_RDR `looks_like` lhs - then "Perhaps you meant to use -XDefaultSignatures?" + then "Perhaps you meant to use DefaultSignatures?" else "Should be of form <variable> :: <type>" -- A common error is to forget the ForeignFunctionInterface flag -- so check for that, and suggest. cf Trac #3805 @@ -740,7 +740,7 @@ checkDoAndIfThenElse guardExpr semiThen thenExpr semiElse elseExpr parseErrorSDoc (combineLocs guardExpr elseExpr) (text "Unexpected semi-colons in conditional:" $$ nest 4 expr - $$ text "Perhaps you meant to use -XDoAndIfThenElse?") + $$ text "Perhaps you meant to use DoAndIfThenElse?") | otherwise = return () where pprOptSemi True = semi pprOptSemi False = empty @@ -1081,7 +1081,7 @@ mkTypeImpExp name = if allowed then return (fmap (`setRdrNameSpace` tcClsName) name) else parseErrorSDoc (getLoc name) - (text "Illegal keyword 'type' (use -XExplicitNamespaces to enable)") + (text "Illegal keyword 'type' (use ExplicitNamespaces to enable)") \end{code} ----------------------------------------------------------------------------- diff --git a/compiler/rename/RnBinds.lhs b/compiler/rename/RnBinds.lhs index e56f721583..81e9316fa9 100644 --- a/compiler/rename/RnBinds.lhs +++ b/compiler/rename/RnBinds.lhs @@ -812,7 +812,7 @@ rnMatch' ctxt rnBody match@(Match pats maybe_rhs_sig grhss) emptyCaseErr :: HsMatchContext Name -> SDoc emptyCaseErr ctxt = hang (ptext (sLit "Empty list of alterantives in") <+> pp_ctxt) - 2 (ptext (sLit "Use -XEmptyCase to allow this")) + 2 (ptext (sLit "Use EmptyCase to allow this")) where pp_ctxt = case ctxt of CaseAlt -> ptext (sLit "case expression") @@ -898,7 +898,7 @@ misplacedSigErr (L loc sig) defaultSigErr :: Sig RdrName -> SDoc defaultSigErr sig = vcat [ hang (ptext (sLit "Unexpected default signature:")) 2 (ppr sig) - , ptext (sLit "Use -XDefaultSignatures to enable default signatures") ] + , ptext (sLit "Use DefaultSignatures to enable default signatures") ] methodBindErr :: HsBindLR RdrName RdrName -> SDoc methodBindErr mbind @@ -912,7 +912,7 @@ bindsInHsBootFile mbinds nonStdGuardErr :: Outputable body => [LStmtLR Name Name body] -> SDoc nonStdGuardErr guards - = hang (ptext (sLit "accepting non-standard pattern guards (use -XPatternGuards to suppress this message)")) + = hang (ptext (sLit "accepting non-standard pattern guards (use PatternGuards to suppress this message)")) 4 (interpp'SP guards) unusedPatBindWarn :: HsBind Name -> SDoc diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index 73475daa5d..7eb896c883 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -581,7 +581,7 @@ lookup_demoted rdr_name = reportUnboundName rdr_name where - suggest_dk = ptext (sLit "A data constructor of that name is in scope; did you mean -XDataKinds?") + suggest_dk = ptext (sLit "A data constructor of that name is in scope; did you mean DataKinds?") \end{code} Note [Demotion] @@ -1638,7 +1638,7 @@ shadowedNameWarn occ shadowed_locs perhapsForallMsg :: SDoc perhapsForallMsg - = vcat [ ptext (sLit "Perhaps you intended to use -XExplicitForAll or similar flag") + = vcat [ ptext (sLit "Perhaps you intended to use ExplicitForAll or similar flag") , ptext (sLit "to enable explicit-forall syntax: forall <tvs>. <type>")] unknownSubordinateErr :: SDoc -> RdrName -> SDoc @@ -1664,7 +1664,7 @@ dupNamesErr get_loc names kindSigErr :: Outputable a => a -> SDoc kindSigErr thing = hang (ptext (sLit "Illegal kind signature for") <+> quotes (ppr thing)) - 2 (ptext (sLit "Perhaps you intended to use -XKindSignatures")) + 2 (ptext (sLit "Perhaps you intended to use KindSignatures")) badQualBndrErr :: RdrName -> SDoc badQualBndrErr rdr_name @@ -1673,7 +1673,7 @@ badQualBndrErr rdr_name opDeclErr :: RdrName -> SDoc opDeclErr n = hang (ptext (sLit "Illegal declaration of a type or class operator") <+> quotes (ppr n)) - 2 (ptext (sLit "Use -XTypeOperators to declare operators in type and declarations")) + 2 (ptext (sLit "Use TypeOperators to declare operators in type and declarations")) checkTupSize :: Int -> RnM () checkTupSize tup_size diff --git a/compiler/rename/RnExpr.lhs b/compiler/rename/RnExpr.lhs index 23501e3e1a..e871a4f0b8 100644 --- a/compiler/rename/RnExpr.lhs +++ b/compiler/rename/RnExpr.lhs @@ -176,7 +176,7 @@ rnExpr e@(HsBracket br_body) thEnabled <- xoptM Opt_TemplateHaskell unless thEnabled $ failWith ( vcat [ ptext (sLit "Syntax error on") <+> ppr e - , ptext (sLit "Perhaps you intended to use -XTemplateHaskell") ] ) + , ptext (sLit "Perhaps you intended to use TemplateHaskell") ] ) checkTH e "bracket" (body', fvs_e) <- rnBracket br_body return (HsBracket body', fvs_e) @@ -1371,7 +1371,7 @@ okDoStmt dflags ctxt stmt RecStmt {} | Opt_RecursiveDo `xopt` dflags -> isOK | ArrowExpr <- ctxt -> isOK -- Arrows allows 'rec' - | otherwise -> Just (ptext (sLit "Use -XRecursiveDo")) + | otherwise -> Just (ptext (sLit "Use RecursiveDo")) BindStmt {} -> isOK LetStmt {} -> isOK BodyStmt {} -> isOK @@ -1385,10 +1385,10 @@ okCompStmt dflags _ stmt BodyStmt {} -> isOK ParStmt {} | Opt_ParallelListComp `xopt` dflags -> isOK - | otherwise -> Just (ptext (sLit "Use -XParallelListComp")) + | otherwise -> Just (ptext (sLit "Use ParallelListComp")) TransStmt {} | Opt_TransformListComp `xopt` dflags -> isOK - | otherwise -> Just (ptext (sLit "Use -XTransformListComp")) + | otherwise -> Just (ptext (sLit "Use TransformListComp")) RecStmt {} -> notOK LastStmt {} -> notOK -- Should not happen (dealt with by checkLastStmt) @@ -1400,7 +1400,7 @@ okPArrStmt dflags _ stmt BodyStmt {} -> isOK ParStmt {} | Opt_ParallelListComp `xopt` dflags -> isOK - | otherwise -> Just (ptext (sLit "Use -XParallelListComp")) + | otherwise -> Just (ptext (sLit "Use ParallelListComp")) TransStmt {} -> notOK RecStmt {} -> notOK LastStmt {} -> notOK -- Should not happen (dealt with by checkLastStmt) @@ -1411,7 +1411,7 @@ checkTupleSection args = do { tuple_section <- xoptM Opt_TupleSections ; checkErr (all tupArgPresent args || tuple_section) msg } where - msg = ptext (sLit "Illegal tuple section: use -XTupleSections") + msg = ptext (sLit "Illegal tuple section: use TupleSections") --------- sectionErr :: HsExpr RdrName -> SDoc diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs index cdd53d199b..dcf9c4ff35 100644 --- a/compiler/rename/RnNames.lhs +++ b/compiler/rename/RnNames.lhs @@ -207,7 +207,7 @@ rnImportDecl this_mod when (mod_safe && not (safeImportsOn dflags)) $ addErrAt loc (ptext (sLit "safe import can't be used as Safe Haskell isn't on!") $+$ ptext (sLit $ "please enable Safe Haskell through either" - ++ "-XSafe, -XTruswrothy or -XUnsafe")) + ++ "Safe, Trustwrothy or Unsafe")) let imp_mod = mi_module iface warns = mi_warns iface @@ -1707,5 +1707,5 @@ moduleWarn mod (DeprecatedTxt txt) packageImportErr :: SDoc packageImportErr - = ptext (sLit "Package-qualified imports are not enabled; use -XPackageImports") + = ptext (sLit "Package-qualified imports are not enabled; use PackageImports") \end{code} diff --git a/compiler/rename/RnPat.lhs b/compiler/rename/RnPat.lhs index 9488f91ddd..88b09c328a 100644 --- a/compiler/rename/RnPat.lhs +++ b/compiler/rename/RnPat.lhs @@ -614,14 +614,14 @@ getFieldIds flds = map (unLoc . hsRecFieldId) flds needFlagDotDot :: HsRecFieldContext -> SDoc needFlagDotDot ctxt = vcat [ptext (sLit "Illegal `..' in record") <+> pprRFC ctxt, - ptext (sLit "Use -XRecordWildCards to permit this")] + ptext (sLit "Use RecordWildCards to permit this")] badDotDot :: HsRecFieldContext -> SDoc badDotDot ctxt = ptext (sLit "You cannot use `..' in a record") <+> pprRFC ctxt badPun :: Located RdrName -> SDoc badPun fld = vcat [ptext (sLit "Illegal use of punning for field") <+> quotes (ppr fld), - ptext (sLit "Use -XNamedFieldPuns to permit this")] + ptext (sLit "Use NamedFieldPuns to permit this")] dupFieldErr :: HsRecFieldContext -> [RdrName] -> SDoc dupFieldErr ctxt dups @@ -684,7 +684,7 @@ rnOverLit origLit patSigErr :: Outputable a => a -> SDoc patSigErr ty = (ptext (sLit "Illegal signature in pattern:") <+> ppr ty) - $$ nest 4 (ptext (sLit "Use -XScopedTypeVariables to permit it")) + $$ nest 4 (ptext (sLit "Use ScopedTypeVariables to permit it")) bogusCharError :: Char -> SDoc bogusCharError c @@ -692,5 +692,5 @@ bogusCharError c badViewPat :: Pat RdrName -> SDoc badViewPat pat = vcat [ptext (sLit "Illegal view pattern: ") <+> ppr pat, - ptext (sLit "Use -XViewPatterns to enable view patterns")] + ptext (sLit "Use ViewPatterns to enable view patterns")] \end{code} diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs index e1236cac10..6a80e0582f 100644 --- a/compiler/rename/RnSource.lhs +++ b/compiler/rename/RnSource.lhs @@ -635,7 +635,7 @@ rnSrcDerivDecl (DerivDecl ty) standaloneDerivErr :: SDoc standaloneDerivErr = hang (ptext (sLit "Illegal standalone deriving declaration")) - 2 (ptext (sLit "Use -XStandaloneDeriving to enable this extension")) + 2 (ptext (sLit "Use StandaloneDeriving to enable this extension")) \end{code} %********************************************************* diff --git a/compiler/rename/RnTypes.lhs b/compiler/rename/RnTypes.lhs index c13ea336e4..368d9756c5 100644 --- a/compiler/rename/RnTypes.lhs +++ b/compiler/rename/RnTypes.lhs @@ -451,7 +451,7 @@ badKindBndrs :: HsDocContext -> [RdrName] -> SDoc badKindBndrs doc kvs = vcat [ hang (ptext (sLit "Unexpected kind variable") <> plural kvs <+> pprQuotedList kvs) - 2 (ptext (sLit "Perhaps you intended to use -XPolyKinds")) + 2 (ptext (sLit "Perhaps you intended to use PolyKinds")) , docOfHsDocContext doc ] badSigErr :: Bool -> HsDocContext -> LHsType RdrName -> TcM () @@ -464,13 +464,13 @@ badSigErr is_type doc (L loc ty) where what | is_type = ptext (sLit "type") | otherwise = ptext (sLit "kind") - flag | is_type = ptext (sLit "-XScopedTypeVariables") - | otherwise = ptext (sLit "-XKindSignatures") + flag | is_type = ptext (sLit "ScopedTypeVariables") + | otherwise = ptext (sLit "KindSignatures") dataKindsErr :: Bool -> HsType RdrName -> SDoc dataKindsErr is_type thing = hang (ptext (sLit "Illegal") <+> what <> colon <+> quotes (ppr thing)) - 2 (ptext (sLit "Perhaps you intended to use -XDataKinds")) + 2 (ptext (sLit "Perhaps you intended to use DataKinds")) where what | is_type = ptext (sLit "type") | otherwise = ptext (sLit "kind") @@ -479,7 +479,7 @@ badRoleAnnotOpt :: SrcSpan -> HsDocContext -> TcM () badRoleAnnotOpt loc doc = setSrcSpan loc $ addErr $ vcat [ ptext (sLit "Illegal role annotation") - , ptext (sLit "Perhaps you intended to use -XRoleAnnotations") + , ptext (sLit "Perhaps you intended to use RoleAnnotations") , docOfHsDocContext doc ] illegalRoleAnnotDoc :: HsDocContext -> LHsType RdrName -> TcM () @@ -850,7 +850,7 @@ opTyErr op ty@(HsOpTy ty1 _ _) extra | op == dot_tv_RDR && forall_head ty1 = perhapsForallMsg | otherwise - = ptext (sLit "Use -XTypeOperators to allow operators in types") + = ptext (sLit "Use TypeOperators to allow operators in types") forall_head (L _ (HsTyVar tv)) = tv == forall_tv_RDR forall_head (L _ (HsAppTy ty _)) = forall_head ty diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 144678e4dd..5216ffd661 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1250,7 +1250,7 @@ checkFlag flag (dflags, _, _) | xopt flag dflags = Nothing | otherwise = Just why where - why = ptext (sLit "You need -X") <> text flag_str + why = ptext (sLit "You need ") <> text flag_str <+> ptext (sLit "to derive an instance for this class") flag_str = case [ s | (s, f, _) <- xFlags, f==flag ] of [s] -> s @@ -1356,7 +1356,7 @@ mkNewTypeEqn orig dflags tvs bale_out msg = failWithTc (derivingThingErr newtype_deriving cls cls_tys inst_ty msg) non_std = nonStdErr cls - suggest_nd = ptext (sLit "Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension") + suggest_nd = ptext (sLit "Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension") -- Here is the plan for newtype derivings. We see -- newtype T a1...an = MkT (t ak+1...an) deriving (.., C s1 .. sm, ...) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index a1d2f1c6cd..559d3f1aa8 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -677,7 +677,7 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 = do { let msg = vcat [ ptext (sLit "Cannot instantiate unification variable") <+> quotes (ppr tv1) , hang (ptext (sLit "with a type involving foralls:")) 2 (ppr ty2) - , nest 2 (ptext (sLit "Perhaps you want -XImpredicativeTypes")) ] + , nest 2 (ptext (sLit "Perhaps you want ImpredicativeTypes")) ] ; mkErrorMsg ctxt ct msg } -- If the immediately-enclosing implication has 'tv' a skolem, and @@ -1030,7 +1030,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) parens (vcat [ ptext (sLit "The choice depends on the instantiation of") <+> quotes (pprWithCommas ppr (varSetElems (tyVarsOfTypes tys))) , ppWhen (null (matching_givens)) $ - vcat [ ptext (sLit "To pick the first instance above, use -XIncoherentInstances") + vcat [ ptext (sLit "To pick the first instance above, use IncoherentInstances") , ptext (sLit "when compiling the other instance declarations")] ])] where diff --git a/compiler/typecheck/TcForeign.lhs b/compiler/typecheck/TcForeign.lhs index d755132696..cf5ed0084a 100644 --- a/compiler/typecheck/TcForeign.lhs +++ b/compiler/typecheck/TcForeign.lhs @@ -270,7 +270,7 @@ tcCheckFIType sig_ty arg_tys res_ty idecl@(CImport cconv safety mh (CFunction ta | cconv == PrimCallConv = do dflags <- getDynFlags check (xopt Opt_GHCForeignImportPrim dflags) - (text "Use -XGHCForeignImportPrim to allow `foreign import prim'.") + (text "Use GHCForeignImportPrim to allow `foreign import prim'.") checkCg checkCOrAsmOrLlvmOrInterp checkCTarget target check (playSafe safety) diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs index b0e7d7a789..f16206b554 100644 --- a/compiler/typecheck/TcHsType.lhs +++ b/compiler/typecheck/TcHsType.lhs @@ -1796,7 +1796,7 @@ tc_kind_var_app name arg_kis dataKindsErr :: Name -> SDoc dataKindsErr name = hang (ptext (sLit "Illegal kind:") <+> quotes (ppr name)) - 2 (ptext (sLit "Perhaps you intended to use -XDataKinds")) + 2 (ptext (sLit "Perhaps you intended to use DataKinds")) promotionErr :: Name -> PromotionErr -> TcM a promotionErr name err @@ -1805,7 +1805,7 @@ promotionErr name err where reason = case err of FamDataConPE -> ptext (sLit "it comes from a data family instance") - NoDataKinds -> ptext (sLit "Perhaps you intended to use -XDataKinds") + NoDataKinds -> ptext (sLit "Perhaps you intended to use DataKinds") _ -> ptext (sLit "it is defined and used in the same recursive group") \end{code} diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index 2c6bd8c1a7..cd18faf8c6 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -979,7 +979,7 @@ misplacedInstSig name hs_ty = vcat [ hang (ptext (sLit "Illegal type signature in instance declaration:")) 2 (hang (pprPrefixName name) 2 (dcolon <+> ppr hs_ty)) - , ptext (sLit "(Use -XInstanceSigs to allow this)") ] + , ptext (sLit "(Use InstanceSigs to allow this)") ] ------------------------------ tcSpecInstPrags :: DFunId -> InstBindings Name @@ -1557,7 +1557,7 @@ badFamInstDecl :: Located Name -> SDoc badFamInstDecl tc_name = vcat [ ptext (sLit "Illegal family instance for") <+> quotes (ppr tc_name) - , nest 2 (parens $ ptext (sLit "Use -XTypeFamilies to allow indexed type families")) ] + , nest 2 (parens $ ptext (sLit "Use TypeFamilies to allow indexed type families")) ] notOpenFamily :: TyCon -> SDoc notOpenFamily tc diff --git a/compiler/typecheck/TcPat.lhs b/compiler/typecheck/TcPat.lhs index cb49d4de2f..f5a78420ae 100644 --- a/compiler/typecheck/TcPat.lhs +++ b/compiler/typecheck/TcPat.lhs @@ -712,7 +712,7 @@ tcConPat penv (L con_span con_name) pat_ty arg_pats thing_inside ; gadts_on <- xoptM Opt_GADTs ; families_on <- xoptM Opt_TypeFamilies ; checkTc (no_equalities || gadts_on || families_on) - (ptext (sLit "A pattern match on a GADT requires -XGADTs or -XTypeFamilies")) + (ptext (sLit "A pattern match on a GADT requires GADTs or TypeFamilies")) -- Trac #2905 decided that a *pattern-match* of a GADT -- should require the GADT language flag. -- Re TypeFamilies see also #7156 diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 6a9da43c1b..8b2b6d4a3e 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1758,7 +1758,7 @@ checkFamFlag tc_name ; checkTc idx_tys err_msg } where err_msg = hang (ptext (sLit "Illegal family declaraion for") <+> quotes (ppr tc_name)) - 2 (ptext (sLit "Use -XTypeFamilies to allow indexed type families")) + 2 (ptext (sLit "Use TypeFamilies to allow indexed type families")) checkNoRoles :: LHsTyVarBndrs Name -> TcM () checkNoRoles (HsQTvs { hsq_tvs = tvs }) @@ -2036,17 +2036,17 @@ classOpCtxt sel_id tau = sep [ptext (sLit "When checking the class method:"), nullaryClassErr :: Class -> SDoc nullaryClassErr cls = vcat [ptext (sLit "No parameters for class") <+> quotes (ppr cls), - parens (ptext (sLit "Use -XNullaryTypeClasses to allow no-parameter classes"))] + parens (ptext (sLit "Use NullaryTypeClasses to allow no-parameter classes"))] classArityErr :: Class -> SDoc classArityErr cls = vcat [ptext (sLit "Too many parameters for class") <+> quotes (ppr cls), - parens (ptext (sLit "Use -XMultiParamTypeClasses to allow multi-parameter classes"))] + parens (ptext (sLit "Use MultiParamTypeClasses to allow multi-parameter classes"))] classFunDepsErr :: Class -> SDoc classFunDepsErr cls = vcat [ptext (sLit "Fundeps in class") <+> quotes (ppr cls), - parens (ptext (sLit "Use -XFunctionalDependencies to allow fundeps"))] + parens (ptext (sLit "Use FunctionalDependencies to allow fundeps"))] noClassTyVarErr :: Class -> Var -> SDoc noClassTyVarErr clas op @@ -2083,14 +2083,14 @@ badGadtKindCon data_con badGadtDecl :: Name -> SDoc badGadtDecl tc_name = vcat [ ptext (sLit "Illegal generalised algebraic data declaration for") <+> quotes (ppr tc_name) - , nest 2 (parens $ ptext (sLit "Use -XGADTs to allow GADTs")) ] + , nest 2 (parens $ ptext (sLit "Use GADTs to allow GADTs")) ] badExistential :: DataCon -> SDoc badExistential con = hang (ptext (sLit "Data constructor") <+> quotes (ppr con) <+> ptext (sLit "has existential type variables, a context, or a specialised result type")) 2 (vcat [ ppr con <+> dcolon <+> ppr (dataConUserType con) - , parens $ ptext (sLit "Use -XExistentialQuantification or -XGADTs to allow this") ]) + , parens $ ptext (sLit "Use ExistentialQuantification or GADTs to allow this") ]) badStupidTheta :: Name -> SDoc badStupidTheta tc_name @@ -2115,12 +2115,12 @@ badSigTyDecl :: Name -> SDoc badSigTyDecl tc_name = vcat [ ptext (sLit "Illegal kind signature") <+> quotes (ppr tc_name) - , nest 2 (parens $ ptext (sLit "Use -XKindSignatures to allow kind signatures")) ] + , nest 2 (parens $ ptext (sLit "Use KindSignatures to allow kind signatures")) ] emptyConDeclsErr :: Name -> SDoc emptyConDeclsErr tycon = sep [quotes (ppr tycon) <+> ptext (sLit "has no constructors"), - nest 2 $ ptext (sLit "(-XEmptyDataDecls permits this)")] + nest 2 $ ptext (sLit "(EmptyDataDecls permits this)")] wrongKindOfFamily :: TyCon -> SDoc wrongKindOfFamily family diff --git a/compiler/typecheck/TcUnify.lhs b/compiler/typecheck/TcUnify.lhs index b3a4743939..525c160c77 100644 --- a/compiler/typecheck/TcUnify.lhs +++ b/compiler/typecheck/TcUnify.lhs @@ -497,7 +497,7 @@ unifyTheta :: TcThetaType -> TcThetaType -> TcM [TcCoercion] unifyTheta theta1 theta2 = do { checkTc (equalLength theta1 theta2) (vcat [ptext (sLit "Contexts differ in length"), - nest 2 $ parens $ ptext (sLit "Use -XRelaxedPolyRec to allow this")]) + nest 2 $ parens $ ptext (sLit "Use RelaxedPolyRec to allow this")]) ; zipWithM unifyPred theta1 theta2 } \end{code} diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs index 677da1c88e..7d02866a62 100644 --- a/compiler/typecheck/TcValidity.lhs +++ b/compiler/typecheck/TcValidity.lhs @@ -233,9 +233,9 @@ data Rank = ArbitraryRank -- Any rank ok | MustBeMonoType -- Monotype regardless of flags rankZeroMonoType, tyConArgMonoType, synArgMonoType :: Rank -rankZeroMonoType = MonoType (ptext (sLit "Perhaps you intended to use -XRankNTypes or -XRank2Types")) -tyConArgMonoType = MonoType (ptext (sLit "Perhaps you intended to use -XImpredicativeTypes")) -synArgMonoType = MonoType (ptext (sLit "Perhaps you intended to use -XLiberalTypeSynonyms")) +rankZeroMonoType = MonoType (ptext (sLit "Perhaps you intended to use RankNTypes or Rank2Types")) +tyConArgMonoType = MonoType (ptext (sLit "Perhaps you intended to use ImpredicativeTypes")) +synArgMonoType = MonoType (ptext (sLit "Perhaps you intended to use LiberalTypeSynonyms")) funArgResRank :: Rank -> (Rank, Rank) -- Function argument and result funArgResRank (LimitedRank _ arg_rank) = (arg_rank, LimitedRank (forAllAllowed arg_rank) arg_rank) @@ -390,7 +390,7 @@ forAllTyErr rank ty , suggestion ] where suggestion = case rank of - LimitedRank {} -> ptext (sLit "Perhaps you intended to use -XRankNTypes or -XRank2Types") + LimitedRank {} -> ptext (sLit "Perhaps you intended to use RankNTypes or Rank2Types") MonoType d -> d _ -> empty -- Polytype is always illegal @@ -501,7 +501,7 @@ check_class_pred dflags ctxt cls tys arity = classArity cls n_tys = length tys arity_err = arityErr "Class" class_name arity n_tys - how_to_allow = parens (ptext (sLit "Use -XFlexibleContexts to permit this")) + how_to_allow = parens (ptext (sLit "Use FlexibleContexts to permit this")) check_eq_pred :: DynFlags -> UserTypeCtxt -> TcType -> TcType -> TcM () @@ -698,20 +698,20 @@ checkThetaCtxt ctxt theta eqPredTyErr, predTyVarErr, predTupleErr, predIrredErr, predIrredBadCtxtErr :: PredType -> SDoc eqPredTyErr pred = ptext (sLit "Illegal equational constraint") <+> pprType pred $$ - parens (ptext (sLit "Use -XGADTs or -XTypeFamilies to permit this")) + parens (ptext (sLit "Use GADTs or TypeFamilies to permit this")) predTyVarErr pred = hang (ptext (sLit "Non type-variable argument")) 2 (ptext (sLit "in the constraint:") <+> pprType pred) predTupleErr pred = hang (ptext (sLit "Illegal tuple constraint:") <+> pprType pred) - 2 (parens (ptext (sLit "Use -XConstraintKinds to permit this"))) + 2 (parens (ptext (sLit "Use ConstraintKinds to permit this"))) predIrredErr pred = hang (ptext (sLit "Illegal constraint:") <+> pprType pred) - 2 (parens (ptext (sLit "Use -XConstraintKinds to permit this"))) + 2 (parens (ptext (sLit "Use ConstraintKinds to permit this"))) predIrredBadCtxtErr pred = hang (ptext (sLit "Illegal constraint") <+> quotes (pprType pred) <+> ptext (sLit "in a superclass/instance context")) - 2 (parens (ptext (sLit "Use -XUndecidableInstances to permit this"))) + 2 (parens (ptext (sLit "Use UndecidableInstances to permit this"))) constraintSynErr :: Type -> SDoc constraintSynErr kind = hang (ptext (sLit "Illegal constraint synonym of kind:") <+> quotes (ppr kind)) - 2 (parens (ptext (sLit "Use -XConstraintKinds to permit this"))) + 2 (parens (ptext (sLit "Use ConstraintKinds to permit this"))) dupPredWarn :: [[PredType]] -> SDoc dupPredWarn dups = ptext (sLit "Duplicate constraint(s):") <+> pprWithCommas pprType (map head dups) @@ -784,21 +784,21 @@ checkValidInstHead ctxt clas cls_args head_type_synonym_msg = parens ( text "All instance types must be of the form (T t1 ... tn)" $$ text "where T is not a synonym." $$ - text "Use -XTypeSynonymInstances if you want to disable this.") + text "Use TypeSynonymInstances if you want to disable this.") head_type_args_tyvars_msg = parens (vcat [ text "All instance types must be of the form (T a1 ... an)", text "where a1 ... an are *distinct type variables*,", text "and each type variable appears at most once in the instance head.", - text "Use -XFlexibleInstances if you want to disable this."]) + text "Use FlexibleInstances if you want to disable this."]) head_one_type_msg = parens ( text "Only one type can be given in an instance head." $$ - text "Use -XMultiParamTypeClasses if you want to allow more.") + text "Use MultiParamTypeClasses if you want to allow more.") head_no_type_msg = parens ( text "No parameters in the instance head." $$ - text "Use -XNullaryTypeClasses if you want to allow this.") + text "Use NullaryTypeClasses if you want to allow this.") abstract_class_msg = text "The class is abstract, manual instances are not permitted." @@ -945,7 +945,7 @@ nomoreMsg tvs smallerMsg, undecidableMsg :: SDoc smallerMsg = ptext (sLit "Constraint is no smaller than the instance head") -undecidableMsg = ptext (sLit "Use -XUndecidableInstances to permit this") +undecidableMsg = ptext (sLit "Use UndecidableInstances to permit this") \end{code} |