diff options
Diffstat (limited to 'compiler/rename/RnSource.hs')
-rw-r--r-- | compiler/rename/RnSource.hs | 46 |
1 files changed, 23 insertions, 23 deletions
diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index bfb252798c..363d8692c5 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -286,7 +286,7 @@ rnSrcFixityDecls bndr_set fix_decls -- this lookup will fail if the definition isn't local do names <- lookupLocalTcNames sig_ctxt what rdr_name return [ L name_loc name | (_, name) <- names ] - what = ptext (sLit "fixity signature") + what = text "fixity signature" {- ********************************************************* @@ -325,7 +325,7 @@ rnSrcWarnDecls bndr_set decls' rdr_names ; return [(rdrNameOcc rdr, txt) | (rdr, _) <- names] } - what = ptext (sLit "deprecation") + what = text "deprecation" warn_rdr_dups = findDupRdrNames $ concatMap (\(L _ (Warning ns _)) -> ns) decls @@ -340,8 +340,8 @@ findDupRdrNames = findDupsEq (\ x -> \ y -> rdrNameOcc (unLoc x) == rdrNameOcc ( dupWarnDecl :: Located RdrName -> RdrName -> SDoc -- Located RdrName -> DeprecDecl RdrName -> SDoc dupWarnDecl (L loc _) rdr_name - = vcat [ptext (sLit "Multiple warning declarations for") <+> quotes (ppr rdr_name), - ptext (sLit "also at ") <+> ppr loc] + = vcat [text "Multiple warning declarations for" <+> quotes (ppr rdr_name), + text "also at " <+> ppr loc] {- ********************************************************* @@ -599,7 +599,7 @@ checkCanonicalInstances cls poly_ty mbinds = do = inst_decl_ctxt (ppr head_ty) inst_decl_ctxt :: SDoc -> SDoc - inst_decl_ctxt doc = hang (ptext (sLit "in the instance declaration for")) + inst_decl_ctxt doc = hang (text "in the instance declaration for") 2 (quotes doc <> text ".") @@ -879,8 +879,8 @@ rnSrcDerivDecl (DerivDecl ty overlap) standaloneDerivErr :: SDoc standaloneDerivErr - = hang (ptext (sLit "Illegal standalone deriving declaration")) - 2 (ptext (sLit "Use StandaloneDeriving to enable this extension")) + = hang (text "Illegal standalone deriving declaration") + 2 (text "Use StandaloneDeriving to enable this extension") {- ********************************************************* @@ -992,21 +992,21 @@ validRuleLhs foralls lhs badRuleVar :: FastString -> Name -> SDoc badRuleVar name var - = sep [ptext (sLit "Rule") <+> doubleQuotes (ftext name) <> colon, - ptext (sLit "Forall'd variable") <+> quotes (ppr var) <+> - ptext (sLit "does not appear on left hand side")] + = sep [text "Rule" <+> doubleQuotes (ftext name) <> colon, + text "Forall'd variable" <+> quotes (ppr var) <+> + text "does not appear on left hand side"] badRuleLhsErr :: FastString -> LHsExpr Name -> HsExpr Name -> SDoc badRuleLhsErr name lhs bad_e - = sep [ptext (sLit "Rule") <+> pprRuleName name <> colon, + = sep [text "Rule" <+> pprRuleName name <> colon, nest 4 (vcat [err, - ptext (sLit "in left-hand side:") <+> ppr lhs])] + text "in left-hand side:" <+> ppr lhs])] $$ - ptext (sLit "LHS must be of form (f e1 .. en) where f is not forall'd") + text "LHS must be of form (f e1 .. en) where f is not forall'd" where err = case bad_e of - HsUnboundVar occ -> ptext (sLit "Not in scope:") <+> ppr occ - _ -> ptext (sLit "Illegal expression:") <+> ppr bad_e + HsUnboundVar occ -> text "Not in scope:" <+> ppr occ + _ -> text "Illegal expression:" <+> ppr bad_e {- ********************************************************* @@ -1026,8 +1026,8 @@ rnHsVectDecl (HsVect s var rhs@(L _ (HsVar _))) } rnHsVectDecl (HsVect _ _var _rhs) = failWith $ vcat - [ ptext (sLit "IMPLEMENTATION RESTRICTION: right-hand side of a VECTORISE pragma") - , ptext (sLit "must be an identifier") + [ text "IMPLEMENTATION RESTRICTION: right-hand side of a VECTORISE pragma" + , text "must be an identifier" ] rnHsVectDecl (HsNoVect s var) = do { var' <- lookupLocatedTopBndrRn var -- only applies to local (not imported) names @@ -1377,8 +1377,8 @@ rnDataDefn doc (HsDataDefn { dd_ND = new_or_data, dd_cType = cType badGadtStupidTheta :: HsDocContext -> SDoc badGadtStupidTheta _ - = vcat [ptext (sLit "No context is allowed on a GADT-style data declaration"), - ptext (sLit "(You can put a context on each contructor, though.)")] + = vcat [text "No context is allowed on a GADT-style data declaration", + text "(You can put a context on each contructor, though.)"] rnFamDecl :: Maybe Name -- Just cls => this FamilyDecl is nested -- inside an *class decl* for cls @@ -1637,9 +1637,9 @@ modules), we get better error messages, too. --------------- badAssocRhs :: [Name] -> RnM () badAssocRhs ns - = addErr (hang (ptext (sLit "The RHS of an associated type declaration mentions") + = addErr (hang (text "The RHS of an associated type declaration mentions" <+> pprWithCommas (quotes . ppr) ns) - 2 (ptext (sLit "All such variables must be bound on the LHS"))) + 2 (text "All such variables must be bound on the LHS")) ----------------- rnConDecls :: [LConDecl RdrName] -> RnM ([LConDecl Name], FreeVars) @@ -1837,8 +1837,8 @@ add gp loc (SpliceD splice@(SpliceDecl _ flag)) ds ; return (gp, Just (splice, ds)) } where - badImplicitSplice = ptext (sLit "Parse error: naked expression at top level") - $$ ptext (sLit "Perhaps you intended to use TemplateHaskell") + badImplicitSplice = text "Parse error: naked expression at top level" + $$ text "Perhaps you intended to use TemplateHaskell" -- Class declarations: pull out the fixity signatures to the top add gp@(HsGroup {hs_tyclds = ts, hs_fixds = fs}) l (TyClD d) ds |