{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Language.Haskell.Syntax.ImpExp where

import Language.Haskell.Syntax.Extension
import Language.Haskell.Syntax.Module.Name

import Data.Eq (Eq)
import Data.Ord (Ord)
import Text.Show (Show)
import Data.Data (Data)
import Data.Bool (Bool)
import Data.Maybe (Maybe)
import Data.String (String)
import Data.Int (Int)

import GHC.Hs.Doc -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST

{-
************************************************************************
*                                                                      *
Import and export declaration lists
*                                                                      *
************************************************************************

One per import declaration in a module.
-}

-- | Located Import Declaration
type LImportDecl pass = XRec pass (ImportDecl pass)
        -- ^ When in a list this may have
        --
        --  - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation

-- | If/how an import is 'qualified'.
data ImportDeclQualifiedStyle
  = QualifiedPre  -- ^ 'qualified' appears in prepositive position.
  | QualifiedPost -- ^ 'qualified' appears in postpositive position.
  | NotQualified  -- ^ Not qualified.
  deriving (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
(ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> Eq ImportDeclQualifiedStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
Eq, Typeable ImportDeclQualifiedStyle
Typeable ImportDeclQualifiedStyle =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> ImportDeclQualifiedStyle
 -> c ImportDeclQualifiedStyle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle)
-> (ImportDeclQualifiedStyle -> Constr)
-> (ImportDeclQualifiedStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c ImportDeclQualifiedStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ImportDeclQualifiedStyle))
-> ((forall b. Data b => b -> b)
    -> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> ImportDeclQualifiedStyle
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> ImportDeclQualifiedStyle
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle)
-> Data ImportDeclQualifiedStyle
ImportDeclQualifiedStyle -> Constr
ImportDeclQualifiedStyle -> DataType
(forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
$ctoConstr :: ImportDeclQualifiedStyle -> Constr
toConstr :: ImportDeclQualifiedStyle -> Constr
$cdataTypeOf :: ImportDeclQualifiedStyle -> DataType
dataTypeOf :: ImportDeclQualifiedStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
$cgmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
gmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
Data)

-- | Indicates whether a module name is referring to a boot interface (hs-boot
-- file) or regular module (hs file). We need to treat boot modules specially
-- when building compilation graphs, since they break cycles. Regular source
-- files and signature files are treated equivalently.
data IsBootInterface = NotBoot | IsBoot
    deriving (IsBootInterface -> IsBootInterface -> Bool
(IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> Eq IsBootInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IsBootInterface -> IsBootInterface -> Bool
== :: IsBootInterface -> IsBootInterface -> Bool
$c/= :: IsBootInterface -> IsBootInterface -> Bool
/= :: IsBootInterface -> IsBootInterface -> Bool
Eq, Eq IsBootInterface
Eq IsBootInterface =>
(IsBootInterface -> IsBootInterface -> Ordering)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> IsBootInterface)
-> (IsBootInterface -> IsBootInterface -> IsBootInterface)
-> Ord IsBootInterface
IsBootInterface -> IsBootInterface -> Bool
IsBootInterface -> IsBootInterface -> Ordering
IsBootInterface -> IsBootInterface -> IsBootInterface
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IsBootInterface -> IsBootInterface -> Ordering
compare :: IsBootInterface -> IsBootInterface -> Ordering
$c< :: IsBootInterface -> IsBootInterface -> Bool
< :: IsBootInterface -> IsBootInterface -> Bool
$c<= :: IsBootInterface -> IsBootInterface -> Bool
<= :: IsBootInterface -> IsBootInterface -> Bool
$c> :: IsBootInterface -> IsBootInterface -> Bool
> :: IsBootInterface -> IsBootInterface -> Bool
$c>= :: IsBootInterface -> IsBootInterface -> Bool
>= :: IsBootInterface -> IsBootInterface -> Bool
$cmax :: IsBootInterface -> IsBootInterface -> IsBootInterface
max :: IsBootInterface -> IsBootInterface -> IsBootInterface
$cmin :: IsBootInterface -> IsBootInterface -> IsBootInterface
min :: IsBootInterface -> IsBootInterface -> IsBootInterface
Ord, Int -> IsBootInterface -> ShowS
[IsBootInterface] -> ShowS
IsBootInterface -> String
(Int -> IsBootInterface -> ShowS)
-> (IsBootInterface -> String)
-> ([IsBootInterface] -> ShowS)
-> Show IsBootInterface
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IsBootInterface -> ShowS
showsPrec :: Int -> IsBootInterface -> ShowS
$cshow :: IsBootInterface -> String
show :: IsBootInterface -> String
$cshowList :: [IsBootInterface] -> ShowS
showList :: [IsBootInterface] -> ShowS
Show, Typeable IsBootInterface
Typeable IsBootInterface =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c IsBootInterface)
-> (IsBootInterface -> Constr)
-> (IsBootInterface -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c IsBootInterface))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c IsBootInterface))
-> ((forall b. Data b => b -> b)
    -> IsBootInterface -> IsBootInterface)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> IsBootInterface -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> IsBootInterface -> m IsBootInterface)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> IsBootInterface -> m IsBootInterface)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> IsBootInterface -> m IsBootInterface)
