@@ -35,7 +35,7 @@ import Development.IDE.GHC.ExactPrint (ASTElement (parseAST),
35
35
import Development.IDE.Spans.Common
36
36
import FieldLabel (flLabel )
37
37
import GHC.Exts (IsList (fromList ))
38
- import GhcPlugins (sigPrec )
38
+ import GhcPlugins (mkRdrUnqual , sigPrec )
39
39
import Language.Haskell.GHC.ExactPrint
40
40
import Language.Haskell.GHC.ExactPrint.Types (DeltaPos (DP ),
41
41
KeywordId (G ), mkAnnKey )
@@ -200,44 +200,48 @@ extendImport mparent identifier lDecl@(L l _) =
200
200
Rewrite l $ \ df -> do
201
201
case mparent of
202
202
Just parent -> extendImportViaParent df parent identifier lDecl
203
- _ -> extendImportTopLevel df identifier lDecl
203
+ _ -> extendImportTopLevel identifier lDecl
204
204
205
- -- | Add an identifier to import list
205
+ -- | Add an identifier or a data type to import list
206
206
--
207
207
-- extendImportTopLevel "foo" AST:
208
208
--
209
209
-- import A --> Error
210
210
-- import A (foo) --> Error
211
211
-- import A (bar) --> import A (bar, foo)
212
- extendImportTopLevel :: DynFlags -> String -> LImportDecl GhcPs -> TransformT (Either String ) (LImportDecl GhcPs )
213
- extendImportTopLevel df idnetifier (L l it@ ImportDecl {.. })
212
+ extendImportTopLevel ::
213
+ -- | rendered
214
+ String ->
215
+ LImportDecl GhcPs ->
216
+ TransformT (Either String ) (LImportDecl GhcPs )
217
+ extendImportTopLevel thing (L l it@ ImportDecl {.. })
214
218
| Just (hide, L l' lies) <- ideclHiding
215
219
, hasSibling <- not $ null lies = do
216
220
src <- uniqueSrcSpanT
217
221
top <- uniqueSrcSpanT
218
- rdr <- liftParseAST df idnetifier
222
+ let rdr = L src $ mkRdrUnqual $ mkVarOcc thing
219
223
220
224
let alreadyImported =
221
225
showNameWithoutUniques (occName (unLoc rdr))
222
226
`elem` map (showNameWithoutUniques @ OccName ) (listify (const True ) lies)
223
227
when alreadyImported $
224
- lift (Left $ idnetifier <> " already imported" )
228
+ lift (Left $ thing <> " already imported" )
225
229
226
230
let lie = L src $ IEName rdr
227
231
x = L top $ IEVar noExtField lie
228
232
if x `elem` lies
229
- then lift (Left $ idnetifier <> " already imported" )
233
+ then lift (Left $ thing <> " already imported" )
230
234
else do
231
235
when hasSibling $
232
236
addTrailingCommaT (last lies)
233
237
addSimpleAnnT x (DP (0 , if hasSibling then 1 else 0 )) []
234
- addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier
238
+ addSimpleAnnT rdr dp00 [( G AnnVal , dp00)]
235
239
-- Parens are attachted to `lies`, so if `lies` was empty previously,
236
240
-- we need change the ann key from `[]` to `:` to keep parens and other anns.
237
241
unless hasSibling $
238
242
transferAnn (L l' lies) (L l' [x]) id
239
243
return $ L l it{ideclHiding = Just (hide, L l' $ lies ++ [x])}
240
- extendImportTopLevel _ _ _ = lift $ Left " Unable to extend the import list"
244
+ extendImportTopLevel _ _ = lift $ Left " Unable to extend the import list"
241
245
242
246
-- | Add an identifier with its parent to import list
243
247
--
@@ -249,7 +253,14 @@ extendImportTopLevel _ _ _ = lift $ Left "Unable to extend the import list"
249
253
-- import A () --> import A (Bar(Cons))
250
254
-- import A (Foo, Bar) --> import A (Foo, Bar(Cons))
251
255
-- import A (Foo, Bar()) --> import A (Foo, Bar(Cons))
252
- extendImportViaParent :: DynFlags -> String -> String -> LImportDecl GhcPs -> TransformT (Either String ) (LImportDecl GhcPs )
256
+ extendImportViaParent ::
257
+ DynFlags ->
258
+ -- | parent (already parenthesized if needs)
259
+ String ->
260
+ -- | rendered child
261
+ String ->
262
+ LImportDecl GhcPs ->
263
+ TransformT (Either String ) (LImportDecl GhcPs )
253
264
extendImportViaParent df parent child (L l it@ ImportDecl {.. })
254
265
| Just (hide, L l' lies) <- ideclHiding = go hide l' [] lies
255
266
where
@@ -260,8 +271,8 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
260
271
-- ThingAbs ie => ThingWith ie child
261
272
| parent == unIEWrappedName ie = do
262
273
srcChild <- uniqueSrcSpanT
263
- childRdr <- liftParseAST df child
264
- let childLIE = L srcChild $ IEName childRdr
274
+ let childRdr = L srcChild $ mkRdrUnqual $ mkVarOcc child
275
+ childLIE = L srcChild $ IEName childRdr
265
276
x :: LIE GhcPs = L ll' $ IEThingWith noExtField absIE NoIEWildcard [childLIE] []
266
277
-- take anns from ThingAbs, and attatch parens to it
267
278
transferAnn lAbs x $ \ old -> old{annsDP = annsDP old ++ [(G AnnOpenP , DP (0 , 1 )), (G AnnCloseP , dp00)]}
@@ -273,7 +284,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
273
284
, hasSibling <- not $ null lies' =
274
285
do
275
286
srcChild <- uniqueSrcSpanT
276
- childRdr <- liftParseAST df child
287
+ let childRdr = L srcChild $ mkRdrUnqual $ mkVarOcc child
277
288
278
289
let alreadyImported =
279
290
showNameWithoutUniques (occName (unLoc childRdr))
@@ -284,7 +295,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
284
295
when hasSibling $
285
296
addTrailingCommaT (last lies')
286
297
let childLIE = L srcChild $ IEName childRdr
287
- addSimpleAnnT childRdr (DP (0 , if hasSibling then 1 else 0 )) $ unqalDP $ hasParen child
298
+ addSimpleAnnT childRdr (DP (0 , if hasSibling then 1 else 0 )) [( G AnnVal , dp00)]
288
299
return $ L l it{ideclHiding = Just (hide, L l' $ reverse pre ++ [L l'' (IEThingWith noExtField twIE NoIEWildcard (lies' ++ [childLIE]) [] )] ++ xs)}
289
300
go hide l' pre (x : xs) = go hide l' (x : pre) xs
290
301
go hide l' pre []
@@ -294,14 +305,18 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
294
305
srcParent <- uniqueSrcSpanT
295
306
srcChild <- uniqueSrcSpanT
296
307
parentRdr <- liftParseAST df parent
297
- childRdr <- liftParseAST df child
308
+ let childRdr = L srcChild $ mkRdrUnqual $ mkVarOcc child
309
+ isParentOperator = hasParen parent
298
310
when hasSibling $
299
311
addTrailingCommaT (head pre)
300
- let parentLIE = L srcParent $ IEName parentRdr
312
+ let parentLIE = L srcParent $ ( if isParentOperator then IEType else IEName ) parentRdr
301
313
childLIE = L srcChild $ IEName childRdr
302
314
x :: LIE GhcPs = L l'' $ IEThingWith noExtField parentLIE NoIEWildcard [childLIE] []
303
- addSimpleAnnT parentRdr (DP (0 , if hasSibling then 1 else 0 )) $ unqalDP $ hasParen parent
304
- addSimpleAnnT childRdr (DP (0 , 0 )) $ unqalDP $ hasParen child
315
+ -- Add AnnType for the parent if it's parenthesized (type operator)
316
+ when isParentOperator $
317
+ addSimpleAnnT parentLIE (DP (0 , 0 )) [(G AnnType , DP (0 , 0 ))]
318
+ addSimpleAnnT parentRdr (DP (0 , if hasSibling then 1 else 0 )) $ unqalDP 1 isParentOperator
319
+ addSimpleAnnT childRdr (DP (0 , 0 )) [(G AnnVal , dp00)]
305
320
addSimpleAnnT x (DP (0 , 0 )) [(G AnnOpenP , DP (0 , 1 )), (G AnnCloseP , DP (0 , 0 ))]
306
321
-- Parens are attachted to `pre`, so if `pre` was empty previously,
307
322
-- we need change the ann key from `[]` to `:` to keep parens and other anns.
@@ -317,10 +332,10 @@ hasParen :: String -> Bool
317
332
hasParen (' (' : _) = True
318
333
hasParen _ = False
319
334
320
- unqalDP :: Bool -> [(KeywordId , DeltaPos )]
321
- unqalDP paren =
335
+ unqalDP :: Int -> Bool -> [(KeywordId , DeltaPos )]
336
+ unqalDP c paren =
322
337
( if paren
323
- then \ x -> (G AnnOpenP , dp00 ) : x : [(G AnnCloseP , dp00)]
338
+ then \ x -> (G AnnOpenP , DP ( 0 , c) ) : x : [(G AnnCloseP , dp00)]
324
339
else pure
325
340
)
326
341
(G AnnVal , dp00)
@@ -364,7 +379,7 @@ extendHiding symbol (L l idecls) mlies df = do
364
379
, (G AnnCloseP , DP (0 , 0 ))
365
380
]
366
381
addSimpleAnnT x (DP (0 , 0 )) []
367
- addSimpleAnnT rdr dp00 $ unqalDP $ isOperator $ unLoc rdr
382
+ addSimpleAnnT rdr dp00 $ unqalDP 0 $ isOperator $ unLoc rdr
368
383
if hasSibling
369
384
then when hasSibling $ do
370
385
addTrailingCommaT x
0 commit comments