Skip to content

Commit 17453bc

Browse files
committed
Unify use printOutputable
1 parent 02a516e commit 17453bc

File tree

21 files changed

+106
-121
lines changed

21 files changed

+106
-121
lines changed

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1301,7 +1301,7 @@ getDocsBatch hsc_env _mod _names = do
13011301
#endif
13021302
Map.findWithDefault mempty name amap))
13031303
case res of
1304-
Just x -> return $ map (first $ T.unpack . printOutputableText) x
1304+
Just x -> return $ map (first $ T.unpack . printOutputable) x
13051305
Nothing -> throwErrors
13061306
#if MIN_VERSION_ghc(9,2,0)
13071307
$ Error.getErrorMessages msgs

ghcide/src/Development/IDE/GHC/Compat/Outputable.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -108,7 +108,7 @@ oldMkErrStyle _ = Out.mkErrStyle
108108
oldFormatErrDoc :: DynFlags -> Err.ErrDoc -> Out.SDoc
109109
oldFormatErrDoc dflags = Err.formatErrDoc dummySDocContext
110110
where dummySDocContext = initSDocContext dflags Out.defaultUserStyle
111-
#elif !MIN_VERSION_ghc(9,2,0)
111+
#elif !MIN_VERSION_ghc(9,0,0)
112112
oldRenderWithStyle :: DynFlags -> Out.SDoc -> Out.PprStyle -> String
113113
oldRenderWithStyle = Out.renderWithStyle
114114

ghcide/src/Development/IDE/GHC/Orphans.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -46,27 +46,27 @@ import ByteCodeTypes
4646
#endif
4747

4848
-- Orphan instances for types from the GHC API.
49-
instance Show CoreModule where show = printOutputable
49+
instance Show CoreModule where show = show . printOutputable
5050
instance NFData CoreModule where rnf = rwhnf
51-
instance Show CgGuts where show = printOutputable . cg_module
51+
instance Show CgGuts where show = show . printOutputable . cg_module
5252
instance NFData CgGuts where rnf = rwhnf
5353
instance Show ModDetails where show = const "<moddetails>"
5454
instance NFData ModDetails where rnf = rwhnf
5555
instance NFData SafeHaskellMode where rnf = rwhnf
56-
instance Show Linkable where show = printOutputable
56+
instance Show Linkable where show = show . printOutputable
5757
instance NFData Linkable where rnf (LM a b c) = rnf a `seq` rnf b `seq` rnf c
5858
instance NFData Unlinked where
5959
rnf (DotO f) = rnf f
6060
rnf (DotA f) = rnf f
6161
rnf (DotDLL f) = rnf f
6262
rnf (BCOs a b) = seqCompiledByteCode a `seq` liftRnf rwhnf b
63-
instance Show PackageFlag where show = printOutputable
64-
instance Show InteractiveImport where show = printOutputable
65-
instance Show PackageName where show = printOutputable
63+
instance Show PackageFlag where show = show . printOutputable
64+
instance Show InteractiveImport where show = show . printOutputable
65+
instance Show PackageName where show = show . printOutputable
6666

6767
#if !MIN_VERSION_ghc(9,0,1)
68-
instance Show ComponentId where show = printOutputable
69-
instance Show SourcePackageId where show = printOutputable
68+
instance Show ComponentId where show = show . printOutputable
69+
instance Show SourcePackageId where show = show . printOutputable
7070

7171
instance Show GhcPlugins.InstalledUnitId where
7272
show = installedUnitIdString
@@ -76,7 +76,7 @@ instance NFData GhcPlugins.InstalledUnitId where rnf = rwhnf . installedUnitIdFS
7676
instance Hashable GhcPlugins.InstalledUnitId where
7777
hashWithSalt salt = hashWithSalt salt . installedUnitIdString
7878
#else
79-
instance Show UnitId where show = printOutputable
79+
instance Show UnitId where show = show . printOutputable
8080
deriving instance Ord SrcSpan
8181
deriving instance Ord UnhelpfulSpanReason
8282
#endif
@@ -86,7 +86,7 @@ instance NFData SB.StringBuffer where rnf = rwhnf
8686
instance Show Module where
8787
show = moduleNameString . moduleName
8888