-> Data IsBootInterface
IsBootInterface -> Constr
IsBootInterface -> DataType
(forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
$ctoConstr :: IsBootInterface -> Constr
toConstr :: IsBootInterface -> Constr
$cdataTypeOf :: IsBootInterface -> DataType
dataTypeOf :: IsBootInterface -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
$cgmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
Data)

-- | Import Declaration
--
-- A single Haskell @import@ declaration.
data ImportDecl pass
  = ImportDecl {
      forall pass. ImportDecl pass -> XCImportDecl pass
ideclExt        :: XCImportDecl pass,
      forall pass. ImportDecl pass -> XRec pass ModuleName
ideclName       :: XRec pass ModuleName, -- ^ Module name.
      forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclPkgQual    :: ImportDeclPkgQual pass,  -- ^ Package qualifier.
      forall pass. ImportDecl pass -> IsBootInterface
ideclSource     :: IsBootInterface,      -- ^ IsBoot <=> {-\# SOURCE \#-} import
      forall pass. ImportDecl pass -> Bool
ideclSafe       :: Bool,          -- ^ True => safe import
      forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified  :: ImportDeclQualifiedStyle, -- ^ If/how the import is qualified.
      forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs         :: Maybe (XRec pass ModuleName),  -- ^ as Module
      forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList :: Maybe (ImportListInterpretation, XRec pass [LIE pass])
                                       -- ^ Explicit import list (EverythingBut => hiding, names)
    }
  | XImportDecl !(XXImportDecl pass)
     -- ^
     --  'GHC.Parser.Annotation.AnnKeywordId's
     --
     --  - 'GHC.Parser.Annotation.AnnImport'
     --
     --  - 'GHC.Parser.Annotation.AnnOpen', 'GHC.Parser.Annotation.AnnClose' for ideclSource
     --
     --  - 'GHC.Parser.Annotation.AnnSafe','GHC.Parser.Annotation.AnnQualified',
     --    'GHC.Parser.Annotation.AnnPackageName','GHC.Parser.Annotation.AnnAs',
     --    'GHC.Parser.Annotation.AnnVal'
     --
     --  - 'GHC.Parser.Annotation.AnnHiding','GHC.Parser.Annotation.AnnOpen',
     --    'GHC.Parser.Annotation.AnnClose' attached
     --     to location in ideclImportList

     -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation

-- | Whether the import list is exactly what to import, or whether `hiding` was
-- used, and therefore everything but what was listed should be imported
data ImportListInterpretation = Exactly | EverythingBut
    deriving (ImportListInterpretation -> ImportListInterpretation -> Bool
(ImportListInterpretation -> ImportListInterpretation -> Bool)
-> (ImportListInterpretation -> ImportListInterpretation -> Bool)
-> Eq ImportListInterpretation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportListInterpretation -> ImportListInterpretation -> Bool
== :: ImportListInterpretation -> ImportListInterpretation -> Bool
$c/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
Eq, Typeable ImportListInterpretation
Typeable ImportListInterpretation =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> ImportListInterpretation
 -> c ImportListInterpretation)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ImportListInterpretation)
-> (ImportListInterpretation -> Constr)
-> (ImportListInterpretation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c ImportListInterpretation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ImportListInterpretation))
-> ((forall b. Data b => b -> b)
    -> ImportListInterpretation -> ImportListInterpretation)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> ImportListInterpretation
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> ImportListInterpretation
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ImportListInterpretation -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> ImportListInterpretation -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ImportListInterpretation -> m ImportListInterpretation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ImportListInterpretation -> m ImportListInterpretation)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ImportListInterpretation -> m ImportListInterpretation)
-> Data ImportListInterpretation
ImportListInterpretation -> Constr
ImportListInterpretation -> DataType
(forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
$ctoConstr :: ImportListInterpretation -> Constr
toConstr :: ImportListInterpretation -> Constr
$cdataTypeOf :: ImportListInterpretation -> DataType
dataTypeOf :: ImportListInterpretation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
$cgmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
gmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
Data)

-- | Located Import or Export
type LIE pass = XRec pass (IE pass)
        -- ^ When in a list this may have
        --
        --  - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation

-- | Imported or exported entity.
data IE pass
  = IEVar       (XIEVar pass) (LIEWrappedName pass)
        -- ^ Imported or Exported Variable

  | IEThingAbs  (XIEThingAbs pass) (LIEWrappedName pass)
        -- ^ Imported or exported Thing with Absent list
        --
        -- The thing is a Class/Type (can't tell)
        --  - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnPattern',
        --             'GHC.Parser.Annotation.AnnType','GHC.Parser.Annotation.AnnVal'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
        -- See Note [Located RdrNames] in GHC.Hs.Expr
  | IEThingAll  (XIEThingAll pass) (LIEWrappedName pass)
        -- ^ Imported or exported Thing with All imported or exported
        --
        -- The thing is a Class/Type and the All refers to methods/constructors
        --
        -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen',
        --       'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose',
        --                                 'GHC.Parser.Annotation.AnnType'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
        -- See Note [Located RdrNames] in GHC.Hs.Expr

  | IEThingWith (XIEThingWith pass)
                (LIEWrappedName pass)
                IEWildcard
                [LIEWrappedName pass]
        -- ^ Imported or exported Thing With given imported or exported
        --
        -- The thing is a Class/Type and the imported or exported things are
        -- methods/constructors and record fields; see Note [IEThingWith]
        -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen',
        --                                   'GHC.Parser.Annotation.AnnClose',
        --                                   'GHC.Parser.Annotation.AnnComma',
        --                                   'GHC.Parser.Annotation.AnnType'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
  | IEModuleContents  (XIEModuleContents pass) (XRec pass ModuleName)
        -- ^ Imported or exported module contents
        --
        -- (Export Only)
        --
        -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnModule'

        -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
  | IEGroup             (XIEGroup pass) Int (LHsDoc pass) -- ^ Doc section heading
  | IEDoc               (XIEDoc pass) (LHsDoc pass)       -- ^ Some documentation
  | IEDocNamed          (XIEDocNamed pass) String    -- ^ Reference to named doc
  | XIE !(XXIE pass)

-- | Wildcard in an import or export sublist, like the @..@ in
-- @import Mod ( T(Mk1, Mk2, ..) )@.
data IEWildcard
  = NoIEWildcard   -- ^ no wildcard in this list
  | IEWildcard Int -- ^ wildcard after the given \# of items in this list
                   -- The @Int@ is in the range [0..n], where n is the length
                   -- of the list.
  deriving (IEWildcard -> IEWildcard -> Bool
(IEWildcard -> IEWildcard -> Bool)
-> (IEWildcard -> IEWildcard -> Bool) -> Eq IEWildcard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IEWildcard -> IEWildcard -> Bool
== :: IEWildcard -> IEWildcard -> Bool
$c/= :: IEWildcard -> IEWildcard -> Bool
/= :: IEWildcard -> IEWildcard -> Bool
Eq, Typeable IEWildcard
Typeable IEWildcard =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c IEWildcard)
-> (IEWildcard -> Constr)
-> (IEWildcard -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c IEWildcard))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c IEWildcard))
-> ((forall b. Data b => b -> b) -> IEWildcard -> IEWildcard)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r)
-> (forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> IEWildcard -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard)
-> Data IEWildcard
IEWildcard -> Constr
IEWildcard -> DataType
(forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
$ctoConstr :: IEWildcard -> Constr
toConstr :: IEWildcard -> Constr
$cdataTypeOf :: IEWildcard -> DataType
dataTypeOf :: IEWildcard -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
$cgmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
Data)

-- | A name in an import or export specification which may have
-- adornments. Used primarily for accurate pretty printing of
-- ParsedSource, and API Annotation placement. The
-- 'GHC.Parser.Annotation' is the location of the adornment in
-- the original source.
data IEWrappedName p
  = IEName    (XIEName p)    (LIdP p)  -- ^ no extra
  | IEPattern (XIEPattern p) (LIdP p)  -- ^ pattern X
  | IEType    (XIEType p)    (LIdP p)  -- ^ type (:+:)
  | XIEWrappedName !(XXIEWrappedName p)

-- | Located name with possible adornment
-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnType',
--         'GHC.Parser.Annotation.AnnPattern'
type LIEWrappedName p = XRec p (IEWrappedName p)
-- For details on above see Note [exact print annotations] in GHC.Parser.Annotation