@@ -13,14 +13,14 @@ import Control.Monad.IO.Class
1313import Data.Functor
1414import Data.Generics
1515import Data.Maybe
16- import Data.Text (Text , pack )
1716import qualified Data.Text as T
1817import Development.IDE.Core.Rules
1918import Development.IDE.Core.Shake
2019import Development.IDE.GHC.Compat
2120import Development.IDE.GHC.Error (rangeToRealSrcSpan ,
2221 realSrcSpanToRange )
2322import Development.IDE.Types.Location
23+ import Development.IDE.GHC.Util (printOutputable )
2424import Language.LSP.Server (LspM )
2525import 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 = pprText 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
7070documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
7171documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
7272 = Just (defDocumentSymbol l :: DocumentSymbol )
73- { _name = showRdrName n
74- <> (case pprText fdTyVars of
73+ { _name = printOutputable n
74+ <> (case printOutputable fdTyVars of
7575 " " -> " "
7676 t -> " " <> t
7777 )
78- , _detail = Just $ pprText fdInfo
78+ , _detail = Just $ printOutputable fdInfo
7979 , _kind = SkFunction
8080 }
8181documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
8282 = Just (defDocumentSymbol l :: DocumentSymbol )
83- { _name = showRdrName name
84- <> (case pprText 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 = showRdrName 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 }
101101documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
102102 = Just (defDocumentSymbol l :: DocumentSymbol )
103- { _name = showRdrName name
103+ { _name = printOutputable name
104104 , _kind = SkStruct
105105 , _children =
106106 Just $ List
107107 [ (defDocumentSymbol l :: DocumentSymbol )
108- { _name = showRdrName 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 = showRdrName (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 = showRdrName 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
149149documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ SynDecl { tcdLName = L (locA -> (RealSrcSpan l' _)) n })) = Just
150- (defDocumentSymbol l :: DocumentSymbol ) { _name = showRdrName n
150+ (defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputable n
151151 , _kind = SkTypeParameter
152152 , _selectionRange = realSrcSpanToRange l'
153153 }
154154documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ ClsInstD { cid_inst = ClsInstDecl { cid_poly_ty } }))
155- = Just (defDocumentSymbol l :: DocumentSymbol ) { _name = pprText 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
161161documentSymbolForDecl (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 = showRdrName (unLoc feqn_tycon) <> " " <> T. unwords
165- (map pprText 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_
171171documentSymbolForDecl (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 = showRdrName (unLoc feqn_tycon) <> " " <> T. unwords
175- (map pprText feqn_pats)
174+ { _name = printOutputable (unLoc feqn_tycon) <> " " <> T. unwords
175+ (map printOutputable feqn_pats)
176176 , _kind = SkInterface
177177 }
178178documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
179179 gfindtype deriv_type <&> \ (L (_ :: SrcSpan ) name) ->
180- (defDocumentSymbol l :: DocumentSymbol ) { _name = pprText @ (HsType GhcPs )
180+ (defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputable @ (HsType GhcPs )
181181 name
182182 , _kind = SkInterface
183183 }
184184documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind {fun_id = L _ name})) = Just
185185 (defDocumentSymbol l :: DocumentSymbol )
186- { _name = showRdrName name
186+ { _name = printOutputable name
187187 , _kind = SkFunction
188188 }
189189documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind {pat_lhs})) = Just
190190 (defDocumentSymbol l :: DocumentSymbol )
191- { _name = pprText 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 = showRdrName $ unLoc $ fd_name x
207+ where name = printOutputable $ unLoc $ fd_name x
208208
209209documentSymbolForDecl _ = Nothing
210210
@@ -228,7 +228,7 @@ documentSymbolForImportSummary importSymbols =
228228documentSymbolForImport :: LImportDecl GhcPs -> Maybe DocumentSymbol
229229documentSymbolForImport (L (locA -> (RealSrcSpan l _)) ImportDecl { ideclName, ideclQualified }) = Just
230230 (defDocumentSymbol l :: DocumentSymbol )
231- { _name = " import " <> pprText 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" }
@@ -249,12 +249,6 @@ defDocumentSymbol l = DocumentSymbol { .. } where
249249 _children = Nothing
250250 _tags = Nothing
251251
252- showRdrName :: RdrName -> Text
253- showRdrName = pprText
254-
255- pprText :: Outputable a => a -> Text
256- pprText = pack . showSDocUnsafe . ppr
257-
258252-- the version of getConNames for ghc9 is restricted to only the renaming phase
259253#if !MIN_VERSION_ghc(9,2,0)
260254getConNames' :: ConDecl GhcPs -> [Located (IdP GhcPs )]
0 commit comments