@@ -35,7 +35,7 @@ import Development.IDE.GHC.ExactPrint (ASTElement (parseAST),
3535import Development.IDE.Spans.Common
3636import FieldLabel (flLabel )
3737import GHC.Exts (IsList (fromList ))
38- import GhcPlugins (sigPrec )
38+ import GhcPlugins (mkRdrUnqual , sigPrec )
3939import Language.Haskell.GHC.ExactPrint
4040import Language.Haskell.GHC.ExactPrint.Types (DeltaPos (DP ),
4141 KeywordId (G ), mkAnnKey )
@@ -200,44 +200,48 @@ extendImport mparent identifier lDecl@(L l _) =
200200 Rewrite l $ \ df -> do
201201 case mparent of
202202 Just parent -> extendImportViaParent df parent identifier lDecl
203- _ -> extendImportTopLevel df identifier lDecl
203+ _ -> extendImportTopLevel identifier lDecl
204204
205- -- | Add an identifier to import list
205+ -- | Add an identifier or a data type to import list
206206--
207207-- extendImportTopLevel "foo" AST:
208208--
209209-- import A --> Error
210210-- import A (foo) --> Error
211211-- 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 {.. })
214218 | Just (hide, L l' lies) <- ideclHiding
215219 , hasSibling <- not $ null lies = do
216220 src <- uniqueSrcSpanT
217221 top <- uniqueSrcSpanT
218- rdr <- liftParseAST df idnetifier
222+ let rdr = L src $ mkRdrUnqual $ mkVarOcc thing
219223
220224 let alreadyImported =
221225 showNameWithoutUniques (occName (unLoc rdr))
222226 `elem` map (showNameWithoutUniques @ OccName ) (listify (const True ) lies)
223227 when alreadyImported $
224- lift (Left $ idnetifier <> " already imported" )
228+ lift (Left $ thing <> " already imported" )
225229
226230 let lie = L src $ IEName rdr
227231 x = L top $ IEVar noExtField lie
228232 if x `elem` lies
229- then lift (Left $ idnetifier <> " already imported" )
233+ then lift (Left $ thing <> " already imported" )
230234 else do
231235 when hasSibling $
232236 addTrailingCommaT (last lies)
233237 addSimpleAnnT x (DP (0 , if hasSibling then 1 else 0 )) []
234- addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier
238+ addSimpleAnnT rdr dp00 [( G AnnVal , dp00)]
235239 -- Parens are attachted to `lies`, so if `lies` was empty previously,
236240 -- we need change the ann key from `[]` to `:` to keep parens and other anns.
237241 unless hasSibling $
238242 transferAnn (L l' lies) (L l' [x]) id
239243 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"
241245
242246-- | Add an identifier with its parent to import list
243247--
@@ -249,7 +253,14 @@ extendImportTopLevel _ _ _ = lift $ Left "Unable to extend the import list"
249253-- import A () --> import A (Bar(Cons))
250254-- import A (Foo, Bar) --> import A (Foo, Bar(Cons))
251255-- 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 )
253264extendImportViaParent df parent child (L l it@ ImportDecl {.. })
254265 | Just (hide, L l' lies) <- ideclHiding = go hide l' [] lies
255266 where
@@ -260,8 +271,8 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
260271 -- ThingAbs ie => ThingWith ie child
261272 | parent == unIEWrappedName ie = do
262273 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
265276 x :: LIE GhcPs = L ll' $ IEThingWith noExtField absIE NoIEWildcard [childLIE] []
266277 -- take anns from ThingAbs, and attatch parens to it
267278 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{..})
273284 , hasSibling <- not $ null lies' =
274285 do
275286 srcChild <- uniqueSrcSpanT
276- childRdr <- liftParseAST df child
287+ let childRdr = L srcChild $ mkRdrUnqual $ mkVarOcc child
277288
278289 let alreadyImported =
279290 showNameWithoutUniques (occName (unLoc childRdr))
@@ -284,7 +295,7 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
284295 when hasSibling $
285296 addTrailingCommaT (last lies')
286297 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)]
288299 return $ L l it{ideclHiding = Just (hide, L l' $ reverse pre ++ [L l'' (IEThingWith noExtField twIE NoIEWildcard (lies' ++ [childLIE]) [] )] ++ xs)}
289300 go hide l' pre (x : xs) = go hide l' (x : pre) xs
290301 go hide l' pre []
@@ -294,14 +305,18 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
294305 srcParent <- uniqueSrcSpanT
295306 srcChild <- uniqueSrcSpanT
296307 parentRdr <- liftParseAST df parent
297- childRdr <- liftParseAST df child
308+ let childRdr = L srcChild $ mkRdrUnqual $ mkVarOcc child
309+ isParentOperator = hasParen parent
298310 when hasSibling $
299311 addTrailingCommaT (head pre)
300- let parentLIE = L srcParent $ IEName parentRdr
312+ let parentLIE = L srcParent $ ( if isParentOperator then IEType else IEName ) parentRdr
301313 childLIE = L srcChild $ IEName childRdr
302314 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)]
305320 addSimpleAnnT x (DP (0 , 0 )) [(G AnnOpenP , DP (0 , 1 )), (G AnnCloseP , DP (0 , 0 ))]
306321 -- Parens are attachted to `pre`, so if `pre` was empty previously,
307322 -- we need change the ann key from `[]` to `:` to keep parens and other anns.
@@ -317,10 +332,10 @@ hasParen :: String -> Bool
317332hasParen (' (' : _) = True
318333hasParen _ = False
319334
320- unqalDP :: Bool -> [(KeywordId , DeltaPos )]
321- unqalDP paren =
335+ unqalDP :: Int -> Bool -> [(KeywordId , DeltaPos )]
336+ unqalDP c paren =
322337 ( if paren
323- then \ x -> (G AnnOpenP , dp00 ) : x : [(G AnnCloseP , dp00)]
338+ then \ x -> (G AnnOpenP , DP ( 0 , c) ) : x : [(G AnnCloseP , dp00)]
324339 else pure
325340 )
326341 (G AnnVal , dp00)
@@ -364,7 +379,7 @@ extendHiding symbol (L l idecls) mlies df = do
364379 , (G AnnCloseP , DP (0 , 0 ))
365380 ]
366381 addSimpleAnnT x (DP (0 , 0 )) []
367- addSimpleAnnT rdr dp00 $ unqalDP $ isOperator $ unLoc rdr
382+ addSimpleAnnT rdr dp00 $ unqalDP 0 $ isOperator $ unLoc rdr
368383 if hasSibling
369384 then when hasSibling $ do
370385 addTrailingCommaT x
0 commit comments