summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/basicTypes/IdInfo.lhs11
-rw-r--r--compiler/deSugar/Desugar.lhs3
-rw-r--r--compiler/main/HscStats.lhs3
-rw-r--r--compiler/main/Packages.lhs5
-rw-r--r--compiler/main/PprTyThing.hs29
5 files changed, 22 insertions, 29 deletions
diff --git a/compiler/basicTypes/IdInfo.lhs b/compiler/basicTypes/IdInfo.lhs
index dbbaeacb49..0a54395eb8 100644
--- a/compiler/basicTypes/IdInfo.lhs
+++ b/compiler/basicTypes/IdInfo.lhs
@@ -92,7 +92,6 @@ import ForeignCall
import NewDemand
import Outputable
import Module
-import Pretty (Doc)
import Data.Maybe
@@ -153,7 +152,7 @@ seqNewStrictnessInfo :: Maybe StrictSig -> ()
seqNewStrictnessInfo Nothing = ()
seqNewStrictnessInfo (Just ty) = seqStrictSig ty
-pprNewStrictness :: Maybe StrictSig -> PprStyle -> Doc
+pprNewStrictness :: Maybe StrictSig -> SDoc
pprNewStrictness Nothing = empty
pprNewStrictness (Just sig) = ftext FSLIT("Str:") <+> ppr sig
@@ -451,7 +450,7 @@ type ArityInfo = Arity
unknownArity :: Arity
unknownArity = 0 :: Arity
-ppArityInfo :: Int -> PprStyle -> Doc
+ppArityInfo :: Int -> SDoc
ppArityInfo 0 = empty
ppArityInfo n = hsep [ptext SLIT("Arity"), int n]
\end{code}
@@ -558,7 +557,7 @@ seqWorker :: WorkerInfo -> ()
seqWorker (HasWorker id a) = id `seq` a `seq` ()
seqWorker NoWorker = ()
-ppWorkerInfo :: WorkerInfo -> PprStyle -> Doc
+ppWorkerInfo :: WorkerInfo -> SDoc
ppWorkerInfo NoWorker = empty
ppWorkerInfo (HasWorker wk_id _) = ptext SLIT("Worker") <+> ppr wk_id
@@ -604,7 +603,7 @@ mayHaveCafRefs _ = False
seqCaf :: CafInfo -> ()
seqCaf c = c `seq` ()
-ppCafInfo :: CafInfo -> PprStyle -> Doc
+ppCafInfo :: CafInfo -> SDoc
ppCafInfo NoCafRefs = ptext SLIT("NoCafRefs")
ppCafInfo MayHaveCafRefs = empty
\end{code}
@@ -694,7 +693,7 @@ hasNoLBVarInfo IsOneShotLambda = False
noLBVarInfo :: LBVarInfo
noLBVarInfo = NoLBVarInfo
-pprLBVarInfo :: LBVarInfo -> PprStyle -> Doc
+pprLBVarInfo :: LBVarInfo -> SDoc
pprLBVarInfo NoLBVarInfo = empty
pprLBVarInfo IsOneShotLambda = ptext SLIT("OneShot")
diff --git a/compiler/deSugar/Desugar.lhs b/compiler/deSugar/Desugar.lhs
index f9e6212b18..e3874a7017 100644
--- a/compiler/deSugar/Desugar.lhs
+++ b/compiler/deSugar/Desugar.lhs
@@ -39,7 +39,6 @@ import Outputable
import SrcLoc
import Maybes
import FastString
-import Pretty ( Doc )
import Coverage
import Data.IORef
\end{code}
@@ -232,7 +231,7 @@ addExportFlags target exports keep_alive prs rules
is_exported | target == HscInterpreted = isExternalName
| otherwise = (`elemNameSet` exports)
-ppr_ds_rules :: [CoreRule] -> PprStyle -> Doc
+ppr_ds_rules :: [CoreRule] -> SDoc
ppr_ds_rules [] = empty
ppr_ds_rules rules
= text "" $$ text "-------------- DESUGARED RULES -----------------" $$
diff --git a/compiler/main/HscStats.lhs b/compiler/main/HscStats.lhs
index d12831edb7..52e396dcde 100644
--- a/compiler/main/HscStats.lhs
+++ b/compiler/main/HscStats.lhs
@@ -16,7 +16,6 @@ import SrcLoc
import Char
import Bag
import Util
-import Pretty ( Doc )
import RdrName
\end{code}
@@ -27,7 +26,7 @@ import RdrName
%************************************************************************
\begin{code}
-ppSourceStats :: Bool -> Located (HsModule RdrName) -> PprStyle -> Doc
+ppSourceStats :: Bool -> Located (HsModule RdrName) -> SDoc
ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
= (if short then hcat else vcat)
(map pp_val
diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs
index d10d873ed4..982085437c 100644
--- a/compiler/main/Packages.lhs
+++ b/compiler/main/Packages.lhs
@@ -46,7 +46,6 @@ import Util
import Maybes ( expectJust, MaybeErr(..) )
import Panic
import Outputable
-import Pretty ( Doc )
import System.Environment ( getEnv )
import Distribution.InstalledPackageInfo
@@ -695,10 +694,10 @@ add_package pkg_db ps (p, mb_parent)
missingPackageErr :: String -> IO [PackageConfig]
missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p)))
-missingPackageMsg :: String -> PprStyle -> Doc
+missingPackageMsg :: String -> SDoc
missingPackageMsg p = ptext SLIT("unknown package:") <+> text p
-missingDependencyMsg :: Maybe PackageId -> PprStyle -> Doc
+missingDependencyMsg :: Maybe PackageId -> SDoc
missingDependencyMsg Nothing = empty
missingDependencyMsg (Just parent)
= space <> parens (ptext SLIT("dependency of") <+> ftext (packageIdFS parent))
diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs
index 16f5181af8..e57122b721 100644
--- a/compiler/main/PprTyThing.hs
+++ b/compiler/main/PprTyThing.hs
@@ -27,7 +27,6 @@ import TcType
import Var
import Name
import Outputable
-import Pretty ( Doc )
-- -----------------------------------------------------------------------------
-- Pretty-printing entities that we get from the GHC API
@@ -75,7 +74,7 @@ pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
pprTyThingHdr pefas (ATyCon tyCon) = pprTyConHdr pefas tyCon
pprTyThingHdr pefas (AClass cls) = pprClassHdr pefas cls
-pprTyConHdr :: PrintExplicitForalls -> TyCon -> PprStyle -> Doc
+pprTyConHdr :: PrintExplicitForalls -> TyCon -> SDoc
pprTyConHdr _ tyCon
| Just (_fam_tc, tys) <- tyConFamInst_maybe tyCon
= ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp tyCon (ppr_bndr tyCon) tys
@@ -98,11 +97,11 @@ pprTyConHdr _ tyCon
| isAlgTyCon tyCon = GHC.pprThetaArrow (tyConStupidTheta tyCon)
| otherwise = empty -- Returns 'empty' if null theta
-pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> PprStyle -> Doc
+pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> SDoc
pprDataConSig pefas dataCon =
ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon)
-pprClassHdr :: PrintExplicitForalls -> GHC.Class -> PprStyle -> Doc
+pprClassHdr :: PrintExplicitForalls -> GHC.Class -> SDoc
pprClassHdr _ cls =
let (tyVars, funDeps) = GHC.classTvsFds cls
in ptext SLIT("class") <+>
@@ -111,13 +110,13 @@ pprClassHdr _ cls =
hsep (map ppr tyVars) <+>
GHC.pprFundeps funDeps
-pprIdInContext :: PrintExplicitForalls -> Var -> PprStyle -> Doc
+pprIdInContext :: PrintExplicitForalls -> Var -> SDoc
pprIdInContext pefas id
| GHC.isRecordSelector id = pprRecordSelector pefas id
| Just cls <- GHC.isClassOpId_maybe id = pprClassOneMethod pefas cls id
| otherwise = pprId pefas id
-pprRecordSelector :: PrintExplicitForalls -> Id -> PprStyle -> Doc
+pprRecordSelector :: PrintExplicitForalls -> Id -> SDoc
pprRecordSelector pefas id
= pprAlgTyCon pefas tyCon show_con show_label
where
@@ -146,7 +145,7 @@ pprTypeForUser print_foralls ty
tidy_ty = tidyTopType ty
(ctxt, ty') = tcMultiSplitSigmaTy tidy_ty
-pprTyCon :: PrintExplicitForalls -> TyCon -> PprStyle -> Doc
+pprTyCon :: PrintExplicitForalls -> TyCon -> SDoc
pprTyCon pefas tyCon
| GHC.isSynTyCon tyCon
= if GHC.isOpenTyCon tyCon
@@ -159,8 +158,7 @@ pprTyCon pefas tyCon
= pprAlgTyCon pefas tyCon (const True) (const True)
pprAlgTyCon :: PrintExplicitForalls -> TyCon -> (GHC.DataCon -> Bool)
- -> (FieldLabel -> Bool) -> PprStyle
- -> Doc
+ -> (FieldLabel -> Bool) -> SDoc
pprAlgTyCon pefas tyCon ok_con ok_label
| gadt = pprTyConHdr pefas tyCon <+> ptext SLIT("where") $$
nest 2 (vcat (ppr_trim show_con datacons))
@@ -174,13 +172,12 @@ pprAlgTyCon pefas tyCon ok_con ok_label
| ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon)
| otherwise = Nothing
-pprDataCon :: PrintExplicitForalls -> GHC.DataCon -> PprStyle -> Doc
+pprDataCon :: PrintExplicitForalls -> GHC.DataCon -> SDoc
pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True)
where tyCon = GHC.dataConTyCon dataCon
pprDataConDecl :: PrintExplicitForalls -> Bool -> (FieldLabel -> Bool)
- -> GHC.DataCon -> PprStyle
- -> Doc
+ -> GHC.DataCon -> SDoc
pprDataConDecl _ gadt_style show_label dataCon
| not gadt_style = ppr_fields tys_w_strs
| otherwise = ppr_bndr dataCon <+> dcolon <+>
@@ -225,7 +222,7 @@ pprDataConDecl _ gadt_style show_label dataCon
braces (sep (punctuate comma (ppr_trim maybe_show_label
(zip labels fields))))
-pprClass :: PrintExplicitForalls -> GHC.Class -> PprStyle -> Doc
+pprClass :: PrintExplicitForalls -> GHC.Class -> SDoc
pprClass pefas cls
| null methods =
pprClassHdr pefas cls
@@ -235,7 +232,7 @@ pprClass pefas cls
where
methods = GHC.classMethods cls
-pprClassOneMethod :: PrintExplicitForalls -> GHC.Class -> Id -> PprStyle -> Doc
+pprClassOneMethod :: PrintExplicitForalls -> GHC.Class -> Id -> SDoc
pprClassOneMethod pefas cls this_one
= hang (pprClassHdr pefas cls <+> ptext SLIT("where"))
2 (vcat (ppr_trim show_meth methods))
@@ -244,7 +241,7 @@ pprClassOneMethod pefas cls this_one
show_meth id | id == this_one = Just (pprClassMethod pefas id)
| otherwise = Nothing
-pprClassMethod :: PrintExplicitForalls -> Id -> PprStyle -> Doc
+pprClassMethod :: PrintExplicitForalls -> Id -> SDoc
pprClassMethod pefas id
= hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty)
where
@@ -272,7 +269,7 @@ ppr_trim show xs
| otherwise = if eliding then (True, so_far)
else (True, ptext SLIT("...") : so_far)
-add_bars :: [SDoc] -> PprStyle -> Doc
+add_bars :: [SDoc] -> SDoc
add_bars [] = empty
add_bars [c] = equals <+> c
add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs)