{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
module Development.IDE.Plugin.CodeAction.ExactPrint (
Rewrite (..),
rewriteToEdit,
rewriteToWEdit,
appendConstraint,
removeConstraint,
extendImport,
hideSymbol,
liftParseAST,
wildCardSymbol
) where
import Control.Monad
import Control.Monad.Trans
import Data.Char (isAlphaNum)
import Data.Data (Data)
import Data.Generics (listify)
import qualified Data.Text as T
import Development.IDE.GHC.Compat hiding (Annotation)
import Development.IDE.GHC.Error
import Development.IDE.GHC.ExactPrint
import Development.IDE.GHC.Util
import Development.IDE.Spans.Common
import GHC.Exts (IsList (fromList))
import GHC.Stack (HasCallStack)
import Language.Haskell.GHC.ExactPrint
import Language.LSP.Protocol.Types
import Development.IDE.Plugin.CodeAction.Util
import Control.Lens (_head, _last, over)
import Data.Bifunctor (first)
import Data.Default (Default (..))
import Data.Maybe (fromJust, fromMaybe,
mapMaybe)
import GHC (AddEpAnn (..),
AnnContext (..),
AnnList (..),
AnnParen (..),
DeltaPos (SameLine),
EpAnn (..),
EpaLocation (EpaDelta),
IsUnicodeSyntax (NormalSyntax),
NameAdornment (NameParens),
TrailingAnn (AddCommaAnn),
addAnns, ann,
emptyComments, reAnnL)
data Rewrite where
Rewrite ::
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast), Outputable (GenLocated (Anno ast) ast), Data (GenLocated (Anno ast) ast)) =>
SrcSpan ->
(DynFlags -> TransformT (Either String) (GenLocated (Anno ast) ast)) ->
Rewrite
class ResetEntryDP ann where
resetEntryDP :: GenLocated ann ast -> GenLocated ann ast
instance {-# OVERLAPPING #-} Default an => ResetEntryDP (SrcAnn an) where
resetEntryDP :: forall ast.
GenLocated (SrcAnn an) ast -> GenLocated (SrcAnn an) ast
resetEntryDP (L SrcAnn an
srcAnn ast
x) = GenLocated (SrcAnn an) ast
-> DeltaPos -> GenLocated (SrcAnn an) ast
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
setEntryDP (SrcAnn an -> ast -> GenLocated (SrcAnn an) ast
forall l e. l -> e -> GenLocated l e
L SrcAnn an
srcAnn{ann=EpAnnNotUsed} ast
x) (Int -> DeltaPos
SameLine Int
0)
instance {-# OVERLAPPABLE #-} ResetEntryDP fallback where
resetEntryDP :: forall ast. GenLocated fallback ast -> GenLocated fallback ast
resetEntryDP = GenLocated fallback ast -> GenLocated fallback ast
forall a. a -> a
id
rewriteToEdit :: HasCallStack =>
DynFlags ->
Rewrite ->
Either String [TextEdit]
rewriteToEdit :: HasCallStack => DynFlags -> Rewrite -> Either String [TextEdit]
rewriteToEdit DynFlags
dflags
(Rewrite SrcSpan
dst DynFlags -> TransformT (Either String) (GenLocated (Anno ast) ast)
f) = do
(GenLocated (Anno ast) ast
ast, Int
_ , [String]
_) <- TransformT (Either String) (GenLocated (Anno ast) ast)
-> Either String (GenLocated (Anno ast) ast, Int, [String])
forall (m :: * -> *) a. TransformT m a -> m (a, Int, [String])
runTransformT
(TransformT (Either String) (GenLocated (Anno ast) ast)
-> Either String (GenLocated (Anno ast) ast, Int, [String]))
-> TransformT (Either String) (GenLocated (Anno ast) ast)
-> Either String (GenLocated (Anno ast) ast, Int, [String])
forall a b. (a -> b) -> a -> b
$ do
GenLocated (Anno ast) ast
ast <- DynFlags -> TransformT (Either String) (GenLocated (Anno ast) ast)
f DynFlags
dflags
GenLocated (Anno ast) ast
-> TransformT (Either String) (GenLocated (Anno ast) ast)
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenLocated (Anno ast) ast
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> GenLocated (Anno ast) ast
-> TransformT (Either String) (GenLocated (Anno ast) ast)
forall a b. (a -> b) -> a -> b
$ String -> GenLocated (Anno ast) ast -> GenLocated (Anno ast) ast
forall a. (Data a, ExactPrint a, HasCallStack) => String -> a -> a
traceAst String
"REWRITE_result" (GenLocated (Anno ast) ast -> GenLocated (Anno ast) ast)
-> GenLocated (Anno ast) ast -> GenLocated (Anno ast) ast
forall a b. (a -> b) -> a -> b
$ GenLocated (Anno ast) ast -> GenLocated (Anno ast) ast
forall ast. GenLocated (Anno ast) ast -> GenLocated (Anno ast) ast
forall ann ast.
ResetEntryDP ann =>
GenLocated ann ast -> GenLocated ann ast
resetEntryDP GenLocated (Anno ast) ast
ast
let editMap :: [TextEdit]
editMap =
[ Range -> Text -> TextEdit
TextEdit (Maybe Range -> Range
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Range -> Range) -> Maybe Range -> Range
forall a b. (a -> b) -> a -> b
$ SrcSpan -> Maybe Range
srcSpanToRange SrcSpan
dst) (Text -> TextEdit) -> Text -> TextEdit
forall a b. (a -> b) -> a -> b
$
String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ GenLocated (Anno ast) ast -> String
forall ast. ExactPrint ast => ast -> String
exactPrint GenLocated (Anno ast) ast
ast
]
[TextEdit] -> Either String [TextEdit]
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [TextEdit]
editMap
rewriteToWEdit :: DynFlags
-> Uri
-> Rewrite
-> Either String WorkspaceEdit
rewriteToWEdit :: DynFlags -> Uri -> Rewrite -> Either String WorkspaceEdit
rewriteToWEdit DynFlags
dflags Uri
uri
Rewrite
r = do
[TextEdit]
edits <- HasCallStack => DynFlags -> Rewrite -> Either String [TextEdit]
DynFlags -> Rewrite -> Either String [TextEdit]
rewriteToEdit DynFlags
dflags
Rewrite
r
WorkspaceEdit -> Either String WorkspaceEdit
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (WorkspaceEdit -> Either String WorkspaceEdit)
-> WorkspaceEdit -> Either String WorkspaceEdit
forall a b. (a -> b) -> a -> b
$
WorkspaceEdit
{ $sel:_changes:WorkspaceEdit :: Maybe (Map Uri [TextEdit])
_changes = Map Uri [TextEdit] -> Maybe (Map Uri [TextEdit])
forall a. a -> Maybe a
Just ([Item (Map Uri [TextEdit])] -> Map Uri [TextEdit]
forall l. IsList l => [Item l] -> l
fromList [(Uri
uri, [TextEdit]
edits)])
, $sel:_documentChanges:WorkspaceEdit :: Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
_documentChanges = Maybe
[TextDocumentEdit |? (CreateFile |? (RenameFile |? DeleteFile))]
forall a. Maybe a
Nothing
, $sel:_changeAnnotations:WorkspaceEdit :: Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
_changeAnnotations = Maybe (Map ChangeAnnotationIdentifier ChangeAnnotation)
forall a. Maybe a
Nothing
}
dropHsParTy :: LHsType (GhcPass pass) -> LHsType (GhcPass pass)
dropHsParTy :: forall (pass :: Pass).
LHsType (GhcPass pass) -> LHsType (GhcPass pass)
dropHsParTy (L SrcSpanAnnA
_ (HsParTy XParTy (GhcPass pass)
_ LHsType (GhcPass pass)
ty)) = LHsType (GhcPass pass)
ty
dropHsParTy LHsType (GhcPass pass)
other = LHsType (GhcPass pass)
other
removeConstraint ::
(LHsType GhcPs -> Bool) ->
LHsType GhcPs ->
Rewrite
removeConstraint :: (LHsType GhcPs -> Bool) -> LHsType GhcPs -> Rewrite
removeConstraint LHsType GhcPs -> Bool
toRemove = LHsType GhcPs -> Rewrite
GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite
go (GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite)
-> (GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> Rewrite
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a. (Data a, ExactPrint a, HasCallStack) => String -> a -> a
traceAst String
"REMOVE_CONSTRAINT_input"
where
go :: LHsType GhcPs -> Rewrite
#if !MIN_VERSION_ghc(9,4,0)
go (L l it@HsQualTy{hst_ctxt = Just (L l' ctxt), hst_body}) = Rewrite (locA l) $ \_ -> do
#else
go :: LHsType GhcPs -> Rewrite
go (L SrcSpanAnnA
l it :: HsType GhcPs
it@HsQualTy{hst_ctxt :: forall pass. HsType pass -> LHsContext pass
hst_ctxt = L SrcSpanAnnC
l' [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt, LHsType GhcPs
hst_body :: LHsType GhcPs
hst_body :: forall pass. HsType pass -> LHsType pass
hst_body}) = SrcSpan
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) ((DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ \DynFlags
_ -> do
#endif
let ctxt' :: [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt' = (GenLocated SrcSpanAnnA (HsType GhcPs) -> Bool)
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (GenLocated SrcSpanAnnA (HsType GhcPs) -> Bool)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LHsType GhcPs -> Bool
GenLocated SrcSpanAnnA (HsType GhcPs) -> Bool
toRemove) [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt
removeStuff :: Bool
removeStuff = (LHsType GhcPs -> Bool
GenLocated SrcSpanAnnA (HsType GhcPs) -> Bool
toRemove (GenLocated SrcSpanAnnA (HsType GhcPs) -> Bool)
-> Maybe (GenLocated SrcSpanAnnA (HsType GhcPs)) -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> Maybe (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a. [a] -> Maybe a
headMaybe [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt) Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
let hst_body' :: GenLocated SrcSpanAnnA (HsType GhcPs)
hst_body' = if Bool
removeStuff then GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall ast.
GenLocated SrcSpanAnnA ast -> GenLocated SrcSpanAnnA ast
forall ann ast.
ResetEntryDP ann =>
GenLocated ann ast -> GenLocated ann ast
resetEntryDP LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
hst_body else LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
hst_body
GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ case [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt' of
[] -> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
GenLocated SrcSpanAnnA (HsType GhcPs)
hst_body'
[GenLocated SrcSpanAnnA (HsType GhcPs)]
_ -> do
let ctxt'' :: [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt'' = ASetter
[GenLocated SrcSpanAnnA (HsType GhcPs)]
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
(GenLocated SrcSpanAnnA (HsType GhcPs))
-> (GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs))
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[GenLocated SrcSpanAnnA (HsType GhcPs)]
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
(GenLocated SrcSpanAnnA (HsType GhcPs))
forall s a. Snoc s s a a => Traversal' s a
Traversal'
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
_last ((SrcSpanAnnA -> SrcSpanAnnA)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SrcSpanAnnA -> SrcSpanAnnA
removeComma) [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt'
#if MIN_VERSION_ghc(9,4,0)
Anno (HsType GhcPs)
-> HsType GhcPs -> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
forall l e. l -> e -> GenLocated l e
L Anno (HsType GhcPs)
SrcSpanAnnA
l (HsType GhcPs -> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs))
-> HsType GhcPs -> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
forall a b. (a -> b) -> a -> b
$ HsType GhcPs
it{ hst_ctxt = L l' ctxt''
#else
L l $ it{ hst_ctxt = Just $ L l' ctxt''
#endif
, hst_body = hst_body'
}
go (L SrcSpanAnnA
_ (HsParTy XParTy GhcPs
_ LHsType GhcPs
ty)) = LHsType GhcPs -> Rewrite
go LHsType GhcPs
ty
go (L SrcSpanAnnA
_ HsForAllTy{LHsType GhcPs
hst_body :: forall pass. HsType pass -> LHsType pass
hst_body :: LHsType GhcPs
hst_body}) = LHsType GhcPs -> Rewrite
go LHsType GhcPs
hst_body
go (L SrcSpanAnnA
l HsType GhcPs
other) = SrcSpan
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) ((DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ \DynFlags
_ -> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> HsType GhcPs -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l HsType GhcPs
other
appendConstraint ::
String ->
LHsType GhcPs ->
Rewrite
appendConstraint :: String -> LHsType GhcPs -> Rewrite
appendConstraint String
constraintT = GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite
go (GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite)
-> (GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> Rewrite
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a. (Data a, ExactPrint a, HasCallStack) => String -> a -> a
traceAst String
"appendConstraint"
where
#if MIN_VERSION_ghc(9,4,0)
go :: GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite
go (L SrcSpanAnnA
l it :: HsType GhcPs
it@HsQualTy{hst_ctxt :: forall pass. HsType pass -> LHsContext pass
hst_ctxt = L SrcSpanAnnC
l' [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt}) = SrcSpan
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) ((DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ \DynFlags
df -> do
#else
go (L l it@HsQualTy{hst_ctxt = Just (L l' ctxt)}) = Rewrite (locA l) $ \df -> do
#endif
GenLocated SrcSpanAnnA (HsType GhcPs)
constraint <- DynFlags
-> String
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall ast l.
(ASTElement l ast, ExactPrint (LocatedAn l ast)) =>
DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST DynFlags
df String
constraintT
GenLocated SrcSpanAnnA (HsType GhcPs)
constraint <- GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs)))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpanAnnA (HsType GhcPs)
-> DeltaPos -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
setEntryDP GenLocated SrcSpanAnnA (HsType GhcPs)
constraint (Int -> DeltaPos
SameLine Int
1)
let l'' :: SrcSpanAnnC
l'' = ((EpAnn AnnContext -> EpAnn AnnContext)
-> SrcSpanAnnC -> SrcSpanAnnC
forall a b. (a -> b) -> SrcSpanAnn' a -> SrcSpanAnn' b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap((EpAnn AnnContext -> EpAnn AnnContext)
-> SrcSpanAnnC -> SrcSpanAnnC)
-> ((AnnContext -> AnnContext)
-> EpAnn AnnContext -> EpAnn AnnContext)
-> (AnnContext -> AnnContext)
-> SrcSpanAnnC
-> SrcSpanAnnC
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(AnnContext -> AnnContext) -> EpAnn AnnContext -> EpAnn AnnContext
forall a b. (a -> b) -> EpAnn a -> EpAnn b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) (Maybe EpaLocation -> AnnContext -> AnnContext
addParensToCtxt Maybe EpaLocation
close_dp) SrcSpanAnnC
l'
close_dp :: Maybe EpaLocation
close_dp = case [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt of
[L SrcSpanAnnA
_ (HsParTy EpAnn{anns :: forall ann. EpAnn ann -> ann
anns=AnnParen{EpaLocation
ap_close :: EpaLocation
ap_close :: AnnParen -> EpaLocation
ap_close}} LHsType GhcPs
_)] -> EpaLocation -> Maybe EpaLocation
forall a. a -> Maybe a
Just EpaLocation
ap_close
[GenLocated SrcSpanAnnA (HsType GhcPs)]
_ -> Maybe EpaLocation
forall a. Maybe a
Nothing
ctxt' :: [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt' = ASetter
[GenLocated SrcSpanAnnA (HsType GhcPs)]
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
(GenLocated SrcSpanAnnA (HsType GhcPs))
-> (GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs))
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[GenLocated SrcSpanAnnA (HsType GhcPs)]
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
(GenLocated SrcSpanAnnA (HsType GhcPs))
forall s a. Snoc s s a a => Traversal' s a
Traversal'
[GenLocated SrcSpanAnnA (HsType GhcPs)]
(GenLocated SrcSpanAnnA (HsType GhcPs))
_last ((SrcSpanAnnA -> SrcSpanAnnA)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SrcSpanAnnA -> SrcSpanAnnA
addComma) ([GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)])
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs))
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall a b. (a -> b) -> [a] -> [b]
map LHsType GhcPs -> LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall (pass :: Pass).
LHsType (GhcPass pass) -> LHsType (GhcPass pass)
dropHsParTy [GenLocated SrcSpanAnnA (HsType GhcPs)]
ctxt
#if MIN_VERSION_ghc(9,4,0)
GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs)))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> HsType GhcPs -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l (HsType GhcPs -> GenLocated SrcSpanAnnA (HsType GhcPs))
-> HsType GhcPs -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a b. (a -> b) -> a -> b
$ HsType GhcPs
it{hst_ctxt = L l'' $ ctxt' ++ [constraint]}
#else
return $ L l $ it{hst_ctxt = Just $ L l'' $ ctxt' ++ [constraint]}
#endif
go (L SrcSpanAnnA
_ HsForAllTy{LHsType GhcPs
hst_body :: forall pass. HsType pass -> LHsType pass
hst_body :: LHsType GhcPs
hst_body}) = GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite
go LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
hst_body
go (L SrcSpanAnnA
_ (HsParTy XParTy GhcPs
_ LHsType GhcPs
ty)) = GenLocated SrcSpanAnnA (HsType GhcPs) -> Rewrite
go LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
ty
go ast :: GenLocated SrcSpanAnnA (HsType GhcPs)
ast@(L SrcSpanAnnA
l HsType GhcPs
_) = SrcSpan
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) ((DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String) (GenLocated (Anno (HsType GhcPs)) (HsType GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ \DynFlags
df -> do
GenLocated SrcSpanAnnA (HsType GhcPs)
constraint <- DynFlags
-> String
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall ast l.
(ASTElement l ast, ExactPrint (LocatedAn l ast)) =>
DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST DynFlags
df String
constraintT
SrcSpan
lContext <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
SrcSpan
lTop <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
#if MIN_VERSION_ghc(9,4,0)
let context :: GenLocated SrcSpanAnnC [GenLocated SrcSpanAnnA (HsType GhcPs)]
context = AnnContext
-> EpAnnComments
-> Located [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> GenLocated SrcSpanAnnC [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall ann e.
ann -> EpAnnComments -> Located e -> GenLocated (SrcAnn ann) e
reAnnL AnnContext
annCtxt EpAnnComments
emptyComments (Located [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> GenLocated SrcSpanAnnC [GenLocated SrcSpanAnnA (HsType GhcPs)])
-> Located [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> GenLocated SrcSpanAnnC [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall a b. (a -> b) -> a -> b
$ SrcSpan
-> [GenLocated SrcSpanAnnA (HsType GhcPs)]
-> Located [GenLocated SrcSpanAnnA (HsType GhcPs)]
forall l e. l -> e -> GenLocated l e
L SrcSpan
lContext [GenLocated SrcSpanAnnA (HsType GhcPs)
-> GenLocated SrcSpanAnnA (HsType GhcPs)
forall ast.
GenLocated SrcSpanAnnA ast -> GenLocated SrcSpanAnnA ast
forall ann ast.
ResetEntryDP ann =>
GenLocated ann ast -> GenLocated ann ast
resetEntryDP GenLocated SrcSpanAnnA (HsType GhcPs)
constraint]
#else
let context = Just $ reAnnL annCtxt emptyComments $ L lContext [resetEntryDP constraint]
#endif
annCtxt :: AnnContext
annCtxt = Maybe (IsUnicodeSyntax, EpaLocation)
-> [EpaLocation] -> [EpaLocation] -> AnnContext
AnnContext ((IsUnicodeSyntax, EpaLocation)
-> Maybe (IsUnicodeSyntax, EpaLocation)
forall a. a -> Maybe a
Just (IsUnicodeSyntax
NormalSyntax, Int -> EpaLocation
epl Int
1)) [Int -> EpaLocation
epl Int
0 | Bool
needsParens] [Int -> EpaLocation
epl Int
0 | Bool
needsParens]
needsParens :: Bool
needsParens = PprPrec -> HsType GhcPs -> Bool
forall (p :: Pass). PprPrec -> HsType (GhcPass p) -> Bool
hsTypeNeedsParens PprPrec
sigPrec (HsType GhcPs -> Bool) -> HsType GhcPs -> Bool
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpanAnnA (HsType GhcPs) -> HsType GhcPs
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpanAnnA (HsType GhcPs)
constraint
GenLocated SrcSpanAnnA (HsType GhcPs)
ast <- GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs)))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ GenLocated SrcSpanAnnA (HsType GhcPs)
-> DeltaPos -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
setEntryDP GenLocated SrcSpanAnnA (HsType GhcPs)
ast (Int -> DeltaPos
SameLine Int
1)
GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs)))
-> GenLocated SrcSpanAnnA (HsType GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (HsType GhcPs))
forall a b. (a -> b) -> a -> b
$ Located (HsType GhcPs) -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (HsType GhcPs) -> GenLocated SrcSpanAnnA (HsType GhcPs))
-> Located (HsType GhcPs) -> GenLocated SrcSpanAnnA (HsType GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsType GhcPs -> Located (HsType GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
lTop (HsType GhcPs -> Located (HsType GhcPs))
-> HsType GhcPs -> Located (HsType GhcPs)
forall a b. (a -> b) -> a -> b
$ XQualTy GhcPs -> LHsContext GhcPs -> LHsType GhcPs -> HsType GhcPs
forall pass.
XQualTy pass -> LHsContext pass -> LHsType pass -> HsType pass
HsQualTy XQualTy GhcPs
NoExtField
noExtField LHsContext GhcPs
GenLocated SrcSpanAnnC [GenLocated SrcSpanAnnA (HsType GhcPs)]
context LHsType GhcPs
GenLocated SrcSpanAnnA (HsType GhcPs)
ast
liftParseAST
:: forall ast l. (ASTElement l ast, ExactPrint (LocatedAn l ast))
=> DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST :: forall ast l.
(ASTElement l ast, ExactPrint (LocatedAn l ast)) =>
DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST DynFlags
df String
s = case Parser (LocatedAn l ast)
forall l ast. ASTElement l ast => Parser (LocatedAn l ast)
parseAST DynFlags
df String
"" String
s of
Right LocatedAn l ast
x -> LocatedAn l ast -> TransformT (Either String) (LocatedAn l ast)
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (LocatedAn l ast -> LocatedAn l ast
forall ast. ExactPrint ast => ast -> ast
makeDeltaAst LocatedAn l ast
x)
Left ErrorMessages
_ -> RWST () [String] Int (Either String) (LocatedAn l ast)
-> TransformT (Either String) (LocatedAn l ast)
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST () [String] Int (Either String) (LocatedAn l ast)
-> TransformT (Either String) (LocatedAn l ast))
-> RWST () [String] Int (Either String) (LocatedAn l ast)
-> TransformT (Either String) (LocatedAn l ast)
forall a b. (a -> b) -> a -> b
$ Either String (LocatedAn l ast)
-> RWST () [String] Int (Either String) (LocatedAn l ast)
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Either String (LocatedAn l ast)
-> RWST () [String] Int (Either String) (LocatedAn l ast))
-> Either String (LocatedAn l ast)
-> RWST () [String] Int (Either String) (LocatedAn l ast)
forall a b. (a -> b) -> a -> b
$ String -> Either String (LocatedAn l ast)
forall a b. a -> Either a b
Left (String -> Either String (LocatedAn l ast))
-> String -> Either String (LocatedAn l ast)
forall a b. (a -> b) -> a -> b
$ String
"No parse: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
s
headMaybe :: [a] -> Maybe a
headMaybe :: forall a. [a] -> Maybe a
headMaybe [] = Maybe a
forall a. Maybe a
Nothing
headMaybe (a
a : [a]
_) = a -> Maybe a
forall a. a -> Maybe a
Just a
a
lastMaybe :: [a] -> Maybe a
lastMaybe :: forall a. [a] -> Maybe a
lastMaybe [] = Maybe a
forall a. Maybe a
Nothing
lastMaybe [a]
other = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ [a] -> a
forall a. HasCallStack => [a] -> a
last [a]
other
extendImport :: Maybe String -> String -> LImportDecl GhcPs -> Rewrite
extendImport :: Maybe String -> String -> LImportDecl GhcPs -> Rewrite
extendImport Maybe String
mparent String
identifier lDecl :: LImportDecl GhcPs
lDecl@(L SrcSpanAnnA
l ImportDecl GhcPs
_) =
SrcSpan
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) ((DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ \DynFlags
df -> do
case Maybe String
mparent of
Just String
parent -> DynFlags
-> String
-> String
-> LImportDecl GhcPs
-> TransformT (Either String) (LImportDecl GhcPs)
extendImportViaParent DynFlags
df String
parent String
identifier (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall ast. ExactPrint ast => ast -> ast
makeDeltaAst LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
lDecl)
Maybe String
_ -> String
-> LImportDecl GhcPs
-> TransformT (Either String) (LImportDecl GhcPs)
extendImportTopLevel String
identifier (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall ast. ExactPrint ast => ast -> ast
makeDeltaAst LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
lDecl)
extendImportTopLevel ::
String ->
LImportDecl GhcPs ->
TransformT (Either String) (LImportDecl GhcPs)
extendImportTopLevel :: String
-> LImportDecl GhcPs
-> TransformT (Either String) (LImportDecl GhcPs)
extendImportTopLevel String
thing (L SrcSpanAnnA
l it :: ImportDecl GhcPs
it@ImportDecl{Bool
Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
Maybe (XRec GhcPs ModuleName)
ImportDeclPkgQual GhcPs
XCImportDecl GhcPs
XRec GhcPs ModuleName
IsBootInterface
ImportDeclQualifiedStyle
ideclExt :: XCImportDecl GhcPs
ideclName :: XRec GhcPs ModuleName
ideclPkgQual :: ImportDeclPkgQual GhcPs
ideclSource :: IsBootInterface
ideclSafe :: Bool
ideclQualified :: ImportDeclQualifiedStyle
ideclAs :: Maybe (XRec GhcPs ModuleName)
ideclImportList :: Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
ideclExt :: forall pass. ImportDecl pass -> XCImportDecl pass
ideclName :: forall pass. ImportDecl pass -> XRec pass ModuleName
ideclPkgQual :: forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclSource :: forall pass. ImportDecl pass -> IsBootInterface
ideclSafe :: forall pass. ImportDecl pass -> Bool
ideclQualified :: forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclAs :: forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclImportList :: forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
..})
#if MIN_VERSION_ghc(9,5,0)
| Just (ImportListInterpretation
hide, L SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
lies) <- Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
ideclImportList
#else
| Just (hide, L l' lies) <- ideclHiding
#endif
= do
SrcSpan
src <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
SrcSpan
top <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
let rdr :: LocatedAn NameAnn RdrName
rdr = Located RdrName -> LocatedAn NameAnn RdrName
forall e ann. Located e -> LocatedAn ann e
reLocA (Located RdrName -> LocatedAn NameAnn RdrName)
-> Located RdrName -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ SrcSpan -> RdrName -> Located RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpan
src (RdrName -> Located RdrName) -> RdrName -> Located RdrName
forall a b. (a -> b) -> a -> b
$ OccName -> RdrName
mkRdrUnqual (OccName -> RdrName) -> OccName -> RdrName
forall a b. (a -> b) -> a -> b
$ String -> OccName
mkVarOcc String
thing
let alreadyImported :: Bool
alreadyImported =
OccName -> Text
forall a. Outputable a => a -> Text
printOutputable (RdrName -> OccName
forall name. HasOccName name => name -> OccName
occName (LocatedAn NameAnn RdrName -> RdrName
forall l e. GenLocated l e -> e
unLoc LocatedAn NameAnn RdrName
rdr))
Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (OccName -> Text) -> [OccName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => a -> Text
printOutputable @OccName) ((OccName -> Bool) -> GenericQ [OccName]
forall r. Typeable r => (r -> Bool) -> GenericQ [r]
listify (Bool -> OccName -> Bool
forall a b. a -> b -> a
const Bool
True) [GenLocated SrcSpanAnnA (IE GhcPs)]
lies)
Bool
-> TransformT (Either String) () -> TransformT (Either String) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
alreadyImported (TransformT (Either String) () -> TransformT (Either String) ())
-> TransformT (Either String) () -> TransformT (Either String) ()
forall a b. (a -> b) -> a -> b
$
RWST () [String] Int (Either String) ()
-> TransformT (Either String) ()
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST () [String] Int (Either String) ()
-> TransformT (Either String) ())
-> RWST () [String] Int (Either String) ()
-> TransformT (Either String) ()
forall a b. (a -> b) -> a -> b
$ Either String () -> RWST () [String] Int (Either String) ()
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ String
thing String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" already imported")
let lie :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
lie = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
src (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn RdrName
rdr
x :: GenLocated SrcSpanAnnA (IE GhcPs)
x = Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs))
-> Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IE GhcPs -> Located (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
top (IE GhcPs -> Located (IE GhcPs)) -> IE GhcPs -> Located (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEVar GhcPs -> LIEWrappedName GhcPs -> IE GhcPs
forall pass. XIEVar pass -> LIEWrappedName pass -> IE pass
IEVar
#if MIN_VERSION_ghc(9,8,0)
Nothing
#else
XIEVar GhcPs
NoExtField
noExtField
#endif
LIEWrappedName GhcPs
GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
lie
if GenLocated SrcSpanAnnA (IE GhcPs)
x GenLocated SrcSpanAnnA (IE GhcPs)
-> [GenLocated SrcSpanAnnA (IE GhcPs)] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [GenLocated SrcSpanAnnA (IE GhcPs)]
lies
then RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (String -> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. a -> Either a b
Left (String
-> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> String
-> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ String
thing String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" already imported")
else do
let lies' :: [GenLocated SrcSpanAnnA (IE GhcPs)]
lies' = [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnA (IE GhcPs)
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a.
[LocatedAn AnnListItem a]
-> LocatedAn AnnListItem a -> [LocatedAn AnnListItem a]
addCommaInImportList [GenLocated SrcSpanAnnA (IE GhcPs)]
lies GenLocated SrcSpanAnnA (IE GhcPs)
x
#if MIN_VERSION_ghc(9,5,0)
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
it{ideclImportList = Just (hide, L l' lies')}
#else
return $ L l it{ideclHiding = Just (hide, L l' lies')}
#endif
extendImportTopLevel String
_ LImportDecl GhcPs
_ = RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs)
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs))
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs))
-> Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ String -> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. a -> Either a b
Left String
"Unable to extend the import list"
wildCardSymbol :: String
wildCardSymbol :: String
wildCardSymbol = String
".."
extendImportViaParent ::
DynFlags ->
String ->
String ->
LImportDecl GhcPs ->
TransformT (Either String) (LImportDecl GhcPs)
extendImportViaParent :: DynFlags
-> String
-> String
-> LImportDecl GhcPs
-> TransformT (Either String) (LImportDecl GhcPs)
extendImportViaParent DynFlags
df String
parent String
child (L SrcSpanAnnA
l it :: ImportDecl GhcPs
it@ImportDecl{Bool
Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
Maybe (XRec GhcPs ModuleName)
ImportDeclPkgQual GhcPs
XCImportDecl GhcPs
XRec GhcPs ModuleName
IsBootInterface
ImportDeclQualifiedStyle
ideclExt :: forall pass. ImportDecl pass -> XCImportDecl pass
ideclName :: forall pass. ImportDecl pass -> XRec pass ModuleName
ideclPkgQual :: forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclSource :: forall pass. ImportDecl pass -> IsBootInterface
ideclSafe :: forall pass. ImportDecl pass -> Bool
ideclQualified :: forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclAs :: forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclImportList :: forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclExt :: XCImportDecl GhcPs
ideclName :: XRec GhcPs ModuleName
ideclPkgQual :: ImportDeclPkgQual GhcPs
ideclSource :: IsBootInterface
ideclSafe :: Bool
ideclQualified :: ImportDeclQualifiedStyle
ideclAs :: Maybe (XRec GhcPs ModuleName)
ideclImportList :: Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
..})
#if MIN_VERSION_ghc(9,5,0)
| Just (ImportListInterpretation
hide, L SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
lies) <- Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
ideclImportList = ImportListInterpretation
-> SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
go ImportListInterpretation
hide SrcSpanAnnL
l' [] [GenLocated SrcSpanAnnA (IE GhcPs)]
lies
#else
| Just (hide, L l' lies) <- ideclHiding = go hide l' [] lies
#endif
where
go :: ImportListInterpretation
-> SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
go ImportListInterpretation
_hide SrcSpanAnnL
_l' [GenLocated SrcSpanAnnA (IE GhcPs)]
_pre ((L SrcSpanAnnA
_ll' (IEThingAll XIEThingAll GhcPs
_ (L SrcSpanAnnA
_ IEWrappedName GhcPs
ie))) : [GenLocated SrcSpanAnnA (IE GhcPs)]
_xs)
| String
parent String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== IEWrappedName GhcPs -> String
unIEWrappedName IEWrappedName GhcPs
ie = RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> (String
-> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> String
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. a -> Either a b
Left (String
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> String
-> RWST
()
[String]
Int
(Either String)
(GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ String
child String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" already included in " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
parent String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" imports"
go ImportListInterpretation
hide SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
pre ((L SrcSpanAnnA
ll' (IEThingAbs XIEThingAbs GhcPs
_ absIE :: LIEWrappedName GhcPs
absIE@(L SrcSpanAnnA
_ IEWrappedName GhcPs
ie))) : [GenLocated SrcSpanAnnA (IE GhcPs)]
xs)
| String
parent String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== IEWrappedName GhcPs -> String
unIEWrappedName IEWrappedName GhcPs
ie = do
SrcSpan
srcChild <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
let childRdr :: LocatedAn NameAnn RdrName
childRdr = Located RdrName -> LocatedAn NameAnn RdrName
forall e ann. Located e -> LocatedAn ann e
reLocA (Located RdrName -> LocatedAn NameAnn RdrName)
-> Located RdrName -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ SrcSpan -> RdrName -> Located RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (RdrName -> Located RdrName) -> RdrName -> Located RdrName
forall a b. (a -> b) -> a -> b
$ OccName -> RdrName
mkRdrUnqual (OccName -> RdrName) -> OccName -> RdrName
forall a b. (a -> b) -> a -> b
$ String -> OccName
mkVarOcc String
child
childLIE :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn RdrName
childRdr
LIE GhcPs
x :: LIE GhcPs = SrcSpanAnnA -> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
ll' (IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs))
-> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEThingWith GhcPs
-> LIEWrappedName GhcPs
-> IEWildcard
-> [LIEWrappedName GhcPs]
-> IE GhcPs
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith
#if MIN_VERSION_ghc(9,7,0)
(Nothing, addAnns mempty [AddEpAnn AnnOpenP (EpaDelta (SameLine 1) []), AddEpAnn AnnCloseP def] emptyComments)
#else
(EpAnn [AddEpAnn] -> [AddEpAnn] -> EpAnnComments -> EpAnn [AddEpAnn]
addAnns EpAnn [AddEpAnn]
forall a. Monoid a => a
mempty [AnnKeywordId -> EpaLocation -> AddEpAnn
AddEpAnn AnnKeywordId
AnnOpenP (DeltaPos -> [LEpaComment] -> EpaLocation
EpaDelta (Int -> DeltaPos
SameLine Int
1) []), AnnKeywordId -> EpaLocation -> AddEpAnn
AddEpAnn AnnKeywordId
AnnCloseP EpaLocation
forall a. Default a => a
def] EpAnnComments
emptyComments)
#endif
LIEWrappedName GhcPs
absIE IEWildcard
NoIEWildcard [LIEWrappedName GhcPs
GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE]
#if MIN_VERSION_ghc(9,5,0)
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
it{ideclImportList = Just (hide, L l' $ reverse pre ++ [x] ++ xs)}
#else
return $ L l it{ideclHiding = Just (hide, L l' $ reverse pre ++ [x] ++ xs)}
#endif
go ImportListInterpretation
hide SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
pre ((L SrcSpanAnnA
l'' (IEThingWith XIEThingWith GhcPs
l''' twIE :: LIEWrappedName GhcPs
twIE@(L SrcSpanAnnA
_ IEWrappedName GhcPs
ie) IEWildcard
_ [LIEWrappedName GhcPs]
lies')) : [GenLocated SrcSpanAnnA (IE GhcPs)]
xs)
| String
parent String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== IEWrappedName GhcPs -> String
unIEWrappedName IEWrappedName GhcPs
ie
, String
child String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
wildCardSymbol = do
#if MIN_VERSION_ghc(9,5,0)
let it' :: ImportDecl GhcPs
it' = ImportDecl GhcPs
it{ideclImportList = Just (hide, lies)}
#else
let it' = it{ideclHiding = Just (hide, lies)}
#endif
thing :: IE GhcPs
thing = XIEThingWith GhcPs
-> LIEWrappedName GhcPs
-> IEWildcard
-> [LIEWrappedName GhcPs]
-> IE GhcPs
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith XIEThingWith GhcPs
EpAnn [AddEpAnn]
newl LIEWrappedName GhcPs
twIE (Int -> IEWildcard
IEWildcard Int
2) []
#if MIN_VERSION_ghc(9,7,0)
newl = fmap (\ann -> ann ++ [AddEpAnn AnnDotdot d0]) <$> l'''
#else
newl :: EpAnn [AddEpAnn]
newl = (\[AddEpAnn]
ann -> [AddEpAnn]
ann [AddEpAnn] -> [AddEpAnn] -> [AddEpAnn]
forall a. [a] -> [a] -> [a]
++ [AnnKeywordId -> EpaLocation -> AddEpAnn
AddEpAnn AnnKeywordId
AnnDotdot EpaLocation
d0]) ([AddEpAnn] -> [AddEpAnn]) -> EpAnn [AddEpAnn] -> EpAnn [AddEpAnn]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XIEThingWith GhcPs
EpAnn [AddEpAnn]
l'''
#endif
lies :: GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
lies = SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnL
l' ([GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a b. (a -> b) -> a -> b
$ [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a]
reverse [GenLocated SrcSpanAnnA (IE GhcPs)]
pre [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a] -> [a]
++ [SrcSpanAnnA -> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l'' IE GhcPs
thing] [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a] -> [a]
++ [GenLocated SrcSpanAnnA (IE GhcPs)]
xs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
it'
| String
parent String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== IEWrappedName GhcPs -> String
unIEWrappedName IEWrappedName GhcPs
ie = do
let hasSibling :: Bool
hasSibling = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LIEWrappedName GhcPs]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
lies'
SrcSpan
srcChild <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
let childRdr :: LocatedAn NameAnn RdrName
childRdr = Located RdrName -> LocatedAn NameAnn RdrName
forall e ann. Located e -> LocatedAn ann e
reLocA (Located RdrName -> LocatedAn NameAnn RdrName)
-> Located RdrName -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ SrcSpan -> RdrName -> Located RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (RdrName -> Located RdrName) -> RdrName -> Located RdrName
forall a b. (a -> b) -> a -> b
$ OccName -> RdrName
mkRdrUnqual (OccName -> RdrName) -> OccName -> RdrName
forall a b. (a -> b) -> a -> b
$ String -> OccName
mkVarOcc String
child
LocatedAn NameAnn RdrName
childRdr <- LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName)
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName))
-> LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName)
forall a b. (a -> b) -> a -> b
$ LocatedAn NameAnn RdrName -> DeltaPos -> LocatedAn NameAnn RdrName
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
setEntryDP LocatedAn NameAnn RdrName
childRdr (DeltaPos -> LocatedAn NameAnn RdrName)
-> DeltaPos -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ Int -> DeltaPos
SameLine (Int -> DeltaPos) -> Int -> DeltaPos
forall a b. (a -> b) -> a -> b
$ if Bool
hasSibling then Int
1 else Int
0
let alreadyImported :: Bool
alreadyImported =
OccName -> Text
forall a. Outputable a => a -> Text
printOutputable (RdrName -> OccName
forall name. HasOccName name => name -> OccName
occName (LocatedAn NameAnn RdrName -> RdrName
forall l e. GenLocated l e -> e
unLoc LocatedAn NameAnn RdrName
childRdr))
Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (OccName -> Text) -> [OccName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => a -> Text
printOutputable @OccName) ((OccName -> Bool) -> GenericQ [OccName]
forall r. Typeable r => (r -> Bool) -> GenericQ [r]
listify (Bool -> OccName -> Bool
forall a b. a -> b -> a
const Bool
True) [LIEWrappedName GhcPs]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
lies')
Bool
-> TransformT (Either String) () -> TransformT (Either String) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
alreadyImported (TransformT (Either String) () -> TransformT (Either String) ())
-> TransformT (Either String) () -> TransformT (Either String) ()
forall a b. (a -> b) -> a -> b
$
RWST () [String] Int (Either String) ()
-> TransformT (Either String) ()
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST () [String] Int (Either String) ()
-> TransformT (Either String) ())
-> RWST () [String] Int (Either String) ()
-> TransformT (Either String) ()
forall a b. (a -> b) -> a -> b
$ Either String () -> RWST () [String] Int (Either String) ()
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ String
child String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" already included in " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
parent String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" imports")
let childLIE :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn RdrName
childRdr
#if MIN_VERSION_ghc(9,5,0)
let it' :: ImportDecl GhcPs
it' = ImportDecl GhcPs
it{ideclImportList = Just (hide, lies)}
#else
let it' = it{ideclHiding = Just (hide, lies)}
#endif
lies :: GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
lies = SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnL
l' ([GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a b. (a -> b) -> a -> b
$ [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a]
reverse [GenLocated SrcSpanAnnA (IE GhcPs)]
pre [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a] -> [a]
++
[SrcSpanAnnA -> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l'' (XIEThingWith GhcPs
-> LIEWrappedName GhcPs
-> IEWildcard
-> [LIEWrappedName GhcPs]
-> IE GhcPs
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith XIEThingWith GhcPs
l''' LIEWrappedName GhcPs
twIE IEWildcard
NoIEWildcard (ASetter
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
(GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
(GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> (GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
(GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
(GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
forall s a. Snoc s s a a => Traversal' s a
Traversal'
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
(GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
_last GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
fixLast [LIEWrappedName GhcPs]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
lies' [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
forall a. [a] -> [a] -> [a]
++ [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE]))] [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a] -> [a]
++ [GenLocated SrcSpanAnnA (IE GhcPs)]
xs
fixLast :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
fixLast = if Bool
hasSibling then (SrcSpanAnnA -> SrcSpanAnnA)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SrcSpanAnnA -> SrcSpanAnnA
addComma else GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a. a -> a
id
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
it'
go ImportListInterpretation
hide SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
pre (GenLocated SrcSpanAnnA (IE GhcPs)
x : [GenLocated SrcSpanAnnA (IE GhcPs)]
xs) = ImportListInterpretation
-> SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
go ImportListInterpretation
hide SrcSpanAnnL
l' (GenLocated SrcSpanAnnA (IE GhcPs)
x GenLocated SrcSpanAnnA (IE GhcPs)
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. a -> [a] -> [a]
: [GenLocated SrcSpanAnnA (IE GhcPs)]
pre) [GenLocated SrcSpanAnnA (IE GhcPs)]
xs
go ImportListInterpretation
hide SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
pre [] = do
SrcSpan
l'' <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
SrcSpan
srcParent <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
SrcSpan
srcChild <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
LocatedAn NameAnn (IdP GhcPs)
parentRdr <- DynFlags
-> String
-> TransformT (Either String) (LocatedAn NameAnn (IdP GhcPs))
forall ast l.
(ASTElement l ast, ExactPrint (LocatedAn l ast)) =>
DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST DynFlags
df String
parent
let childRdr :: LocatedAn NameAnn RdrName
childRdr = Located RdrName -> LocatedAn NameAnn RdrName
forall e ann. Located e -> LocatedAn ann e
reLocA (Located RdrName -> LocatedAn NameAnn RdrName)
-> Located RdrName -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ SrcSpan -> RdrName -> Located RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (RdrName -> Located RdrName) -> RdrName -> Located RdrName
forall a b. (a -> b) -> a -> b
$ OccName -> RdrName
mkRdrUnqual (OccName -> RdrName) -> OccName -> RdrName
forall a b. (a -> b) -> a -> b
$ String -> OccName
mkVarOcc String
child
isParentOperator :: Bool
isParentOperator = String -> Bool
hasParen String
parent
let parentLIE :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
parentLIE = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcParent (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ if Bool
isParentOperator then XIEType GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEType p -> LIdP p -> IEWrappedName p
IEType (Int -> EpaLocation
epl Int
0) LIdP GhcPs
LocatedAn NameAnn (IdP GhcPs)
parentRdr'
else XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn (IdP GhcPs)
parentRdr'
parentRdr' :: LocatedAn NameAnn (IdP GhcPs)
parentRdr' = LocatedAn NameAnn (IdP GhcPs)
-> (NameAnn -> NameAnn) -> LocatedAn NameAnn (IdP GhcPs)
forall a ast. LocatedAn a ast -> (a -> a) -> LocatedAn a ast
modifyAnns LocatedAn NameAnn (IdP GhcPs)
parentRdr ((NameAnn -> NameAnn) -> LocatedAn NameAnn (IdP GhcPs))
-> (NameAnn -> NameAnn) -> LocatedAn NameAnn (IdP GhcPs)
forall a b. (a -> b) -> a -> b
$ \case
it :: NameAnn
it@NameAnn{nann_adornment :: NameAnn -> NameAdornment
nann_adornment = NameAdornment
NameParens} -> NameAnn
it{nann_open = epl 1, nann_close = epl 0}
NameAnn
other -> NameAnn
other
childLIE :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
srcChild (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn RdrName
childRdr
#if MIN_VERSION_ghc(9,7,0)
listAnn = (Nothing, epAnn srcParent [AddEpAnn AnnOpenP (epl 1), AddEpAnn AnnCloseP (epl 0)])
#else
listAnn :: EpAnn [AddEpAnn]
listAnn = SrcSpan -> [AddEpAnn] -> EpAnn [AddEpAnn]
forall ann. SrcSpan -> ann -> EpAnn ann
epAnn SrcSpan
srcParent [AnnKeywordId -> EpaLocation -> AddEpAnn
AddEpAnn AnnKeywordId
AnnOpenP (Int -> EpaLocation
epl Int
1), AnnKeywordId -> EpaLocation -> AddEpAnn
AddEpAnn AnnKeywordId
AnnCloseP (Int -> EpaLocation
epl Int
0)]
#endif
LIE GhcPs
x :: LIE GhcPs = Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs))
-> Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IE GhcPs -> Located (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
l'' (IE GhcPs -> Located (IE GhcPs)) -> IE GhcPs -> Located (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEThingWith GhcPs
-> LIEWrappedName GhcPs
-> IEWildcard
-> [LIEWrappedName GhcPs]
-> IE GhcPs
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith XIEThingWith GhcPs
EpAnn [AddEpAnn]
listAnn LIEWrappedName GhcPs
GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
parentLIE IEWildcard
NoIEWildcard [LIEWrappedName GhcPs
GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
childLIE]
lies' :: [GenLocated SrcSpanAnnA (IE GhcPs)]
lies' = [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnA (IE GhcPs)
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a.
[LocatedAn AnnListItem a]
-> LocatedAn AnnListItem a -> [LocatedAn AnnListItem a]
addCommaInImportList ([GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. [a] -> [a]
reverse [GenLocated SrcSpanAnnA (IE GhcPs)]
pre) LIE GhcPs
GenLocated SrcSpanAnnA (IE GhcPs)
x
#if MIN_VERSION_ghc(9,5,0)
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
it{ideclImportList = Just (hide, L l' lies')}
#else
return $ L l it{ideclHiding = Just (hide, L l' lies')}
#endif
extendImportViaParent DynFlags
_ String
_ String
_ LImportDecl GhcPs
_ = RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs)
forall (m :: * -> *) a. RWST () [String] Int m a -> TransformT m a
TransformT (RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs))
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
-> TransformT (Either String) (LImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
forall (m :: * -> *) a. Monad m => m a -> RWST () [String] Int m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs))
-> Either String (LImportDecl GhcPs)
-> RWST () [String] Int (Either String) (LImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ String -> Either String (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. a -> Either a b
Left String
"Unable to extend the import list via parent"
addCommaInImportList ::
[LocatedAn AnnListItem a]
-> LocatedAn AnnListItem a
-> [LocatedAn AnnListItem a]
addCommaInImportList :: forall a.
[LocatedAn AnnListItem a]
-> LocatedAn AnnListItem a -> [LocatedAn AnnListItem a]
addCommaInImportList [LocatedAn AnnListItem a]
lies LocatedAn AnnListItem a
x =
[LocatedAn AnnListItem a] -> [LocatedAn AnnListItem a]
forall a. [LocatedAn AnnListItem a] -> [LocatedAn AnnListItem a]
fixLast [LocatedAn AnnListItem a]
lies [LocatedAn AnnListItem a]
-> [LocatedAn AnnListItem a] -> [LocatedAn AnnListItem a]
forall a. [a] -> [a] -> [a]
++ [LocatedAn AnnListItem a
newItem]
where
isTrailingAnnComma :: TrailingAnn -> Bool
isTrailingAnnComma :: TrailingAnn -> Bool
isTrailingAnnComma (AddCommaAnn EpaLocation
_) = Bool
True
isTrailingAnnComma TrailingAnn
_ = Bool
False
existingTrailingComma :: Bool
existingTrailingComma = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ do
L SrcSpanAnnA
lastItemSrcAnn a
_ <- [LocatedAn AnnListItem a] -> Maybe (LocatedAn AnnListItem a)
forall a. [a] -> Maybe a
lastMaybe [LocatedAn AnnListItem a]
lies
AnnListItem
lastItemAnn <- case SrcSpanAnnA -> EpAnn AnnListItem
forall a. SrcSpanAnn' a -> a
ann SrcSpanAnnA
lastItemSrcAnn of
EpAnn Anchor
_ AnnListItem
lastItemAnn EpAnnComments
_ -> AnnListItem -> Maybe AnnListItem
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AnnListItem
lastItemAnn
EpAnn AnnListItem
_ -> Maybe AnnListItem
forall a. Maybe a
Nothing
Bool -> Maybe Bool
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ (TrailingAnn -> Bool) -> [TrailingAnn] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TrailingAnn -> Bool
isTrailingAnnComma (AnnListItem -> [TrailingAnn]
lann_trailing AnnListItem
lastItemAnn)
hasSibling :: Bool
hasSibling = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [LocatedAn AnnListItem a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LocatedAn AnnListItem a]
lies
newItem :: LocatedAn AnnListItem a
newItem = (SrcSpanAnnA -> SrcSpanAnnA)
-> LocatedAn AnnListItem a -> LocatedAn AnnListItem a
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (if Bool
existingTrailingComma then SrcSpanAnnA -> SrcSpanAnnA
addComma else SrcSpanAnnA -> SrcSpanAnnA
forall a. a -> a
id) (LocatedAn AnnListItem a -> LocatedAn AnnListItem a)
-> LocatedAn AnnListItem a -> LocatedAn AnnListItem a
forall a b. (a -> b) -> a -> b
$
LocatedAn AnnListItem a -> DeltaPos -> LocatedAn AnnListItem a
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
setEntryDP LocatedAn AnnListItem a
x (Int -> DeltaPos
SameLine (Int -> DeltaPos) -> Int -> DeltaPos
forall a b. (a -> b) -> a -> b
$ if Bool
hasSibling then Int
1 else Int
0)
fixLast :: [LocatedAn AnnListItem a] -> [LocatedAn AnnListItem a]
fixLast :: forall a. [LocatedAn AnnListItem a] -> [LocatedAn AnnListItem a]
fixLast = ASetter
[LocatedAn AnnListItem a]
[LocatedAn AnnListItem a]
(LocatedAn AnnListItem a)
(LocatedAn AnnListItem a)
-> (LocatedAn AnnListItem a -> LocatedAn AnnListItem a)
-> [LocatedAn AnnListItem a]
-> [LocatedAn AnnListItem a]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[LocatedAn AnnListItem a]
[LocatedAn AnnListItem a]
(LocatedAn AnnListItem a)
(LocatedAn AnnListItem a)
forall s a. Snoc s s a a => Traversal' s a
Traversal' [LocatedAn AnnListItem a] (LocatedAn AnnListItem a)
_last ((SrcSpanAnnA -> SrcSpanAnnA)
-> LocatedAn AnnListItem a -> LocatedAn AnnListItem a
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (if Bool
existingTrailingComma then SrcSpanAnnA -> SrcSpanAnnA
forall a. a -> a
id else SrcSpanAnnA -> SrcSpanAnnA
addComma))
#if MIN_VERSION_ghc(9,5,0)
unIEWrappedName :: IEWrappedName GhcPs -> String
#else
unIEWrappedName :: IEWrappedName (IdP GhcPs) -> String
#endif
unIEWrappedName :: IEWrappedName GhcPs -> String
unIEWrappedName (IEWrappedName GhcPs -> OccName
forall name. HasOccName name => name -> OccName
occName -> OccName
occ) = Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ SDoc -> Text
forall a. Outputable a => a -> Text
printOutputable (SDoc -> Text) -> SDoc -> Text
forall a b. (a -> b) -> a -> b
$ OccName -> SDoc -> SDoc
parenSymOcc OccName
occ (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ)
hasParen :: String -> Bool
hasParen :: String -> Bool
hasParen (Char
'(' : String
_) = Bool
True
hasParen String
_ = Bool
False
hideSymbol ::
String -> LImportDecl GhcPs -> Rewrite
hideSymbol :: String -> LImportDecl GhcPs -> Rewrite
hideSymbol String
symbol lidecl :: LImportDecl GhcPs
lidecl@(L SrcSpanAnnA
loc ImportDecl{Bool
Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
Maybe (XRec GhcPs ModuleName)
ImportDeclPkgQual GhcPs
XCImportDecl GhcPs
XRec GhcPs ModuleName
IsBootInterface
ImportDeclQualifiedStyle
ideclExt :: forall pass. ImportDecl pass -> XCImportDecl pass
ideclName :: forall pass. ImportDecl pass -> XRec pass ModuleName
ideclPkgQual :: forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclSource :: forall pass. ImportDecl pass -> IsBootInterface
ideclSafe :: forall pass. ImportDecl pass -> Bool
ideclQualified :: forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclAs :: forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclImportList :: forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclExt :: XCImportDecl GhcPs
ideclName :: XRec GhcPs ModuleName
ideclPkgQual :: ImportDeclPkgQual GhcPs
ideclSource :: IsBootInterface
ideclSafe :: Bool
ideclQualified :: ImportDeclQualifiedStyle
ideclAs :: Maybe (XRec GhcPs ModuleName)
ideclImportList :: Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
..}) =
#if MIN_VERSION_ghc(9,5,0)
case Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
ideclImportList of
Maybe (ImportListInterpretation, XRec GhcPs [LIE GhcPs])
Nothing -> SrcSpan
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) ((DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ String
-> LImportDecl GhcPs
-> Maybe (XRec GhcPs [LIE GhcPs])
-> DynFlags
-> TransformT (Either String) (LImportDecl GhcPs)
extendHiding String
symbol LImportDecl GhcPs
lidecl Maybe (XRec GhcPs [LIE GhcPs])
Maybe (GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
forall a. Maybe a
Nothing
Just (ImportListInterpretation
EverythingBut, XRec GhcPs [LIE GhcPs]
hides) -> SrcSpan
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) ((DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ String
-> LImportDecl GhcPs
-> Maybe (XRec GhcPs [LIE GhcPs])
-> DynFlags
-> TransformT (Either String) (LImportDecl GhcPs)
extendHiding String
symbol LImportDecl GhcPs
lidecl (GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> Maybe
(GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
forall a. a -> Maybe a
Just XRec GhcPs [LIE GhcPs]
GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
hides)
Just (ImportListInterpretation
Exactly, XRec GhcPs [LIE GhcPs]
imports) -> SrcSpan
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall ast.
(ExactPrint (GenLocated (Anno ast) ast), ResetEntryDP (Anno ast),
Outputable (GenLocated (Anno ast) ast),
Data (GenLocated (Anno ast) ast)) =>
SrcSpan
-> (DynFlags
-> TransformT (Either String) (GenLocated (Anno ast) ast))
-> Rewrite
Rewrite (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) ((DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite)
-> (DynFlags
-> TransformT
(Either String)
(GenLocated (Anno (ImportDecl GhcPs)) (ImportDecl GhcPs)))
-> Rewrite
forall a b. (a -> b) -> a -> b
$ String
-> LImportDecl GhcPs
-> XRec GhcPs [LIE GhcPs]
-> DynFlags
-> TransformT (Either String) (LImportDecl GhcPs)
deleteFromImport String
symbol LImportDecl GhcPs
lidecl XRec GhcPs [LIE GhcPs]
imports
#else
case ideclHiding of
Nothing -> Rewrite (locA loc) $ extendHiding symbol lidecl Nothing
Just (True, hides) -> Rewrite (locA loc) $ extendHiding symbol lidecl (Just hides)
Just (False, imports) -> Rewrite (locA loc) $ deleteFromImport symbol lidecl imports
#endif
extendHiding ::
String ->
LImportDecl GhcPs ->
Maybe (XRec GhcPs [LIE GhcPs]) ->
DynFlags ->
TransformT (Either String) (LImportDecl GhcPs)
extendHiding :: String
-> LImportDecl GhcPs
-> Maybe (XRec GhcPs [LIE GhcPs])
-> DynFlags
-> TransformT (Either String) (LImportDecl GhcPs)
extendHiding String
symbol (L SrcSpanAnnA
l ImportDecl GhcPs
idecls) Maybe (XRec GhcPs [LIE GhcPs])
mlies DynFlags
df = do
L SrcSpanAnnL
l' [GenLocated SrcSpanAnnA (IE GhcPs)]
lies <- case Maybe (XRec GhcPs [LIE GhcPs])
mlies of
Maybe (XRec GhcPs [LIE GhcPs])
Nothing -> do
SrcSpan
src <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
let ann :: SrcSpanAnnL
ann = SrcSpan -> SrcSpanAnnL
forall ann. Monoid ann => SrcSpan -> SrcSpanAnn' (EpAnn ann)
noAnnSrcSpanDP0 SrcSpan
src
ann' :: SrcSpanAnnL
ann' = ((AnnList -> AnnList) -> SrcSpanAnnL -> SrcSpanAnnL)
-> SrcSpanAnnL -> (AnnList -> AnnList) -> SrcSpanAnnL
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((EpAnn AnnList -> EpAnn AnnList) -> SrcSpanAnnL -> SrcSpanAnnL
forall a b. (a -> b) -> SrcSpanAnn' a -> SrcSpanAnn' b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap((EpAnn AnnList -> EpAnn AnnList) -> SrcSpanAnnL -> SrcSpanAnnL)
-> ((AnnList -> AnnList) -> EpAnn AnnList -> EpAnn AnnList)
-> (AnnList -> AnnList)
-> SrcSpanAnnL
-> SrcSpanAnnL
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(AnnList -> AnnList) -> EpAnn AnnList -> EpAnn AnnList
forall a b. (a -> b) -> EpAnn a -> EpAnn b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) SrcSpanAnnL
ann ((AnnList -> AnnList) -> SrcSpanAnnL)
-> (AnnList -> AnnList) -> SrcSpanAnnL
forall a b. (a -> b) -> a -> b
$ \AnnList
x -> AnnList
x
{al_rest = [AddEpAnn AnnHiding (epl 1)]
,al_open = Just $ AddEpAnn AnnOpenP (epl 1)
,al_close = Just $ AddEpAnn AnnCloseP (epl 0)
}
GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String)
(GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String)
(GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]))
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String)
(GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnL
ann' []
Just XRec GhcPs [LIE GhcPs]
pr -> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT
(Either String)
(GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure XRec GhcPs [LIE GhcPs]
GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
pr
let hasSibling :: Bool
hasSibling = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [GenLocated SrcSpanAnnA (IE GhcPs)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [GenLocated SrcSpanAnnA (IE GhcPs)]
lies
SrcSpan
src <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
SrcSpan
top <- TransformT (Either String) SrcSpan
forall (m :: * -> *). Monad m => TransformT m SrcSpan
uniqueSrcSpanT
LocatedAn NameAnn RdrName
rdr <- DynFlags
-> String -> TransformT (Either String) (LocatedAn NameAnn RdrName)
forall ast l.
(ASTElement l ast, ExactPrint (LocatedAn l ast)) =>
DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
liftParseAST DynFlags
df String
symbol
LocatedAn NameAnn RdrName
rdr <- LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName)
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName))
-> LocatedAn NameAnn RdrName
-> TransformT (Either String) (LocatedAn NameAnn RdrName)
forall a b. (a -> b) -> a -> b
$ LocatedAn NameAnn RdrName
-> (NameAnn -> NameAnn) -> LocatedAn NameAnn RdrName
forall a ast. LocatedAn a ast -> (a -> a) -> LocatedAn a ast
modifyAnns LocatedAn NameAnn RdrName
rdr ((NameAnn -> NameAnn) -> LocatedAn NameAnn RdrName)
-> (NameAnn -> NameAnn) -> LocatedAn NameAnn RdrName
forall a b. (a -> b) -> a -> b
$ Bool -> NameAnn -> NameAnn
addParens (RdrName -> Bool
isOperator (RdrName -> Bool) -> RdrName -> Bool
forall a b. (a -> b) -> a -> b
$ LocatedAn NameAnn RdrName -> RdrName
forall l e. GenLocated l e -> e
unLoc LocatedAn NameAnn RdrName
rdr)
let lie :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
lie = Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
-> Located (IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
src (IEWrappedName GhcPs -> Located (IEWrappedName GhcPs))
-> IEWrappedName GhcPs -> Located (IEWrappedName GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName
#if MIN_VERSION_ghc(9,5,0)
XIEName GhcPs
NoExtField
noExtField
#endif
LIdP GhcPs
LocatedAn NameAnn RdrName
rdr
x :: GenLocated SrcSpanAnnA (IE GhcPs)
x = Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall e ann. Located e -> LocatedAn ann e
reLocA (Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs))
-> Located (IE GhcPs) -> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ SrcSpan -> IE GhcPs -> Located (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
top (IE GhcPs -> Located (IE GhcPs)) -> IE GhcPs -> Located (IE GhcPs)
forall a b. (a -> b) -> a -> b
$ XIEVar GhcPs -> LIEWrappedName GhcPs -> IE GhcPs
forall pass. XIEVar pass -> LIEWrappedName pass -> IE pass
IEVar
#if MIN_VERSION_ghc(9,7,0)
Nothing
#else
XIEVar GhcPs
NoExtField
noExtField
#endif
LIEWrappedName GhcPs
GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
lie
GenLocated SrcSpanAnnA (IE GhcPs)
x <- GenLocated SrcSpanAnnA (IE GhcPs)
-> TransformT (Either String) (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenLocated SrcSpanAnnA (IE GhcPs)
-> TransformT (Either String) (GenLocated SrcSpanAnnA (IE GhcPs)))
-> GenLocated SrcSpanAnnA (IE GhcPs)
-> TransformT (Either String) (GenLocated SrcSpanAnnA (IE GhcPs))
forall a b. (a -> b) -> a -> b
$ if Bool
hasSibling then (SrcSpanAnnA -> SrcSpanAnnA)
-> GenLocated SrcSpanAnnA (IE GhcPs)
-> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b c. (a -> b) -> GenLocated a c -> GenLocated b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SrcSpanAnnA -> SrcSpanAnnA
addComma GenLocated SrcSpanAnnA (IE GhcPs)
x else GenLocated SrcSpanAnnA (IE GhcPs)
x
[GenLocated SrcSpanAnnA (IE GhcPs)]
lies <- [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT (Either String) [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT (Either String) [GenLocated SrcSpanAnnA (IE GhcPs)])
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> TransformT (Either String) [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a b. (a -> b) -> a -> b
$ ASetter
[GenLocated SrcSpanAnnA (IE GhcPs)]
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
(GenLocated SrcSpanAnnA (IE GhcPs))
-> (GenLocated SrcSpanAnnA (IE GhcPs)
-> GenLocated SrcSpanAnnA (IE GhcPs))
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[GenLocated SrcSpanAnnA (IE GhcPs)]
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
(GenLocated SrcSpanAnnA (IE GhcPs))
forall s a. Cons s s a a => Traversal' s a
Traversal'
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
_head (GenLocated SrcSpanAnnA (IE GhcPs)
-> DeltaPos -> GenLocated SrcSpanAnnA (IE GhcPs)
forall t a. Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a
`setEntryDP` Int -> DeltaPos
SameLine Int
1) [GenLocated SrcSpanAnnA (IE GhcPs)]
lies
#if MIN_VERSION_ghc(9,5,0)
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs)))
-> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a b. (a -> b) -> a -> b
$ SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l ImportDecl GhcPs
idecls{ideclImportList = Just (EverythingBut, L l' $ x : lies)}
#else
return $ L l idecls{ideclHiding = Just (True, L l' $ x : lies)}
#endif
where
isOperator :: RdrName -> Bool
isOperator = Bool -> Bool
not (Bool -> Bool) -> (RdrName -> Bool) -> RdrName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAlphaNum (String -> Bool) -> (RdrName -> String) -> RdrName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccName -> String
occNameString (OccName -> String) -> (RdrName -> OccName) -> RdrName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc
deleteFromImport ::
String ->
LImportDecl GhcPs ->
XRec GhcPs [LIE GhcPs] ->
DynFlags ->
TransformT (Either String) (LImportDecl GhcPs)
deleteFromImport :: String
-> LImportDecl GhcPs
-> XRec GhcPs [LIE GhcPs]
-> DynFlags
-> TransformT (Either String) (LImportDecl GhcPs)
deleteFromImport (String -> Text
T.pack -> Text
symbol) (L SrcSpanAnnA
l ImportDecl GhcPs
idecl) (L SrcSpanAnnL
lieLoc [GenLocated SrcSpanAnnA (IE GhcPs)]
lies) DynFlags
_ = do
let edited :: GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
edited = SrcSpanAnnL
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)]
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnL
lieLoc [GenLocated SrcSpanAnnA (IE GhcPs)]
deletedLies
lidecl' :: GenLocated SrcSpanAnnA (ImportDecl GhcPs)
lidecl' =
SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l (ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs))
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$
ImportDecl GhcPs
idecl
#if MIN_VERSION_ghc(9,5,0)
{ ideclImportList = Just (Exactly, edited)
#else
{ ideclHiding = Just (False, edited)
#endif
}
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> TransformT
(Either String) (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
forall a. a -> TransformT (Either String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure GenLocated SrcSpanAnnA (ImportDecl GhcPs)
lidecl'
where
deletedLies :: [GenLocated SrcSpanAnnA (IE GhcPs)]
deletedLies =
ASetter
[GenLocated SrcSpanAnnA (IE GhcPs)]
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
(GenLocated SrcSpanAnnA (IE GhcPs))
-> (GenLocated SrcSpanAnnA (IE GhcPs)
-> GenLocated SrcSpanAnnA (IE GhcPs))
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
[GenLocated SrcSpanAnnA (IE GhcPs)]
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
(GenLocated SrcSpanAnnA (IE GhcPs))
forall s a. Snoc s s a a => Traversal' s a
Traversal'
[GenLocated SrcSpanAnnA (IE GhcPs)]
(GenLocated SrcSpanAnnA (IE GhcPs))
_last GenLocated SrcSpanAnnA (IE GhcPs)
-> GenLocated SrcSpanAnnA (IE GhcPs)
forall ast.
GenLocated SrcSpanAnnA ast -> GenLocated SrcSpanAnnA ast
removeTrailingComma ([GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)])
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a b. (a -> b) -> a -> b
$
(GenLocated SrcSpanAnnA (IE GhcPs)
-> Maybe (GenLocated SrcSpanAnnA (IE GhcPs)))
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LIE GhcPs -> Maybe (LIE GhcPs)
GenLocated SrcSpanAnnA (IE GhcPs)
-> Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
killLie [GenLocated SrcSpanAnnA (IE GhcPs)]
lies
killLie :: LIE GhcPs -> Maybe (LIE GhcPs)
killLie :: LIE GhcPs -> Maybe (LIE GhcPs)
killLie v :: LIE GhcPs
v@(L SrcSpanAnnA
_ (IEVar XIEVar GhcPs
_ (L SrcSpanAnnA
_ (IEWrappedName GhcPs -> Text
unqualIEWrapName -> Text
nam))))
| Text
nam Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
symbol = Maybe (LIE GhcPs)
Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. Maybe a
Nothing
| Bool
otherwise = GenLocated SrcSpanAnnA (IE GhcPs)
-> Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. a -> Maybe a
Just LIE GhcPs
GenLocated SrcSpanAnnA (IE GhcPs)
v
killLie v :: LIE GhcPs
v@(L SrcSpanAnnA
_ (IEThingAbs XIEThingAbs GhcPs
_ (L SrcSpanAnnA
_ (IEWrappedName GhcPs -> Text
unqualIEWrapName -> Text
nam))))
| Text
nam Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
symbol = Maybe (LIE GhcPs)
Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. Maybe a
Nothing
| Bool
otherwise = GenLocated SrcSpanAnnA (IE GhcPs)
-> Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. a -> Maybe a
Just LIE GhcPs
GenLocated SrcSpanAnnA (IE GhcPs)
v
killLie (L SrcSpanAnnA
lieL (IEThingWith XIEThingWith GhcPs
xt ty :: LIEWrappedName GhcPs
ty@(L SrcSpanAnnA
_ (IEWrappedName GhcPs -> Text
unqualIEWrapName -> Text
nam)) IEWildcard
wild [LIEWrappedName GhcPs]
cons))
| Text
nam Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
symbol = Maybe (LIE GhcPs)
Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. Maybe a
Nothing
| Bool
otherwise =
LIE GhcPs -> Maybe (LIE GhcPs)
forall a. a -> Maybe a
Just (LIE GhcPs -> Maybe (LIE GhcPs)) -> LIE GhcPs -> Maybe (LIE GhcPs)
forall a b. (a -> b) -> a -> b
$
SrcSpanAnnA -> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
lieL (IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs))
-> IE GhcPs -> GenLocated SrcSpanAnnA (IE GhcPs)
forall a b. (a -> b) -> a -> b
$
XIEThingWith GhcPs
-> LIEWrappedName GhcPs
-> IEWildcard
-> [LIEWrappedName GhcPs]
-> IE GhcPs
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith
XIEThingWith GhcPs
xt
LIEWrappedName GhcPs
ty
IEWildcard
wild
((GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Bool)
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
symbol) (Text -> Bool)
-> (GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Text)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IEWrappedName GhcPs -> Text
unqualIEWrapName (IEWrappedName GhcPs -> Text)
-> (GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> IEWrappedName GhcPs)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> IEWrappedName GhcPs
forall l e. GenLocated l e -> e
unLoc) [LIEWrappedName GhcPs]
[GenLocated SrcSpanAnnA (IEWrappedName GhcPs)]
cons)
killLie LIE GhcPs
v = GenLocated SrcSpanAnnA (IE GhcPs)
-> Maybe (GenLocated SrcSpanAnnA (IE GhcPs))
forall a. a -> Maybe a
Just LIE GhcPs
GenLocated SrcSpanAnnA (IE GhcPs)
v