{-# LANGUAGE CPP #-}
module AutoSplit.GhcFacade
( module Ghc
, mkParPat'
, anchorD0
, anchorD1
, nameAnchorD0
, nameAnchorD1
, colDelta
, nextLine
, getComments
, setComments
, fakeCommentLocation
, parenAnns
, parenHashAnns
, greToName
, noLocCpp
, noExtFieldCpp
) where
#if MIN_VERSION_ghc(9,8,0)
import GHC.Driver.DynFlags as Ghc
import GHC.Types.Var as Ghc
#else
import GHC.Driver.Flags as Ghc
import GHC.Types.Var as Ghc hiding (varName)
import GHC.Driver.Session as Ghc
#endif
import GHC as Ghc (ParsedSource)
import GHC.Core.ConLike as Ghc
import GHC.Core.DataCon as Ghc
import GHC.Data.Bag as Ghc
import GHC.Driver.Env as Ghc
import GHC.Driver.Errors.Types as Ghc
import GHC.Driver.Hooks as Ghc
import GHC.Driver.Main as Ghc
import GHC.Driver.Pipeline.Execute as Ghc
import GHC.Driver.Pipeline.Phases as Ghc
import GHC.Driver.Plugins as Ghc
import GHC.Driver.Monad as Ghc
import GHC.Hs as Ghc
import GHC.HsToCore.Errors.Types as Ghc
import GHC.HsToCore.Pmc.Solver.Types as Ghc
import GHC.Tc.Errors.Types as Ghc
import GHC.Tc.Utils.Monad as Ghc hiding (DefaultingPlugin, TcPlugin)
import GHC.Types.Error as Ghc
import GHC.Types.Name as Ghc
import GHC.Types.Name.Reader as Ghc
import GHC.Types.SourceError as Ghc
import GHC.Types.SourceText as Ghc
import GHC.Types.SrcLoc as Ghc
import GHC.Unit.Module.Location as Ghc
import GHC.Unit.Module.ModSummary as Ghc
import GHC.Unit.Types as Ghc
import GHC.Utils.Error as Ghc
import GHC.Utils.Outputable as Ghc
import Language.Haskell.Syntax.Basic as Ghc
#if !MIN_VERSION_ghc(9,10,0)
import Data.Maybe
#endif
import qualified Language.Haskell.GHC.ExactPrint as EP
mkParPat' :: Ghc.LPat Ghc.GhcPs -> Ghc.Pat Ghc.GhcPs
#if MIN_VERSION_ghc(9,10,0)
mkParPat' inner = Ghc.ParPat (Ghc.EpTok EP.d0, Ghc.EpTok EP.d0) inner
#elif MIN_VERSION_ghc(9,6,0)
mkParPat' :: LPat GhcPs -> Pat GhcPs
mkParPat' LPat GhcPs
inner = XParPat GhcPs
-> LHsToken "(" GhcPs
-> LPat GhcPs
-> LHsToken ")" GhcPs
-> Pat GhcPs
forall p.
XParPat p -> LHsToken "(" p -> LPat p -> LHsToken ")" p -> Pat p
Ghc.ParPat XParPat GhcPs
EpAnn NoEpAnns
forall a. EpAnn a
Ghc.noAnn (TokenLocation
-> HsToken "(" -> GenLocated TokenLocation (HsToken "(")
forall l e. l -> e -> GenLocated l e
Ghc.L (EpaLocation -> TokenLocation
Ghc.TokenLoc EpaLocation
EP.d0) HsToken "("
forall (tok :: Symbol). HsToken tok
Ghc.HsTok) LPat GhcPs
inner (TokenLocation
-> HsToken ")" -> GenLocated TokenLocation (HsToken ")")
forall l e. l -> e -> GenLocated l e
Ghc.L (EpaLocation -> TokenLocation
Ghc.TokenLoc EpaLocation
EP.d0) HsToken ")"
forall (tok :: Symbol). HsToken tok
Ghc.HsTok)
#endif
anchorD0
#if MIN_VERSION_ghc(9,10,0)
:: Ghc.NoAnn ann => Ghc.EpAnn ann
anchorD0 = Ghc.EpAnn EP.d0 Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,6,0)
:: Ghc.SrcSpanAnnA
anchorD0 :: SrcSpanAnnA
anchorD0 =
EpAnn AnnListItem -> SrcSpan -> SrcSpanAnnA
forall a. a -> SrcSpan -> SrcSpanAnn' a
Ghc.SrcSpanAnn
(Anchor -> AnnListItem -> EpAnnComments -> EpAnn AnnListItem
forall ann. Anchor -> ann -> EpAnnComments -> EpAnn ann
Ghc.EpAnn
(RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> DeltaPos
Ghc.SameLine Int
0)))
AnnListItem
forall a. Monoid a => a
mempty
EpAnnComments
Ghc.emptyComments
)
SrcSpan
Ghc.generatedSrcSpan
#endif
anchorD1
#if MIN_VERSION_ghc(9,10,0)
:: Ghc.NoAnn ann => Ghc.EpAnn ann
anchorD1 = Ghc.EpAnn EP.d1 Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,6,0)
:: Ghc.SrcSpanAnnA
anchorD1 :: SrcSpanAnnA
anchorD1 =
EpAnn AnnListItem -> SrcSpan -> SrcSpanAnnA
forall a. a -> SrcSpan -> SrcSpanAnn' a
Ghc.SrcSpanAnn
(Anchor -> AnnListItem -> EpAnnComments -> EpAnn AnnListItem
forall ann. Anchor -> ann -> EpAnnComments -> EpAnn ann
Ghc.EpAnn
(RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> DeltaPos
Ghc.SameLine Int
1)))
AnnListItem
forall a. Monoid a => a
mempty
EpAnnComments
Ghc.emptyComments
)
SrcSpan
Ghc.generatedSrcSpan
#endif
nameAnchorD0
#if MIN_VERSION_ghc(9,10,0)
:: Ghc.NoAnn ann => Ghc.EpAnn ann
nameAnchorD0 = Ghc.EpAnn EP.d0 Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,6,0)
:: Ghc.SrcSpanAnnN
nameAnchorD0 :: SrcSpanAnnN
nameAnchorD0 =
EpAnn NameAnn -> SrcSpan -> SrcSpanAnnN
forall a. a -> SrcSpan -> SrcSpanAnn' a
Ghc.SrcSpanAnn
(Anchor -> NameAnn -> EpAnnComments -> EpAnn NameAnn
forall ann. Anchor -> ann -> EpAnnComments -> EpAnn ann
Ghc.EpAnn
(RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> DeltaPos
Ghc.SameLine Int
0)))
NameAnn
forall a. Monoid a => a
mempty
EpAnnComments
Ghc.emptyComments
)
SrcSpan
Ghc.generatedSrcSpan
#endif
nameAnchorD1
#if MIN_VERSION_ghc(9,10,0)
:: Ghc.NoAnn ann => Ghc.EpAnn ann
nameAnchorD1 = Ghc.EpAnn EP.d1 Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,6,0)
:: Ghc.SrcSpanAnnN
nameAnchorD1 :: SrcSpanAnnN
nameAnchorD1 =
EpAnn NameAnn -> SrcSpan -> SrcSpanAnnN
forall a. a -> SrcSpan -> SrcSpanAnn' a
Ghc.SrcSpanAnn
(Anchor -> NameAnn -> EpAnnComments -> EpAnn NameAnn
forall ann. Anchor -> ann -> EpAnnComments -> EpAnn ann
Ghc.EpAnn
(RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> DeltaPos
Ghc.SameLine Int
1)))
NameAnn
forall a. Monoid a => a
mempty
EpAnnComments
Ghc.emptyComments
)
SrcSpan
Ghc.generatedSrcSpan
#endif
nextLine
:: Int
#if MIN_VERSION_ghc(9,12,0)
-> Ghc.NoAnn ann => Ghc.EpAnn ann
nextLine colOffset =
Ghc.EpAnn (Ghc.EpaDelta Ghc.noSrcSpan (Ghc.DifferentLine 1 colOffset) []) Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,10,0)
-> Ghc.NoAnn ann => Ghc.EpAnn ann
nextLine colOffset =
Ghc.EpAnn (Ghc.EpaDelta (Ghc.DifferentLine 1 colOffset) []) Ghc.noAnn Ghc.emptyComments
#elif MIN_VERSION_ghc(9,6,0)
-> Ghc.SrcSpanAnnA
nextLine :: Int -> SrcSpanAnnA
nextLine Int
colOffset =
EpAnn AnnListItem -> SrcSpan -> SrcSpanAnnA
forall a. a -> SrcSpan -> SrcSpanAnn' a
Ghc.SrcSpanAnn
(Anchor -> AnnListItem -> EpAnnComments -> EpAnn AnnListItem
forall ann. Anchor -> ann -> EpAnnComments -> EpAnn ann
Ghc.EpAnn
(RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> Int -> DeltaPos
Ghc.DifferentLine Int
1 Int
colOffset)))
AnnListItem
forall a. Monoid a => a
mempty
EpAnnComments
Ghc.emptyComments
)
SrcSpan
Ghc.generatedSrcSpan
#endif
#if MIN_VERSION_ghc(9,12,0)
colDelta :: Ghc.EpAnn ann -> Int
colDelta (Ghc.EpAnn (Ghc.EpaDelta _ delta _) _ _)
#elif MIN_VERSION_ghc(9,10,0)
colDelta :: Ghc.EpAnn ann -> Int
colDelta (Ghc.EpAnn (Ghc.EpaDelta delta _) _ _)
#elif MIN_VERSION_ghc(9,6,0)
colDelta :: Ghc.SrcSpanAnn' (Ghc.EpAnn ann) -> Int
colDelta :: forall ann. SrcSpanAnn' (EpAnn ann) -> Int
colDelta (Ghc.SrcSpanAnn (Ghc.EpAnn (Ghc.Anchor RealSrcSpan
_ (Ghc.MovedAnchor DeltaPos
delta)) ann
_ EpAnnComments
_) SrcSpan
_)
#endif
= case DeltaPos
delta of
Ghc.DifferentLine Int
_ Int
c -> Int
c
Ghc.SameLine Int
c -> Int
c
colDelta SrcSpanAnn' (EpAnn ann)
_ = Int
0
#if MIN_VERSION_ghc(9,10,0)
getComments :: Ghc.EpAnn ann -> Ghc.EpAnnComments
getComments = Ghc.comments
#elif MIN_VERSION_ghc(9,6,0)
getComments :: Ghc.SrcSpanAnn' (Ghc.EpAnn ann) -> Ghc.EpAnnComments
SrcSpanAnn' (EpAnn ann)
a = case SrcSpanAnn' (EpAnn ann) -> EpAnn ann
forall a. SrcSpanAnn' a -> a
Ghc.ann SrcSpanAnn' (EpAnn ann)
a of
EpAnn ann
Ghc.EpAnnNotUsed -> EpAnnComments
Ghc.emptyComments
EpAnn ann
epAn -> EpAnn ann -> EpAnnComments
forall ann. EpAnn ann -> EpAnnComments
Ghc.comments EpAnn ann
epAn
#endif
#if MIN_VERSION_ghc(9,10,0)
setComments :: Ghc.EpAnnComments -> () -> Ghc.EpAnn ann -> Ghc.EpAnn ann
setComments comms () a = a {Ghc.comments = comms}
#elif MIN_VERSION_ghc(9,6,0)
setComments :: Ghc.EpAnnComments -> ann -> Ghc.SrcSpanAnn' (Ghc.EpAnn ann) -> Ghc.SrcSpanAnn' (Ghc.EpAnn ann)
EpAnnComments
comms ann
defAnn SrcSpanAnn' (EpAnn ann)
a =
case SrcSpanAnn' (EpAnn ann) -> EpAnn ann
forall a. SrcSpanAnn' a -> a
Ghc.ann SrcSpanAnn' (EpAnn ann)
a of
EpAnn ann
Ghc.EpAnnNotUsed ->
SrcSpanAnn' (EpAnn ann)
a { Ghc.ann = Ghc.EpAnn
(Ghc.Anchor
(fromMaybe Ghc.placeholderRealSpan . Ghc.srcSpanToRealSrcSpan $ Ghc.locA a)
Ghc.UnchangedAnchor
) defAnn comms
}
EpAnn ann
_ -> SrcSpanAnn' (EpAnn ann)
a {Ghc.ann = (Ghc.ann a) {Ghc.comments = comms}}
#endif
fakeCommentLocation
#if MIN_VERSION_ghc(9,12,0)
:: Ghc.NoCommentsLocation
fakeCommentLocation = Ghc.EpaDelta Ghc.noSrcSpan (Ghc.DifferentLine (-1) 0) Ghc.NoComments
#elif MIN_VERSION_ghc(9,10,0)
:: Ghc.NoCommentsLocation
fakeCommentLocation = Ghc.EpaDelta (Ghc.DifferentLine (-1) 0) Ghc.NoComments
#elif MIN_VERSION_ghc(9,6,0)
:: Ghc.Anchor
= RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan (DeltaPos -> AnchorOperation
Ghc.MovedAnchor (Int -> Int -> DeltaPos
Ghc.DifferentLine (-Int
1) Int
0))
#endif
#if MIN_VERSION_ghc(9,12,0)
parenAnns :: (Ghc.EpaLocation, Ghc.EpaLocation)
parenAnns = (EP.d0, EP.d0)
parenHashAnns :: (Ghc.EpaLocation, Ghc.EpaLocation)
parenHashAnns = (EP.d0, EP.d0)
#elif MIN_VERSION_ghc(9,10,0)
parenAnns :: [Ghc.AddEpAnn]
parenAnns =
[ Ghc.AddEpAnn Ghc.AnnOpenP EP.d0
, Ghc.AddEpAnn Ghc.AnnCloseP EP.d0
]
parenHashAnns :: [Ghc.AddEpAnn]
parenHashAnns =
[ Ghc.AddEpAnn Ghc.AnnOpenPH EP.d0
, Ghc.AddEpAnn Ghc.AnnClosePH EP.d0
]
#else
parenAnns :: Ghc.EpAnn [Ghc.AddEpAnn]
parenAnns :: EpAnn [AddEpAnn]
parenAnns = Ghc.EpAnn
{ entry :: Anchor
Ghc.entry = RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan AnchorOperation
EP.m0
, anns :: [AddEpAnn]
Ghc.anns =
[ AnnKeywordId -> EpaLocation -> AddEpAnn
Ghc.AddEpAnn AnnKeywordId
Ghc.AnnOpenP EpaLocation
EP.d0
, AnnKeywordId -> EpaLocation -> AddEpAnn
Ghc.AddEpAnn AnnKeywordId
Ghc.AnnCloseP EpaLocation
EP.d0
]
, comments :: EpAnnComments
Ghc.comments = EpAnnComments
Ghc.emptyComments
}
parenHashAnns :: Ghc.EpAnn [Ghc.AddEpAnn]
parenHashAnns :: EpAnn [AddEpAnn]
parenHashAnns = Ghc.EpAnn
{ entry :: Anchor
Ghc.entry = RealSrcSpan -> AnchorOperation -> Anchor
Ghc.Anchor RealSrcSpan
Ghc.placeholderRealSpan AnchorOperation
EP.m0
, anns :: [AddEpAnn]
Ghc.anns =
[ AnnKeywordId -> EpaLocation -> AddEpAnn
Ghc.AddEpAnn AnnKeywordId
Ghc.AnnOpenPH EpaLocation
EP.d0
, AnnKeywordId -> EpaLocation -> AddEpAnn
Ghc.AddEpAnn AnnKeywordId
Ghc.AnnClosePH EpaLocation
EP.d0
]
, comments :: EpAnnComments
Ghc.comments = EpAnnComments
Ghc.emptyComments
}
#endif
greToName :: Ghc.GlobalRdrElt -> Ghc.Name
greToName :: GlobalRdrElt -> Name
greToName =
#if MIN_VERSION_ghc(9,8,0)
Ghc.greName
#else
GlobalRdrElt -> Name
Ghc.grePrintableName
#endif
#if MIN_VERSION_ghc(9,12,0)
noLocCpp :: Ghc.HasAnnotation e => a -> Ghc.GenLocated e a
noLocCpp = Ghc.noLocA
#else
noLocCpp :: a -> a
noLocCpp :: forall a. a -> a
noLocCpp = a -> a
forall a. a -> a
id
#endif
#if MIN_VERSION_ghc(9,12,0)
noExtFieldCpp :: Ghc.NoExtField
noExtFieldCpp = Ghc.noExtField
#elif MIN_VERSION_ghc(9,10,0)
noExtFieldCpp :: [a]
noExtFieldCpp = []
#else
noExtFieldCpp :: Ghc.EpAnn a
noExtFieldCpp :: forall a. EpAnn a
noExtFieldCpp = EpAnn a
forall a. EpAnn a
Ghc.noAnn
#endif