Skip to content

Commit 02a516e

Browse files
committed
Remove unnecessary exports & Rename
1 parent c4d442c commit 02a516e

File tree

20 files changed

+127
-148
lines changed

20 files changed

+127
-148
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 . showGhc) x
1304+
Just x -> return $ map (first $ T.unpack . printOutputableText) 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: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,10 @@ import qualified Outputable as Out
6767
import SrcLoc
6868
#endif
6969

70+
-- | A compatible function to print `Outputable` instances
71+
-- without unique symbols.
72+
--
73+
-- It print with a user-friendly style like: `a_a4ME` as `a`.
7074
printWithoutUniques :: Outputable a => a -> String
7175
printWithoutUniques =
7276
#if MIN_VERSION_ghc(9,2,0)
@@ -96,19 +100,15 @@ printSDocQualifiedUnsafe unqual doc =
96100
showSDocForUser unsafeGlobalDynFlags unqual doc
97101
#endif
98102

99-
100-
#if MIN_VERSION_ghc(9,2,0)
101-
#else
102-
#if MIN_VERSION_ghc(9,0,0)
103+
#if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,2,0)
103104
oldRenderWithStyle dflags sdoc sty = Out.renderWithStyle (initSDocContext dflags sty) sdoc
104105
oldMkUserStyle _ = Out.mkUserStyle
105106
oldMkErrStyle _ = Out.mkErrStyle
106107

107108
oldFormatErrDoc :: DynFlags -> Err.ErrDoc -> Out.SDoc
108109
oldFormatErrDoc dflags = Err.formatErrDoc dummySDocContext
109110
where dummySDocContext = initSDocContext dflags Out.defaultUserStyle
110-
111-
#else
111+
#elif !MIN_VERSION_ghc(9,2,0)
112112
oldRenderWithStyle :: DynFlags -> Out.SDoc -> Out.PprStyle -> String
113113
oldRenderWithStyle = Out.renderWithStyle
114114

@@ -121,7 +121,6 @@ oldMkErrStyle = Out.mkErrStyle
121121
oldFormatErrDoc :: DynFlags -> Err.ErrDoc -> Out.SDoc
122122
oldFormatErrDoc = Err.formatErrDoc
123123
#endif
124-
#endif
125124

126125
pprWarning :: PsWarning -> MsgEnvelope DecoratedSDoc
127126
pprWarning =

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 = prettyPrint
49+
instance Show CoreModule where show = printOutputable
5050
instance NFData CoreModule where rnf = rwhnf
51-
instance Show CgGuts where show = prettyPrint . cg_module
51+
instance Show CgGuts where 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 = prettyPrint
56+
instance Show Linkable where 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 = prettyPrint
64-
instance Show InteractiveImport where show = prettyPrint
65-
instance Show PackageName where show = prettyPrint
63+
instance Show PackageFlag where show = printOutputable
64+
instance Show InteractiveImport where show = printOutputable
65+
instance Show PackageName where show = printOutputable
6666

6767
#if !MIN_VERSION_ghc(9,0,1)
68-
instance Show ComponentId where show = prettyPrint
69-
instance Show SourcePackageId where show = prettyPrint
68+
instance Show ComponentId where show = printOutputable
69+
instance Show SourcePackageId where 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 = prettyPrint
79+
instance Show UnitId where 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 = prettyPrint
89+
instance Outputable a => Show (GenLocated SrcSpan a) where 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 = prettyPrint
210+
instance Show OccName where show = printOutputable
211211
instance Hashable OccName where hashWithSalt s n = hashWithSalt s (getKey $ getUnique n)

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

Lines changed: 17 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -27,10 +27,8 @@ module Development.IDE.GHC.Util(
2727
dontWriteHieFiles,
2828
disableWarningsAsErrors,
2929
traceAst,
30-
showGhc,
31-
showGhcWithUniques,
32-
prettyPrint,
33-
prettyPrintWithUniques
30+
printOutputable,
31+
printOutputableText
3432
) where
3533

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

136134
-- | Pretty print a 'RdrName' wrapping operators in parens
137135
printRdrName :: RdrName -> String
138-
printRdrName name = prettyPrint $ parenSymOcc rn (ppr rn)
136+
printRdrName name = printOutputable $ parenSymOcc rn (ppr rn)
139137
where
140138
rn = rdrNameOcc name
141139

@@ -300,7 +298,7 @@ traceAst lbl x
300298
#if MIN_VERSION_ghc(9,2,0)
301299
renderDump = renderWithContext defaultSDocContext{sdocStyle = defaultDumpStyle, sdocPprDebug = True}
302300
#else
303-
renderDump = prettyPrintWithUniques
301+
renderDump = showSDocUnsafe . ppr
304302
#endif
305303
htmlDump = showAstDataHtml x
306304
doTrace = unsafePerformIO $ do
@@ -321,38 +319,24 @@ instance Outputable SDoc where
321319
ppr = id
322320
#endif
323321

