@@ -13,15 +13,14 @@ import Control.Monad.IO.Class
13
13
import Data.Functor
14
14
import Data.Generics
15
15
import Data.Maybe
16
- import Data.Text (Text )
17
16
import qualified Data.Text as T
18
17
import Development.IDE.Core.Rules
19
18
import Development.IDE.Core.Shake
20
19
import Development.IDE.GHC.Compat
21
20
import Development.IDE.GHC.Error (rangeToRealSrcSpan ,
22
21
realSrcSpanToRange )
23
22
import Development.IDE.Types.Location
24
- import Development.IDE.GHC.Util (showGhc )
23
+ import Development.IDE.GHC.Util (printOutputableText )
25
24
import Language.LSP.Server (LspM )
26
25
import Language.LSP.Types (DocumentSymbol (.. ),
27
26
DocumentSymbolParams (DocumentSymbolParams , _textDocument ),
@@ -48,7 +47,7 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
48
47
moduleSymbol = hsmodName >>= \ case
49
48
(L (locA -> (RealSrcSpan l _)) m) -> Just $
50
49
(defDocumentSymbol l :: DocumentSymbol )
51
- { _name = showGhc m
50
+ { _name = printOutputableText m
52
51
, _kind = SkFile
53
52
, _range = Range (Position 0 0 ) (Position maxBound 0 ) -- _ltop is 0 0 0 0
54
53
}
@@ -71,18 +70,18 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
71
70
documentSymbolForDecl :: LHsDecl GhcPs -> Maybe DocumentSymbol
72
71
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ FamDecl { tcdFam = FamilyDecl { fdLName = L _ n, fdInfo, fdTyVars } }))
73
72
= Just (defDocumentSymbol l :: DocumentSymbol )
74
- { _name = showRdrName n
75
- <> (case showGhc fdTyVars of
73
+ { _name = printOutputableText n
74
+ <> (case printOutputableText fdTyVars of
76
75
" " -> " "
77
76
t -> " " <> t
78
77
)
79
- , _detail = Just $ showGhc fdInfo
78
+ , _detail = Just $ printOutputableText fdInfo
80
79
, _kind = SkFunction
81
80
}
82
81
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLName = L _ name, tcdSigs, tcdTyVars }))
83
82
= Just (defDocumentSymbol l :: DocumentSymbol )
84
- { _name = showRdrName name
85
- <> (case showGhc tcdTyVars of
83
+ { _name = printOutputableText name
84
+ <> (case printOutputableText tcdTyVars of
86
85
" " -> " "
87
86
t -> " " <> t
88
87
)
@@ -91,7 +90,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
91
90
, _children =
92
91
Just $ List
93
92
[ (defDocumentSymbol l :: DocumentSymbol )
94
- { _name = showRdrName n
93
+ { _name = printOutputableText n
95
94
, _kind = SkMethod
96
95
, _selectionRange = realSrcSpanToRange l'
97
96
}
@@ -101,12 +100,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ ClassDecl { tcdLNa
101
100
}
102
101
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLName = L _ name, tcdDataDefn = HsDataDefn { dd_cons } }))
103
102
= Just (defDocumentSymbol l :: DocumentSymbol )
104
- { _name = showRdrName name
103
+ { _name = printOutputableText name
105
104
, _kind = SkStruct
106
105
, _children =
107
106
Just $ List
108
107
[ (defDocumentSymbol l :: DocumentSymbol )
109
- { _name = showRdrName n
108
+ { _name = printOutputableText n
110
109
, _kind = SkConstructor
111
110
, _selectionRange = realSrcSpanToRange l'
112
111
#if MIN_VERSION_ghc(9,2,0)
@@ -124,7 +123,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
124
123
where
125
124
cvtFld :: LFieldOcc GhcPs -> Maybe DocumentSymbol
126
125
cvtFld (L (RealSrcSpan l _) n) = Just $ (defDocumentSymbol l :: DocumentSymbol )
127
- { _name = showRdrName (unLoc (rdrNameFieldOcc n))
126
+ { _name = printOutputableText (unLoc (rdrNameFieldOcc n))
128
127
, _kind = SkField
129
128
}
130
129
cvtFld _ = Nothing
@@ -139,7 +138,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
139
138
-- | Extract the record fields of a constructor
140
139
conArgRecordFields (RecCon (L _ lcdfs)) = Just $ List
141
140
[ (defDocumentSymbol l :: DocumentSymbol )
142
- { _name = showRdrName n
141
+ { _name = printOutputableText n
143
142
, _kind = SkField
144
143
}
145
144
| L _ cdf <- lcdfs
@@ -148,12 +147,12 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
148
147
conArgRecordFields _ = Nothing
149
148
#endif
150
149
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
152
151
, _kind = SkTypeParameter
153
152
, _selectionRange = realSrcSpanToRange l'
154
153
}
155
154
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
157
156
, _kind = SkInterface
158
157
}
159
158
#if MIN_VERSION_ghc(9,2,0)
@@ -162,8 +161,8 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ DataFamInstD { dfi
162
161
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ DataFamInstD { dfid_inst = DataFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
163
162
#endif
164
163
= 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)
167
166
, _kind = SkInterface
168
167
}
169
168
#if MIN_VERSION_ghc(9,2,0)
@@ -172,24 +171,24 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (InstD _ TyFamInstD { tfid_
172
171
documentSymbolForDecl (L (RealSrcSpan l _) (InstD _ TyFamInstD { tfid_inst = TyFamInstDecl HsIB { hsib_body = FamEqn { feqn_tycon, feqn_pats } } }))
173
172
#endif
174
173
= 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)
177
176
, _kind = SkInterface
178
177
}
179
178
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (DerivD _ DerivDecl { deriv_type })) =
180
179
gfindtype deriv_type <&> \ (L (_ :: SrcSpan ) name) ->
181
- (defDocumentSymbol l :: DocumentSymbol ) { _name = showGhc @ (HsType GhcPs )
180
+ (defDocumentSymbol l :: DocumentSymbol ) { _name = printOutputableText @ (HsType GhcPs )
182
181
name
183
182
, _kind = SkInterface
184
183
}
185
184
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ FunBind {fun_id = L _ name})) = Just
186
185
(defDocumentSymbol l :: DocumentSymbol )
187
- { _name = showRdrName name
186
+ { _name = printOutputableText name
188
187
, _kind = SkFunction
189
188
}
190
189
documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ValD _ PatBind {pat_lhs})) = Just
191
190
(defDocumentSymbol l :: DocumentSymbol )
192
- { _name = showGhc pat_lhs
191
+ { _name = printOutputableText pat_lhs
193
192
, _kind = SkFunction
194
193
}
195
194
@@ -205,7 +204,7 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (ForD _ x)) = Just
205
204
ForeignExport {} -> Just " export"
206
205
XForeignDecl {} -> Nothing
207
206
}
208
- where name = showRdrName $ unLoc $ fd_name x
207
+ where name = printOutputableText $ unLoc $ fd_name x
209
208
210
209
documentSymbolForDecl _ = Nothing
211
210
@@ -229,7 +228,7 @@ documentSymbolForImportSummary importSymbols =
229
228
documentSymbolForImport :: LImportDecl GhcPs -> Maybe DocumentSymbol
230
229
documentSymbolForImport (L (locA -> (RealSrcSpan l _)) ImportDecl { ideclName, ideclQualified }) = Just
231
230
(defDocumentSymbol l :: DocumentSymbol )
232
- { _name = " import " <> showGhc ideclName
231
+ { _name = " import " <> printOutputableText ideclName
233
232
, _kind = SkModule
234
233
#if MIN_VERSION_ghc(8,10,0)
235
234
, _detail = case ideclQualified of { NotQualified -> Nothing ; _ -> Just " qualified" }
@@ -250,9 +249,6 @@ defDocumentSymbol l = DocumentSymbol { .. } where
250
249
_children = Nothing
251
250
_tags = Nothing
252
251
253
- showRdrName :: RdrName -> Text
254
- showRdrName = showGhc
255
-
256
252
-- the version of getConNames for ghc9 is restricted to only the renaming phase
257
253
#if !MIN_VERSION_ghc(9,2,0)
258
254
getConNames' :: ConDecl GhcPs -> [Located (IdP GhcPs )]
0 commit comments