89-
instance Outputable a => Show (GenLocated SrcSpan a) where show = printOutputable
89+
instance Outputable a => Show (GenLocated SrcSpan a) where show = show . printOutputable
9090

9191
instance (NFData l, NFData e) => NFData (GenLocated l e) where
9292
rnf (L l e) = rnf l `seq` rnf e
@@ -207,5 +207,5 @@ instance (NFData (HsModule a)) where
207207
#endif
208208
rnf = rwhnf
209209

210-
instance Show OccName where show = printOutputable
210+
instance Show OccName where show = show . printOutputable
211211
instance Hashable OccName where hashWithSalt s n = hashWithSalt s (getKey $ getUnique n)

ghcide/src/Development/IDE/GHC/Util.hs

Lines changed: 4 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -27,8 +27,7 @@ module Development.IDE.GHC.Util(
2727
dontWriteHieFiles,
2828
disableWarningsAsErrors,
2929
traceAst,
30-
printOutputable,
31-
printOutputableText
30+
printOutputable
3231
) where
3332

3433
#if MIN_VERSION_ghc(9,2,0)
@@ -133,7 +132,7 @@ bytestringToStringBuffer (PS buf cur len) = StringBuffer{..}
133132

134133
-- | Pretty print a 'RdrName' wrapping operators in parens
135134
printRdrName :: RdrName -> String
136-
printRdrName name = printOutputable $ parenSymOcc rn (ppr rn)
135+
printRdrName name = show $ printOutputable $ parenSymOcc rn (ppr rn)
137136
where
138137
rn = rdrNameOcc name
139138

