4
4
{-# LANGUAGE RankNTypes #-}
5
5
{-# LANGUAGE CPP #-}
6
6
{-# LANGUAGE FlexibleInstances #-}
7
+ {-# LANGUAGE ScopedTypeVariables #-}
7
8
8
9
module Development.IDE.Plugin.CodeAction.ExactPrint (
9
10
Rewrite (.. ),
@@ -23,41 +24,47 @@ module Development.IDE.Plugin.CodeAction.ExactPrint (
23
24
wildCardSymbol
24
25
) where
25
26
26
- import Control.Applicative
27
27
import Control.Monad
28
- import Control.Monad.Extra (whenJust )
29
28
import Control.Monad.Trans
30
- import Data.Char (isAlphaNum )
31
- import Data.Data (Data )
32
- import Data.Functor
33
- import Data.Generics (listify )
34
- import qualified Data.Map.Strict as Map
35
- import Data.Maybe (fromJust , isNothing ,
36
- mapMaybe )
37
- import qualified Data.Text as T
38
- import Development.IDE.GHC.Compat hiding (Annotation )
29
+ import Data.Char (isAlphaNum )
30
+ import Data.Data (Data )
31
+ import Data.Generics (listify )
32
+ import qualified Data.Text as T
33
+ import Development.IDE.GHC.Compat hiding (Annotation )
39
34
import Development.IDE.GHC.Error
40
35
import Development.IDE.GHC.ExactPrint
36
+ import Development.IDE.GHC.Util
41
37
import Development.IDE.Spans.Common
42
- import GHC.Exts (IsList (fromList ))
38
+ import GHC.Exts (IsList (fromList ))
39
+ import GHC.Stack (HasCallStack )
43
40
import Language.Haskell.GHC.ExactPrint
44
- #if !MIN_VERSION_ghc(9,2,0)
41
+ import Language.LSP.Types
42
+
43
+ -- GHC version specific imports. For any supported GHC version, make sure there is no warning in imports.
44
+ #if MIN_VERSION_ghc(9,2,0)
45
+ import Control.Lens (_head , _last , over )
46
+ import Data.Bifunctor (first )
47
+ import Data.Default (Default (.. ))
48
+ import Data.Maybe (fromJust , fromMaybe , mapMaybe )
49
+ import GHC (AddEpAnn (.. ), AnnContext (.. ), AnnList (.. ),
50
+ AnnParen (.. ), DeltaPos (SameLine ), EpAnn (.. ),
51
+ EpaLocation (EpaDelta ),
52
+ IsUnicodeSyntax (NormalSyntax ),
53
+ NameAdornment (NameParens ),
54
+ TrailingAnn (AddCommaAnn ), addAnns , ann ,
55
+ emptyComments , reAnnL )
56
+ #else
57
+ import Control.Applicative (Alternative ((<|>) ))
58
+ import Control.Monad.Extra (whenJust )
59
+ import Data.Foldable (find )
60
+ import Data.Functor (($>) )
61
+ import qualified Data.Map.Strict as Map
62
+ import Data.Maybe (fromJust , isJust ,
63
+ isNothing , mapMaybe )
45
64
import qualified Development.IDE.GHC.Compat.Util as Util
46
65
import Language.Haskell.GHC.ExactPrint.Types (DeltaPos (DP ),
47
66
KeywordId (G ), mkAnnKey )
48
- #else
49
- import Data.Default
50
- import GHC (AddEpAnn (.. ), AnnContext (.. ), AnnParen (.. ),
51
- DeltaPos (SameLine ), EpAnn (.. ), EpaLocation (EpaDelta ),
52
- IsUnicodeSyntax (NormalSyntax ),
53
- NameAdornment (NameParens ), NameAnn (.. ), addAnns , ann , emptyComments ,
54
- reAnnL , AnnList (.. ), TrailingAnn (AddCommaAnn ), addTrailingAnnToA )
55
67
#endif
56
- import Language.LSP.Types
57
- import Development.IDE.GHC.Util
58
- import Data.Bifunctor (first )
59
- import Control.Lens (_head , _last , over )
60
- import GHC.Stack (HasCallStack )
61
68
62
69
------------------------------------------------------------------------------
63
70
@@ -367,17 +374,28 @@ extendImportTopLevel thing (L l it@ImportDecl{..})
367
374
then lift (Left $ thing <> " already imported" )
368
375
else do
369
376
#if !MIN_VERSION_ghc(9,2,0)
370
- when hasSibling $
371
- addTrailingCommaT (last lies)
377
+ anns <- getAnnsT
378
+ maybe ( pure () ) addTrailingCommaT (lastMaybe lies)
372
379
addSimpleAnnT x (DP (0 , if hasSibling then 1 else 0 )) []
373
380
addSimpleAnnT rdr dp00 [(G AnnVal , dp00)]
381
+
382
+ -- When the last item already has a trailing comma, we append a trailing comma to the new item.
383
+ let isAnnComma (G AnnComma , _) = True
384
+ isAnnComma _ = False
385
+ shouldAddTrailingComma = maybe False nodeHasComma (lastMaybe lies)
386
+ && not (nodeHasComma (L l' lies))
387
+
388
+ nodeHasComma :: Data a => Located a -> Bool
389
+ nodeHasComma x = isJust $ Map. lookup (mkAnnKey x) anns >>= find isAnnComma . annsDP
390
+ when shouldAddTrailingComma (addTrailingCommaT x)
391
+
374
392
-- Parens are attachted to `lies`, so if `lies` was empty previously,
375
393
-- we need change the ann key from `[]` to `:` to keep parens and other anns.
376
394
unless hasSibling $
377
395
transferAnn (L l' lies) (L l' [x]) id
378
396
return $ L l it{ideclHiding = Just (hide, L l' $ lies ++ [x])}
379
397
#else
380
- lies' <- addCommaInImportList lies x
398
+ let lies' = addCommaInImportList lies x
381
399
return $ L l it{ideclHiding = Just (hide, L l' lies')}
382
400
#endif
383
401
extendImportTopLevel _ _ = lift $ Left " Unable to extend the import list"
@@ -514,30 +532,44 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
514
532
listAnn = epAnn srcParent [AddEpAnn AnnOpenP (epl 1 ), AddEpAnn AnnCloseP (epl 0 )]
515
533
x :: LIE GhcPs = reLocA $ L l'' $ IEThingWith listAnn parentLIE NoIEWildcard [childLIE]
516
534
517
- lies' <- addCommaInImportList (reverse pre) x
535
+ lies' = addCommaInImportList (reverse pre) x
518
536
#endif
519
537
return $ L l it{ideclHiding = Just (hide, L l' lies')}
520
538
extendImportViaParent _ _ _ _ = lift $ Left " Unable to extend the import list via parent"
521
539
522
540
#if MIN_VERSION_ghc(9,2,0)
523
541
-- Add an item in an import list, taking care of adding comma if needed.
524
- addCommaInImportList :: Monad m =>
542
+ addCommaInImportList ::
525
543
-- | Initial list
526
544
[LocatedAn AnnListItem a ]
527
545
-- | Additionnal item
528
546
-> LocatedAn AnnListItem a
529
- -> m [LocatedAn AnnListItem a ]
530
- addCommaInImportList lies x = do
531
- let hasSibling = not (null lies)
532
- -- Add the space before the comma
533
- x <- pure $ setEntryDP x (SameLine $ if hasSibling then 1 else 0 )
534
-
535
- -- Add the comma (if needed)
536
- let
537
- fixLast = if hasSibling then first addComma else id
538
- lies' = over _last fixLast lies ++ [x]
539
-
540
- pure lies'
547
+ -> [LocatedAn AnnListItem a ]
548
+ addCommaInImportList lies x =
549
+ fixLast lies ++ [newItem]
550
+ where
551
+ isTrailingAnnComma :: TrailingAnn -> Bool
552
+ isTrailingAnnComma (AddCommaAnn _) = True
553
+ isTrailingAnnComma _ = False
554
+
555
+ -- check if there is an existing trailing comma
556
+ existingTrailingComma = fromMaybe False $ do
557
+ L lastItemSrcAnn _ <- lastMaybe lies
558
+ lastItemAnn <- case ann lastItemSrcAnn of
559
+ EpAnn _ lastItemAnn _ -> pure lastItemAnn
560
+ _ -> Nothing
561
+ pure $ any isTrailingAnnComma (lann_trailing lastItemAnn)
562
+
563
+ hasSibling = not . null $ lies
564
+
565
+ -- Setup the new item. It should have a preceding whitespace if it has siblings, and a trailing comma if the
566
+ -- preceding item already has one.
567
+ newItem = first (if existingTrailingComma then addComma else id ) $
568
+ setEntryDP x (SameLine $ if hasSibling then 1 else 0 )
569
+
570
+ -- Add the comma (if needed)
571
+ fixLast :: [LocatedAn AnnListItem a ] -> [LocatedAn AnnListItem a ]
572
+ fixLast = over _last (first (if existingTrailingComma then id else addComma))
541
573
#endif
542
574
543
575
unIEWrappedName :: IEWrappedName (IdP GhcPs ) -> String
0 commit comments