324-
-- | Print a GHC value by default `showSDocUnsafe`.
325-
--
326-
-- You may prefer `prettyPrint` unless you know what you are doing.
327-
--
328-
-- It internal using `unsafeGlobalDynFlags`.
329-
--
330-
-- `String` version of `showGhcWithUniques`.
331-
prettyPrintWithUniques :: Outputable a => a -> String
332-
prettyPrintWithUniques = showSDocUnsafe . ppr
333-
334322
-- | Print a GHC value in `defaultUserStyle` without unique symbols.
335323
--
336-
-- This is the most common print utility, will print with a user friendly style like: `a_a4ME` as `a`.
324+
-- This is the most common print utility, will print with a user-friendly style like: `a_a4ME` as `a`.
337325
--
338-
-- It internal using `unsafeGlobalDynFlags`.
326+
-- It internal using `showSDocUnsafe` with `unsafeGlobalDynFlags`.
339327
--
340-
-- `String` version of `showGhc`.
341-
prettyPrint :: Outputable a => a -> String
342-
prettyPrint = printWithoutUniques
343-
344-
-- | Print a GHC value by default `showSDocUnsafe`.
345-
--
346-
-- You may prefer `showGhc` unless you know what you are doing.
347-
--
348-
-- It internal using `unsafeGlobalDynFlags`.
349-
showGhcWithUniques :: Outputable a => a -> T.Text
350-
showGhcWithUniques = T.pack . showSDocUnsafe . ppr
328+
-- You may prefer `printOutputableText` if `Text` is expected to return.
329+
printOutputable :: Outputable a => a -> String
330+
printOutputable = printWithoutUniques
331+
{-# INLINE printOutputable #-}
351332

352333
-- | Print a GHC value in `defaultUserStyle` without unique symbols.
353334
--
354-
-- This is the most common print utility, will print with a user friendly style like: `a_a4ME` as `a`.
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`.
355338
--
356-
-- It internal using `unsafeGlobalDynFlags`.
357-
showGhc :: Outputable a => a -> T.Text
358-
showGhc = T.pack . printWithoutUniques
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 & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -13,15 +13,14 @@ import Control.Monad.IO.Class
1313
import Data.Functor
1414
import Data.Generics
1515
import Data.Maybe
16-
import Data.Text (Text)
1716
import qualified Data.Text as T
1817
import Development.IDE.Core.Rules
1918
import Development.IDE.Core.Shake
2019
import Development.IDE.GHC.Compat
2120
import Development.IDE.GHC.Error (rangeToRealSrcSpan,
2221
realSrcSpanToRange)
2322
import Development.IDE.Types.Location
24-
import Development.IDE.GHC.Util (showGhc)
23+
import Development.IDE.GHC.Util (printOutputableText)
2524
import Language.LSP.Server (LspM)
2625
import Language.LSP.Types (DocumentSymbol (..),
2726
DocumentSymbolParams (DocumentSymbolParams, _textDocument),
@@ -48,7 +47,7 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
4847
moduleSymbol = hsmodName >>= \case
4948
(L (locA -> (RealSrcSpan l _)) m) -> Just $
5049
(defDocumentSymbol l :: DocumentSymbol)
51-
{ _name = showGhc m
50+
{ _name = printOutputableText m
5251
, _kind = SkFile
5352
, _range = Range (Position 0 0) (Position maxBound 0) -- _ltop is 0 0 0 0
5453
}
@@ -71,18 +70,18 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
7170
documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
7271
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
7372
= Just (defDocumentSymbol l :: DocumentSymbol)
74-
{ _name = showRdrName n
75-
<> (case showGhc fdTyVars of
73+
{ _name = printOutputableText n
74+
<> (case printOutputableText fdTyVars of
7675
"" -> ""
7776
t -> " " <> t
7877
)
79-
, _detail = Just $ showGhc fdInfo
78+
, _detail = Just $ printOutputableText fdInfo
8079
, _kind = SkFunction
8180
}
8281
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
8382
= Just (defDocumentSymbol l :: DocumentSymbol)
84-
{ _name = showRdrName name
85-
<> (case showGhc tcdTyVars of
83+
{ _name = printOutputableText name
84+
<> (case printOutputableText tcdTyVars of
8685
"" -> ""
8786
t -> " " <> t
8887
)
@@ -91,7 +90,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
9190
, _children =
9291
Just $ List
9392
[ (defDocumentSymbol l :: DocumentSymbol)
94-
{ _name = showRdrName n
93+
{ _name = printOutputableText n
9594
, _kind = SkMethod
9695
, _selectionRange = realSrcSpanToRange l'
9796
}
@@ -101,12 +100,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
101100
}
102101
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
103102
= Just (defDocumentSymbol l :: DocumentSymbol)
104-
{ _name = showRdrName name
103+
{ _name = printOutputableText name
105104
, _kind = SkStruct
106105
, _children =
107106
Just $ List
108107
[ (defDocumentSymbol l :: DocumentSymbol)
109-
{ _name = showRdrName n
108+
{ _name = printOutputableText n
110109
, _kind = SkConstructor
111110
, _selectionRange = realSrcSpanToRange l'
112111
#if MIN_VERSION_ghc(9,2,0)
@@ -124,7 +123,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
124123
where
125124
cvtFld :: LFieldOcc GhcPs -> Maybe DocumentSymbol
126125
cvtFld (L (RealSrcSpan l _) n) = Just $ (defDocumentSymbol l :: DocumentSymbol)
127-
{ _name = showRdrName (unLoc (rdrNameFieldOcc n))
126+
{ _name = printOutputableText (unLoc (rdrNameFieldOcc n))
128127
, _kind = SkField
129128
}
130129
cvtFld _ = Nothing
@@ -139,7 +138,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
139138
-- | Extract the record fields of a constructor
140139
conArgRecordFields (RecCon (L _ lcdfs)) = Just $ List
141140
[ (defDocumentSymbol l :: DocumentSymbol)
142-
{ _name = showRdrName n
141+
{ _name = printOutputableText n
143142
, _kind = SkField
144143
}
145144
| L _ cdf <- lcdfs
@@ -148,12 +147,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
148147
conArgRecordFields _ = Nothing
149148
#endif
150149
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
151-
(defDocumentSymbol l :: DocumentSymbol) { _name = showRdrName n
150+
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText n
152151
, _kind = SkTypeParameter
153152
, _selectionRange = realSrcSpanToRange l'
154153
}
155154
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
156-
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = showGhc cid_poly_ty
155+
= Just (defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText cid_poly_ty
157156
, _kind = SkInterface
158157
}
159158
#if MIN_VERSION_ghc(9,2,0)
@@ -162,8 +161,8 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
162161
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
163162
#endif
164163
= Just (defDocumentSymbol l :: DocumentSymbol)
165-
{ _name = showRdrName (unLoc feqn_tycon) <> " " <> T.unwords
166-
(map showGhc feqn_pats)
164+
{ _name = printOutputableText (unLoc feqn_tycon) <> " " <> T.unwords
165+
(map printOutputableText feqn_pats)
167166
, _kind = SkInterface
168167
}
169168
#if MIN_VERSION_ghc(9,2,0)
@@ -172,24 +171,24 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
172171
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
173172
#endif
174173
= Just (defDocumentSymbol l :: DocumentSymbol)
175-
{ _name = showRdrName (unLoc feqn_tycon) <> " " <> T.unwords
176-
(map showGhc feqn_pats)
174+
{ _name = printOutputableText (unLoc feqn_tycon) <> " " <> T.unwords
175+
(map printOutputableText feqn_pats)
177176
, _kind = SkInterface
178177
}
179178
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
180179
gfindtype deriv_type <&> \(L (_ :: SrcSpan) name) ->
181-
(defDocumentSymbol l :: DocumentSymbol) { _name = showGhc @(HsType GhcPs)
180+
(defDocumentSymbol l :: DocumentSymbol) { _name = printOutputableText @(HsType GhcPs)
182181
name
183182
, _kind = SkInterface
184183
}
185184
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind{fun_id = L _ name})) = Just
186185
(defDocumentSymbol l :: DocumentSymbol)
187-
{ _name = showRdrName name
186+
{ _name = printOutputableText name
188187
, _kind = SkFunction
189188
}
190189
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind{pat_lhs})) = Just
191190
(defDocumentSymbol l :: DocumentSymbol)
192-
{ _name = showGhc pat_lhs
191+
{ _name = printOutputableText pat_lhs
193192
, _kind = SkFunction
194193
}
195194

@@ -205,7 +204,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
205204
ForeignExport{} -> Just "export"
206205
XForeignDecl{} -> Nothing
207206
}
208-
where name = showRdrName $ unLoc $ fd_name x
207+
where name = printOutputableText $ unLoc $ fd_name x
209208

210209
documentSymbolForDecl _ = Nothing
211210

@@ -229,7 +228,7 @@ documentSymbolForImportSummary importSymbols =
229228
documentSymbolForImport :: LImportDecl GhcPs -> Maybe DocumentSymbol
230229
documentSymbolForImport (L (locA -> (RealSrcSpan l _)) ImportDecl { ideclName, ideclQualified }) = Just
231230
(defDocumentSymbol l :: DocumentSymbol)
232-
{ _name = "import " <> showGhc ideclName
231+
{ _name = "import " <> printOutputableText ideclName
233232
, _kind = SkModule
234233
#if MIN_VERSION_ghc(8,10,0)
235234
, _detail = case ideclQualified of { NotQualified -> Nothing; _ -> Just "qualified" }
@@ -250,9 +249,6 @@ defDocumentSymbol l = DocumentSymbol { .. } where
250249
_children = Nothing
251250
_tags = Nothing
252251

253-
showRdrName :: RdrName -> Text
254-
showRdrName = showGhc
255-
256252
-- the version of getConNames for ghc9 is restricted to only the renaming phase
257253
#if !MIN_VERSION_ghc(9,2,0)
258254
getConNames' :: ConDecl GhcPs -> [Located (IdP GhcPs)]

0 commit comments

Comments
 (0)