@@ -324,19 +323,6 @@ instance Outputable SDoc where
324323
-- This is the most common print utility, will print with a user-friendly style like: `a_a4ME` as `a`.
325324
--
326325
-- It internal using `showSDocUnsafe` with `unsafeGlobalDynFlags`.
327-
--
328-
-- You may prefer `printOutputableText` if `Text` is expected to return.
329-
printOutputable :: Outputable a => a -> String
330-
printOutputable = printWithoutUniques
326+
printOutputable :: Outputable a => a -> T.Text
327+
printOutputable = T.pack . printWithoutUniques
331328
{-# INLINE printOutputable #-}
332-
333-
-- | Print a GHC value in `defaultUserStyle` without unique symbols.
334-
--
335-
-- This is the most common print utility, will print with a user-friendly style like: `a_a4ME` as `a`.
336-
--
337-
-- It internal using `showSDocUnsafe` with `unsafeGlobalDynFlags`.
338-
--
339-
-- You may prefer `printOutputable` if `String` is expected to return.
340-
printOutputableText :: Outputable a => a -> T.Text
341-
printOutputableText = T.pack . printOutputable
342-
{-# INLINE printOutputableText #-}

ghcide/src/Development/IDE/LSP/Outline.hs

Lines changed: 23 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ import Development.IDE.GHC.Compat
2020
import Development.IDE.GHC.Error (rangeToRealSrcSpan,
2121
realSrcSpanToRange)
2222
import Development.IDE.Types.Location
23-
import Development.IDE.GHC.Util (printOutputableText)
23+
import Development.IDE.GHC.Util (printOutputable)
2424
import Language.LSP.Server (LspM)
2525
import Language.LSP.Types (DocumentSymbol (..),
2626
DocumentSymbolParams (DocumentSymbolParams, _textDocument),
@@ -47,7 +47,7 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
4747
moduleSymbol = hsmodName >>= \case
4848
(L (locA -> (RealSrcSpan l _)) m) -> Just $
4949
(defDocumentSymbol l :: DocumentSymbol)
50-
{ _name = printOutputableText m
50+
{ _name = printOutputable m
5151
, _kind = SkFile
5252
, _range = Range (Position 0 0) (Position maxBound 0) -- _ltop is 0 0 0 0
5353
}
@@ -70,18 +70,18 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
7070
documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
7171
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
7272
= Just (defDocumentSymbol l :: DocumentSymbol)
73-
{ _name = printOutputableText n
74-
<> (case printOutputableText fdTyVars of
73+
{ _name = printOutputable n
74+
<> (case printOutputable fdTyVars of
7575
"" -> ""
7676
t -> " " <> t
7777
)
78-
, _detail = Just $ printOutputableText fdInfo
78+
, _detail = Just $ printOutputable fdInfo
7979
, _kind = SkFunction
8080
}
8181
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
8282
= Just (defDocumentSymbol l :: DocumentSymbol)
83-
{ _name = printOutputableText name
84-
<> (case printOutputableText tcdTyVars of
83+
{ _name = printOutputable name
84+
<> (case printOutputable tcdTyVars of
8585
"" -> ""
8686
t -> " " <> t
8787
)
@@ -90,7 +90,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
9090
, _children =
9191
Just $ List
9292
[ (defDocumentSymbol l :: DocumentSymbol)
93-
{ _name = printOutputableText n
93+
{ _name = printOutputable n
9494
, _kind = SkMethod
9595
, _selectionRange = realSrcSpanToRange l'
9696
}
@@ -100,12 +100,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
100100
}
101101
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
102102
= Just (defDocumentSymbol l :: DocumentSymbol)
103-
{ _name = printOutputableText name
103+
{ _name = printOutputable name
104104
, _kind = SkStruct
105105
, _children =
106106
Just $ List
107107
[ (defDocumentSymbol l :: DocumentSymbol)
108-
{ _name = printOutputableText n
108+
{ _name = printOutputable n
109109
, _kind = SkConstructor
110110
, _selectionRange = realSrcSpanToRange l'
111111
#if MIN_VERSION_ghc(9,2,0)
@@ -123,7 +123,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
123123
where
124124
cvtFld :: LFieldOcc GhcPs -> Maybe DocumentSymbol
125125
cvtFld (L (RealSrcSpan l _) n) = Just $ (defDocumentSymbol l :: DocumentSymbol)
126-
{ _name = printOutputableText (unLoc (rdrNameFieldOcc n))
126+
{ _name = printOutputable (unLoc (rdrNameFieldOcc n))
127127
, _kind = SkField
128128
}
129129
cvtFld _ = Nothing
@@ -138,7 +138,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
138138
-- | Extract the record fields of a constructor
139139
conArgRecordFields (RecCon (L _ lcdfs)) = Just $ List
140140
[ (defDocumentSymbol l :: DocumentSymbol)
141-
{ _name = printOutputableText n
141+
{ _name = printOutputable n
142142
, _kind = SkField
143143
}
144144
| L _ cdf <- lcdfs
@@ -147,12 +147,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
147147
conArgRecordFields _ = Nothing
148148
#endif
149149
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
150-
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText n
150+
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable n
151151
, _kind = SkTypeParameter
152152
, _selectionRange = realSrcSpanToRange l'
153153
}
154154
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
155-
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText cid_poly_ty
155+
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable cid_poly_ty
156156
, _kind = SkInterface
157157
}
158158
#if MIN_VERSION_ghc(9,2,0)
@@ -161,8 +161,8 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
161161
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
162162
#endif
163163
= Just (defDocumentSymbol l :: DocumentSymbol)
164-
{ _name = printOutputableText (unLoc feqn_tycon) <> " " <> T.unwords
165-
(map printOutputableText feqn_pats)
164+
{ _name = printOutputable (unLoc feqn_tycon) <> " " <> T.unwords
165+
(map printOutputable feqn_pats)
166166
, _kind = SkInterface
167167
}
168168
#if MIN_VERSION_ghc(9,2,0)
@@ -171,24 +171,24 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
171171
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
172172
#endif
173173
= Just (defDocumentSymbol l :: DocumentSymbol)
174-
{ _name = printOutputableText (unLoc feqn_tycon) <> " " <> T.unwords
175-
(map printOutputableText feqn_pats)
174+
{ _name = printOutputable (unLoc feqn_tycon) <> " " <> T.unwords
175+
(map printOutputable feqn_pats)
176176
, _kind = SkInterface
177177
}
178178
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
179179
gfindtype deriv_type <&> \(L (_ :: SrcSpan) name) ->
180-
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText @(HsType GhcPs)
180+
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputable @(HsType GhcPs)
181181
name
182182
, _kind = SkInterface
183183
}
184184
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind{fun_id = L _ name})) = Just
185185
(defDocumentSymbol l :: DocumentSymbol)
186-
{ _name = printOutputableText name
186+
{ _name = printOutputable name
187187
, _kind = SkFunction
188188
}
189189
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind{pat_lhs})) = Just
190190
(defDocumentSymbol l :: DocumentSymbol)
191-
{ _name = printOutputableText pat_lhs
191+
{ _name = printOutputable pat_lhs
192192
, _kind = SkFunction
193193
}
194194

@@ -204,7 +204,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
204204
ForeignExport{} -> Just "export"
205205
XForeignDecl{} -> Nothing
206206
}
207-
where name = printOutputableText $ unLoc $ fd_name x
207+
where name = printOutputable $ unLoc $ fd_name x
208208

209209
documentSymbolForDecl _ = Nothing
210210

@@ -228,7 +228,7 @@ documentSymbolForImportSummary importSymbols =
228228
documentSymbolForImport :: LImportDecl GhcPs -> Maybe DocumentSymbol
229229
documentSymbolForImport (L (locA -> (RealSrcSpan l _)) ImportDecl { ideclName, ideclQualified }) = Just
230230
(defDocumentSymbol l :: DocumentSymbol)
231-
{ _name = "import " <> printOutputableText ideclName
231+
{ _name = "import " <> printOutputable ideclName
232232
, _kind = SkModule
233233
#if MIN_VERSION_ghc(8,10,0)
234234
, _detail = case ideclQualified of { NotQualified -> Nothing; _ -> Just "qualified" }

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ import Development.IDE.GHC.ExactPrint
5151
import Development.IDE.GHC.Util (printOutputable,
5252
printRdrName,
5353
traceAst,
54-
printOutputableText)
54+
printOutputable)
5555
import Development.IDE.Plugin.CodeAction.Args
5656
import Development.IDE.Plugin.CodeAction.ExactPrint
5757
import Development.IDE.Plugin.CodeAction.PositionIndexed
@@ -545,7 +545,7 @@ suggestDeleteUnusedBinding
545545
isTheBinding span = srcSpanToRange span == Just _range
546546

547547
isSameName :: IdP GhcPs -> String -> Bool
548-
isSameName x name = printOutputable x == name
548+
isSameName x name = show (printOutputable x) == name
549549

550550
data ExportsAs = ExportName | ExportPattern | ExportFamily | ExportAll
551551
deriving (Eq)
@@ -1012,7 +1012,7 @@ occursUnqualified symbol ImportDecl{..}
10121012
occursUnqualified _ _ = False
10131013

10141014
symbolOccursIn :: T.Text -> IE GhcPs -> Bool
1015-
symbolOccursIn symb = any ((== symb). printOutputableText) . ieNames
1015+
symbolOccursIn symb = any ((== symb). printOutputable) . ieNames
10161016

10171017
targetModuleName :: ModuleTarget -> ModuleName
10181018
targetModuleName ImplicitPrelude{} = mkModuleName "Prelude"
@@ -1046,12 +1046,12 @@ disambiguateSymbol pm fileContents Diagnostic {..} (T.unpack -> symbol) = \case
10461046
in Right <$> [ if parensed
10471047
then Rewrite (rangeToSrcSpan "<dummy>" _range) $ \df ->
10481048
liftParseAST @(HsExpr GhcPs) df $
1049-
printOutputable $
1049+
show $ printOutputable $
10501050
HsVar @GhcPs noExtField $
10511051
reLocA $ L (mkGeneralSrcSpan "") rdr
10521052
else Rewrite (rangeToSrcSpan "<dummy>" _range) $ \df ->
10531053
liftParseAST @RdrName df $
1054-
printOutputable $ L (mkGeneralSrcSpan "") rdr
1054+
show $ printOutputable $ L (mkGeneralSrcSpan "") rdr
10551055
]
10561056
findImportDeclByRange :: [LImportDecl GhcPs] -> Range -> Maybe (LImportDecl GhcPs)
10571057
findImportDeclByRange xs range = find (\(L (locA -> l) _)-> srcSpanToRange l == Just range) xs
@@ -1422,7 +1422,7 @@ newImport modName mSymbol mQual hiding = NewImport impStmt
14221422
symImp
14231423
| Just symbol <- mSymbol
14241424
, symOcc <- mkVarOcc $ T.unpack symbol =
1425-
" (" <> printOutputableText (parenSymOcc symOcc $ ppr symOcc) <> ")"
1425+
" (" <> printOutputable (parenSymOcc symOcc $ ppr symOcc) <> ")"
14261426
| otherwise = ""
14271427
impStmt =
14281428
"import "
@@ -1616,32 +1616,32 @@ smallerRangesForBindingExport lies b =
16161616
b' = wrapOperatorInParens . unqualify $ b
16171617
#if !MIN_VERSION_ghc(9,2,0)
16181618
ranges' (L _ (IEThingWith _ thing _ inners labels))
1619-
| printOutputable thing == b' = []
1619+
| show (printOutputable thing) == b' = []
16201620
| otherwise =
1621-
[ locA l' | L l' x <- inners, printOutputable x == b']
1622-
++ [ l' | L l' x <- labels, printOutputable x == b']
1621+
[ locA l' | L l' x <- inners, show (printOutputable x) == b']
1622+
++ [ l' | L l' x <- labels, show (printOutputable x) == b']
16231623
#else
16241624
ranges' (L _ (IEThingWith _ thing _ inners))
1625-
| printOutputable thing == b' = []
1625+
| show (printOutputable thing) == b' = []
16261626
| otherwise =
1627-
[ locA l' | L l' x <- inners, printOutputable x == b']
1627+
[ locA l' | L l' x <- inners, show (printOutputable x) == b']
16281628
#endif
16291629
ranges' _ = []
16301630

16311631
rangesForBinding' :: String -> LIE GhcPs -> [SrcSpan]
1632-
rangesForBinding' b (L (locA -> l) x@IEVar{}) | printOutputable x == b = [l]
1633-
rangesForBinding' b (L (locA -> l) x@IEThingAbs{}) | printOutputable x == b = [l]
1634-
rangesForBinding' b (L (locA -> l) (IEThingAll _ x)) | printOutputable x == b = [l]
1632+
rangesForBinding' b (L (locA -> l) x@IEVar{}) | show (printOutputable x) == b = [l]
1633+
rangesForBinding' b (L (locA -> l) x@IEThingAbs{}) | show (printOutputable x) == b = [l]
1634+
rangesForBinding' b (L (locA -> l) (IEThingAll _ x)) | show (printOutputable x) == b = [l]
16351635
#if !MIN_VERSION_ghc(9,2,0)
16361636
rangesForBinding' b (L l (IEThingWith _ thing _ inners labels))
16371637
#else
16381638
rangesForBinding' b (L (locA -> l) (IEThingWith _ thing _ inners))
16391639
#endif
1640-
| printOutputable thing == b = [l]
1640+
| show (printOutputable thing) == b = [l]
16411641
| otherwise =
1642-
[ locA l' | L l' x <- inners, printOutputable x == b]
1642+
[ locA l' | L l' x <- inners, show (printOutputable x) == b]
16431643
#if !MIN_VERSION_ghc(9,2,0)
1644-
++ [ l' | L l' x <- labels, printOutputable x == b]
1644+
++ [ l' | L l' x <- labels, show (printOutputable x) == b]
16451645
#endif
16461646
rangesForBinding' _ _ = []
16471647

0 commit comments

Comments
 (0)