{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module GHC.Hs.ImpExp where
import GhcPrelude
import Module ( ModuleName )
import GHC.Hs.Doc ( HsDocString )
import OccName ( HasOccName(..), isTcOcc, isSymOcc )
import BasicTypes ( SourceText(..), StringLiteral(..), pprWithSourceText )
import FieldLabel ( FieldLbl(..) )
import Outputable
import FastString
import SrcLoc
import GHC.Hs.Extension
import Data.Data
import Data.Maybe
type LImportDecl pass = Located (ImportDecl pass)
data ImportDeclQualifiedStyle
= QualifiedPre
| QualifiedPost
| NotQualified
deriving (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
(ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> Eq ImportDeclQualifiedStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
Eq, Typeable ImportDeclQualifiedStyle
DataType
Constr
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 -> DataType
ImportDeclQualifiedStyle -> Constr
(forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cNotQualified :: Constr
$cQualifiedPost :: Constr
$cQualifiedPre :: Constr
$tImportDeclQualifiedStyle :: DataType
gmapMo :: (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
gmapMp :: (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
gmapM :: (forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapQi :: Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
gmapQ :: (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
$cgmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
dataTypeOf :: ImportDeclQualifiedStyle -> DataType
$cdataTypeOf :: ImportDeclQualifiedStyle -> DataType
toConstr :: ImportDeclQualifiedStyle -> Constr
$ctoConstr :: ImportDeclQualifiedStyle -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
$cp1Data :: Typeable ImportDeclQualifiedStyle
Data)
importDeclQualifiedStyle :: Maybe (Located a)
-> Maybe (Located a)
-> ImportDeclQualifiedStyle
importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle
importDeclQualifiedStyle Maybe (Located a)
mPre Maybe (Located a)
mPost =
if Maybe (Located a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Located a)
mPre then ImportDeclQualifiedStyle
QualifiedPre
else if Maybe (Located a) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Located a)
mPost then ImportDeclQualifiedStyle
QualifiedPost else ImportDeclQualifiedStyle
NotQualified
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
isImportDeclQualified ImportDeclQualifiedStyle
NotQualified = Bool
False
isImportDeclQualified ImportDeclQualifiedStyle
_ = Bool
True
data ImportDecl pass
= ImportDecl {
ImportDecl pass -> XCImportDecl pass
ideclExt :: XCImportDecl pass,
ImportDecl pass -> SourceText
ideclSourceSrc :: SourceText,
ImportDecl pass -> Located ModuleName
ideclName :: Located ModuleName,
ImportDecl pass -> Maybe StringLiteral
ideclPkgQual :: Maybe StringLiteral,
ImportDecl pass -> Bool
ideclSource :: Bool,
ImportDecl pass -> Bool
ideclSafe :: Bool,
ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified :: ImportDeclQualifiedStyle,
ImportDecl pass -> Bool
ideclImplicit :: Bool,
ImportDecl pass -> Maybe (Located ModuleName)
ideclAs :: Maybe (Located ModuleName),
ImportDecl pass -> Maybe (Bool, Located [LIE pass])
ideclHiding :: Maybe (Bool, Located [LIE pass])
}
| XImportDecl (XXImportDecl pass)
type instance XCImportDecl (GhcPass _) = NoExtField
type instance XXImportDecl (GhcPass _) = NoExtCon
simpleImportDecl :: ModuleName -> ImportDecl (GhcPass p)
simpleImportDecl :: ModuleName -> ImportDecl (GhcPass p)
simpleImportDecl ModuleName
mn = ImportDecl :: forall pass.
XCImportDecl pass
-> SourceText
-> Located ModuleName
-> Maybe StringLiteral
-> Bool
-> Bool
-> ImportDeclQualifiedStyle
-> Bool
-> Maybe (Located ModuleName)
-> Maybe (Bool, Located [LIE pass])
-> ImportDecl pass
ImportDecl {
ideclExt :: XCImportDecl (GhcPass p)
ideclExt = XCImportDecl (GhcPass p)
NoExtField
noExtField,
ideclSourceSrc :: SourceText
ideclSourceSrc = SourceText
NoSourceText,
ideclName :: Located ModuleName
ideclName = SrcSpanLess (Located ModuleName) -> Located ModuleName
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc ModuleName
SrcSpanLess (Located ModuleName)
mn,
ideclPkgQual :: Maybe StringLiteral
ideclPkgQual = Maybe StringLiteral
forall a. Maybe a
Nothing,
ideclSource :: Bool
ideclSource = Bool
False,
ideclSafe :: Bool
ideclSafe = Bool
False,
ideclImplicit :: Bool
ideclImplicit = Bool
False,
ideclQualified :: ImportDeclQualifiedStyle
ideclQualified = ImportDeclQualifiedStyle
NotQualified,
ideclAs :: Maybe (Located ModuleName)
ideclAs = Maybe (Located ModuleName)
forall a. Maybe a
Nothing,
ideclHiding :: Maybe (Bool, Located [LIE (GhcPass p)])
ideclHiding = Maybe (Bool, Located [LIE (GhcPass p)])
forall a. Maybe a
Nothing
}
instance OutputableBndrId p
=> Outputable (ImportDecl (GhcPass p)) where
ppr :: ImportDecl (GhcPass p) -> SDoc
ppr (ImportDecl { ideclSourceSrc :: forall pass. ImportDecl pass -> SourceText
ideclSourceSrc = SourceText
mSrcText, ideclName :: forall pass. ImportDecl pass -> Located ModuleName
ideclName = Located ModuleName
mod'
, ideclPkgQual :: forall pass. ImportDecl pass -> Maybe StringLiteral
ideclPkgQual = Maybe StringLiteral
pkg
, ideclSource :: forall pass. ImportDecl pass -> Bool
ideclSource = Bool
from, ideclSafe :: forall pass. ImportDecl pass -> Bool
ideclSafe = Bool
safe
, ideclQualified :: forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified = ImportDeclQualifiedStyle
qual, ideclImplicit :: forall pass. ImportDecl pass -> Bool
ideclImplicit = Bool
implicit
, ideclAs :: forall pass. ImportDecl pass -> Maybe (Located ModuleName)
ideclAs = Maybe (Located ModuleName)
as, ideclHiding :: forall pass. ImportDecl pass -> Maybe (Bool, Located [LIE pass])
ideclHiding = Maybe (Bool, Located [LIE (GhcPass p)])
spec })
= SDoc -> Int -> SDoc -> SDoc
hang ([SDoc] -> SDoc
hsep [String -> SDoc
text String
"import", Bool -> SDoc
ppr_imp Bool
from, Bool -> SDoc
pp_implicit Bool
implicit, Bool -> SDoc
pp_safe Bool
safe,
ImportDeclQualifiedStyle -> Bool -> SDoc
pp_qual ImportDeclQualifiedStyle
qual Bool
False, Maybe StringLiteral -> SDoc
pp_pkg Maybe StringLiteral
pkg, Located ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr Located ModuleName
mod', ImportDeclQualifiedStyle -> Bool -> SDoc
pp_qual ImportDeclQualifiedStyle
qual Bool
True, Maybe (Located ModuleName) -> SDoc
forall a. Outputable a => Maybe a -> SDoc
pp_as Maybe (Located ModuleName)
as])
Int
4 (Maybe (Bool, Located [LIE (GhcPass p)]) -> SDoc
forall a l. Outputable a => Maybe (Bool, GenLocated l [a]) -> SDoc
pp_spec Maybe (Bool, Located [LIE (GhcPass p)])
spec)
where
pp_implicit :: Bool -> SDoc
pp_implicit Bool
False = SDoc
empty
pp_implicit Bool
True = PtrString -> SDoc
ptext (String -> PtrString
sLit (String
"(implicit)"))
pp_pkg :: Maybe StringLiteral -> SDoc
pp_pkg Maybe StringLiteral
Nothing = SDoc
empty
pp_pkg (Just (StringLiteral SourceText
st FastString
p))
= SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
st (SDoc -> SDoc
doubleQuotes (FastString -> SDoc
ftext FastString
p))
pp_qual :: ImportDeclQualifiedStyle -> Bool -> SDoc
pp_qual ImportDeclQualifiedStyle
QualifiedPre Bool
False = String -> SDoc
text String
"qualified"
pp_qual ImportDeclQualifiedStyle
QualifiedPost Bool
True = String -> SDoc
text String
"qualified"
pp_qual ImportDeclQualifiedStyle
QualifiedPre Bool
True = SDoc
empty
pp_qual ImportDeclQualifiedStyle
QualifiedPost Bool
False = SDoc
empty
pp_qual ImportDeclQualifiedStyle
NotQualified Bool
_ = SDoc
empty
pp_safe :: Bool -> SDoc
pp_safe Bool
False = SDoc
empty
pp_safe Bool
True = String -> SDoc
text String
"safe"
pp_as :: Maybe a -> SDoc
pp_as Maybe a
Nothing = SDoc
empty
pp_as (Just a
a) = String -> SDoc
text String
"as" SDoc -> SDoc -> SDoc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
a
ppr_imp :: Bool -> SDoc
ppr_imp Bool
True = case SourceText
mSrcText of
SourceText
NoSourceText -> String -> SDoc
text String
"{-# SOURCE #-}"
SourceText String
src -> String -> SDoc
text String
src SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"#-}"
ppr_imp Bool
False = SDoc
empty
pp_spec :: Maybe (Bool, GenLocated l [a]) -> SDoc
pp_spec Maybe (Bool, GenLocated l [a])
Nothing = SDoc
empty
pp_spec (Just (Bool
False, (L l
_ [a]
ies))) = [a] -> SDoc
forall a. Outputable a => [a] -> SDoc
ppr_ies [a]
ies
pp_spec (Just (Bool
True, (L l
_ [a]
ies))) = String -> SDoc
text String
"hiding" SDoc -> SDoc -> SDoc
<+> [a] -> SDoc
forall a. Outputable a => [a] -> SDoc
ppr_ies [a]
ies
ppr_ies :: [a] -> SDoc
ppr_ies [] = String -> SDoc
text String
"()"
ppr_ies [a]
ies = Char -> SDoc
char Char
'(' SDoc -> SDoc -> SDoc
<+> [a] -> SDoc
forall a. Outputable a => [a] -> SDoc
interpp'SP [a]
ies SDoc -> SDoc -> SDoc
<+> Char -> SDoc
char Char
')'
ppr (XImportDecl XXImportDecl (GhcPass p)
x) = NoExtCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr XXImportDecl (GhcPass p)
NoExtCon
x
data IEWrappedName name
= IEName (Located name)
| IEPattern (Located name)
| IEType (Located name)
deriving (IEWrappedName name -> IEWrappedName name -> Bool
(IEWrappedName name -> IEWrappedName name -> Bool)
-> (IEWrappedName name -> IEWrappedName name -> Bool)
-> Eq (IEWrappedName name)
forall name.
Eq name =>
IEWrappedName name -> IEWrappedName name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IEWrappedName name -> IEWrappedName name -> Bool
$c/= :: forall name.
Eq name =>
IEWrappedName name -> IEWrappedName name -> Bool
== :: IEWrappedName name -> IEWrappedName name -> Bool
$c== :: forall name.
Eq name =>
IEWrappedName name -> IEWrappedName name -> Bool
Eq,Typeable (IEWrappedName name)
DataType
Constr
Typeable (IEWrappedName name)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name))
-> (IEWrappedName name -> Constr)
-> (IEWrappedName name -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (IEWrappedName name)))
-> ((forall b. Data b => b -> b)
-> IEWrappedName name -> IEWrappedName name)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r)
-> (forall u.
(forall d. Data d => d -> u) -> IEWrappedName name -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name))
-> Data (IEWrappedName name)
IEWrappedName name -> DataType
IEWrappedName name -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name))
(forall b. Data b => b -> b)
-> IEWrappedName name -> IEWrappedName name
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name)
forall name. Data name => Typeable (IEWrappedName name)
forall name. Data name => IEWrappedName name -> DataType
forall name. Data name => IEWrappedName name -> Constr
forall name.
Data name =>
(forall b. Data b => b -> b)
-> IEWrappedName name -> IEWrappedName name
forall name u.
Data name =>
Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u
forall name u.
Data name =>
(forall d. Data d => d -> u) -> IEWrappedName name -> [u]
forall name r r'.
Data name =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
forall name r r'.
Data name =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
forall name (m :: * -> *).
(Data name, Monad m) =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
forall name (m :: * -> *).
(Data name, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
forall name (c :: * -> *).
Data name =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name)
forall name (c :: * -> *).
Data name =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name)
forall name (t :: * -> *) (c :: * -> *).
(Data name, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name))
forall name (t :: * -> * -> *) (c :: * -> *).
(Data name, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (IEWrappedName name))
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) -> IEWrappedName name -> u
forall u. (forall d. Data d => d -> u) -> IEWrappedName name -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (IEWrappedName name))
$cIEType :: Constr
$cIEPattern :: Constr
$cIEName :: Constr
$tIEWrappedName :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
$cgmapMo :: forall name (m :: * -> *).
(Data name, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
gmapMp :: (forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
$cgmapMp :: forall name (m :: * -> *).
(Data name, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
gmapM :: (forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
$cgmapM :: forall name (m :: * -> *).
(Data name, Monad m) =>
(forall d. Data d => d -> m d)
-> IEWrappedName name -> m (IEWrappedName name)
gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u
$cgmapQi :: forall name u.
Data name =>
Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u
gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u]
$cgmapQ :: forall name u.
Data name =>
(forall d. Data d => d -> u) -> IEWrappedName name -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
$cgmapQr :: forall name r r'.
Data name =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
$cgmapQl :: forall name r r'.
Data name =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r
gmapT :: (forall b. Data b => b -> b)
-> IEWrappedName name -> IEWrappedName name
$cgmapT :: forall name.
Data name =>
(forall b. Data b => b -> b)
-> IEWrappedName name -> IEWrappedName name
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (IEWrappedName name))
$cdataCast2 :: forall name (t :: * -> * -> *) (c :: * -> *).
(Data name, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (IEWrappedName name))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name))
$cdataCast1 :: forall name (t :: * -> *) (c :: * -> *).
(Data name, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name))
dataTypeOf :: IEWrappedName name -> DataType
$cdataTypeOf :: forall name. Data name => IEWrappedName name -> DataType
toConstr :: IEWrappedName name -> Constr
$ctoConstr :: forall name. Data name => IEWrappedName name -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name)
$cgunfold :: forall name (c :: * -> *).
Data name =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IEWrappedName name)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name)
$cgfoldl :: forall name (c :: * -> *).
Data name =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> IEWrappedName name
-> c (IEWrappedName name)
$cp1Data :: forall name. Data name => Typeable (IEWrappedName name)
Data)
type LIEWrappedName name = Located (IEWrappedName name)
type LIE pass = Located (IE pass)
data IE pass
= IEVar (XIEVar pass) (LIEWrappedName (IdP pass))
| IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass))
| IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))
| IEThingWith (XIEThingWith pass)
(LIEWrappedName (IdP pass))
IEWildcard
[LIEWrappedName (IdP pass)]
[Located (FieldLbl (IdP pass))]
| IEModuleContents (XIEModuleContents pass) (Located ModuleName)
| IEGroup (XIEGroup pass) Int HsDocString
| IEDoc (XIEDoc pass) HsDocString
| IEDocNamed (XIEDocNamed pass) String
| XIE (XXIE pass)
type instance XIEVar (GhcPass _) = NoExtField
type instance XIEThingAbs (GhcPass _) = NoExtField
type instance XIEThingAll (GhcPass _) = NoExtField
type instance XIEThingWith (GhcPass _) = NoExtField
type instance XIEModuleContents (GhcPass _) = NoExtField
type instance XIEGroup (GhcPass _) = NoExtField
type instance XIEDoc (GhcPass _) = NoExtField
type instance XIEDocNamed (GhcPass _) = NoExtField
type instance XXIE (GhcPass _) = NoExtCon
data IEWildcard = NoIEWildcard | IEWildcard Int deriving (IEWildcard -> IEWildcard -> Bool
(IEWildcard -> IEWildcard -> Bool)
-> (IEWildcard -> IEWildcard -> Bool) -> Eq IEWildcard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IEWildcard -> IEWildcard -> Bool
$c/= :: IEWildcard -> IEWildcard -> Bool
== :: IEWildcard -> IEWildcard -> Bool
$c== :: IEWildcard -> IEWildcard -> Bool
Eq, Typeable IEWildcard
DataType
Constr
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 -> DataType
IEWildcard -> Constr
(forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cIEWildcard :: Constr
$cNoIEWildcard :: Constr
$tIEWildcard :: DataType
gmapMo :: (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
gmapMp :: (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
gmapM :: (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
$cgmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
dataTypeOf :: IEWildcard -> DataType
$cdataTypeOf :: IEWildcard -> DataType
toConstr :: IEWildcard -> Constr
$ctoConstr :: IEWildcard -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
$cp1Data :: Typeable IEWildcard
Data)
ieName :: IE (GhcPass p) -> IdP (GhcPass p)
ieName :: IE (GhcPass p) -> IdP (GhcPass p)
ieName (IEVar XIEVar (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n)) = IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n
ieName (IEThingAbs XIEThingAbs (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n)) = IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n
ieName (IEThingWith XIEThingWith (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n) IEWildcard
_ [GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))]
_ [Located (FieldLbl (IdP (GhcPass p)))]
_) = IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n
ieName (IEThingAll XIEThingAll (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n)) = IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n
ieName IE (GhcPass p)
_ = String -> IdP (GhcPass p)
forall a. String -> a
panic String
"ieName failed pattern match!"
ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)]
ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)]
ieNames (IEVar XIEVar (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n) ) = [IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n]
ieNames (IEThingAbs XIEThingAbs (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n) ) = [IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n]
ieNames (IEThingAll XIEThingAll (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n) ) = [IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n]
ieNames (IEThingWith XIEThingWith (GhcPass p)
_ (L SrcSpan
_ IEWrappedName (IdP (GhcPass p))
n) IEWildcard
_ [GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))]
ns [Located (FieldLbl (IdP (GhcPass p)))]
_) = IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName (IdP (GhcPass p))
n
IdP (GhcPass p) -> [IdP (GhcPass p)] -> [IdP (GhcPass p)]
forall a. a -> [a] -> [a]
: (GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))
-> IdP (GhcPass p))
-> [GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))]
-> [IdP (GhcPass p)]
forall a b. (a -> b) -> [a] -> [b]
map (IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p)
forall name. IEWrappedName name -> name
ieWrappedName (IEWrappedName (IdP (GhcPass p)) -> IdP (GhcPass p))
-> (GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))
-> IEWrappedName (IdP (GhcPass p)))
-> GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))
-> IdP (GhcPass p)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))
-> IEWrappedName (IdP (GhcPass p))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [GenLocated SrcSpan (IEWrappedName (IdP (GhcPass p)))]
ns
ieNames (IEModuleContents {}) = []
ieNames (IEGroup {}) = []
ieNames (IEDoc {}) = []
ieNames (IEDocNamed {}) = []
ieNames (XIE XXIE (GhcPass p)
nec) = NoExtCon -> [IdP (GhcPass p)]
forall a. NoExtCon -> a
noExtCon XXIE (GhcPass p)
NoExtCon
nec
ieWrappedName :: IEWrappedName name -> name
ieWrappedName :: IEWrappedName name -> name
ieWrappedName (IEName (L SrcSpan
_ name
n)) = name
n
ieWrappedName (IEPattern (L SrcSpan
_ name
n)) = name
n
ieWrappedName (IEType (L SrcSpan
_ name
n)) = name
n
lieWrappedName :: LIEWrappedName name -> name
lieWrappedName :: LIEWrappedName name -> name
lieWrappedName (L SrcSpan
_ IEWrappedName name
n) = IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
n
ieLWrappedName :: LIEWrappedName name -> Located name
ieLWrappedName :: LIEWrappedName name -> Located name
ieLWrappedName (L SrcSpan
l IEWrappedName name
n) = SrcSpan -> name -> Located name
forall l e. l -> e -> GenLocated l e
L SrcSpan
l (IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
n)
replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2
replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2
replaceWrappedName (IEName (L SrcSpan
l name1
_)) name2
n = Located name2 -> IEWrappedName name2
forall name. Located name -> IEWrappedName name
IEName (SrcSpan -> name2 -> Located name2
forall l e. l -> e -> GenLocated l e
L SrcSpan
l name2
n)
replaceWrappedName (IEPattern (L SrcSpan
l name1
_)) name2
n = Located name2 -> IEWrappedName name2
forall name. Located name -> IEWrappedName name
IEPattern (SrcSpan -> name2 -> Located name2
forall l e. l -> e -> GenLocated l e
L SrcSpan
l name2
n)
replaceWrappedName (IEType (L SrcSpan
l name1
_)) name2
n = Located name2 -> IEWrappedName name2
forall name. Located name -> IEWrappedName name
IEType (SrcSpan -> name2 -> Located name2
forall l e. l -> e -> GenLocated l e
L SrcSpan
l name2
n)
replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2
replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2
replaceLWrappedName (L SrcSpan
l IEWrappedName name1
n) name2
n' = SrcSpan -> IEWrappedName name2 -> LIEWrappedName name2
forall l e. l -> e -> GenLocated l e
L SrcSpan
l (IEWrappedName name1 -> name2 -> IEWrappedName name2
forall name1 name2.
IEWrappedName name1 -> name2 -> IEWrappedName name2
replaceWrappedName IEWrappedName name1
n name2
n')
instance OutputableBndrId p => Outputable (IE (GhcPass p)) where
ppr :: IE (GhcPass p) -> SDoc
ppr (IEVar XIEVar (GhcPass p)
_ LIEWrappedName (IdP (GhcPass p))
var) = IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LIEWrappedName (IdP (GhcPass p))
-> SrcSpanLess (LIEWrappedName (IdP (GhcPass p)))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIEWrappedName (IdP (GhcPass p))
var)
ppr (IEThingAbs XIEThingAbs (GhcPass p)
_ LIEWrappedName (IdP (GhcPass p))
thing) = IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LIEWrappedName (IdP (GhcPass p))
-> SrcSpanLess (LIEWrappedName (IdP (GhcPass p)))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIEWrappedName (IdP (GhcPass p))
thing)
ppr (IEThingAll XIEThingAll (GhcPass p)
_ LIEWrappedName (IdP (GhcPass p))
thing) = [SDoc] -> SDoc
hcat [IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LIEWrappedName (IdP (GhcPass p))
-> SrcSpanLess (LIEWrappedName (IdP (GhcPass p)))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIEWrappedName (IdP (GhcPass p))
thing), String -> SDoc
text String
"(..)"]
ppr (IEThingWith XIEThingWith (GhcPass p)
_ LIEWrappedName (IdP (GhcPass p))
thing IEWildcard
wc [LIEWrappedName (IdP (GhcPass p))]
withs [Located (FieldLbl (IdP (GhcPass p)))]
flds)
= IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LIEWrappedName (IdP (GhcPass p))
-> SrcSpanLess (LIEWrappedName (IdP (GhcPass p)))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIEWrappedName (IdP (GhcPass p))
thing) SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma
([SDoc]
ppWiths [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++
(Located (FieldLbl (IdP (GhcPass p))) -> SDoc)
-> [Located (FieldLbl (IdP (GhcPass p)))] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (FastString -> SDoc
forall a. Outputable a => a -> SDoc
ppr (FastString -> SDoc)
-> (Located (FieldLbl (IdP (GhcPass p))) -> FastString)
-> Located (FieldLbl (IdP (GhcPass p)))
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLbl (IdP (GhcPass p)) -> FastString
forall a. FieldLbl a -> FastString
flLabel (FieldLbl (IdP (GhcPass p)) -> FastString)
-> (Located (FieldLbl (IdP (GhcPass p)))
-> FieldLbl (IdP (GhcPass p)))
-> Located (FieldLbl (IdP (GhcPass p)))
-> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located (FieldLbl (IdP (GhcPass p))) -> FieldLbl (IdP (GhcPass p))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [Located (FieldLbl (IdP (GhcPass p)))]
flds)))
where
ppWiths :: [SDoc]
ppWiths =
case IEWildcard
wc of
IEWildcard
NoIEWildcard ->
(LIEWrappedName (IdP (GhcPass p)) -> SDoc)
-> [LIEWrappedName (IdP (GhcPass p))] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (IEWrappedName (IdP (GhcPass p)) -> SDoc)
-> (LIEWrappedName (IdP (GhcPass p))
-> IEWrappedName (IdP (GhcPass p)))
-> LIEWrappedName (IdP (GhcPass p))
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LIEWrappedName (IdP (GhcPass p)) -> IEWrappedName (IdP (GhcPass p))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [LIEWrappedName (IdP (GhcPass p))]
withs
IEWildcard Int
pos ->
let ([SDoc]
bs, [SDoc]
as) = Int -> [SDoc] -> ([SDoc], [SDoc])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
pos ((LIEWrappedName (IdP (GhcPass p)) -> SDoc)
-> [LIEWrappedName (IdP (GhcPass p))] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (IEWrappedName (IdP (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (IEWrappedName (IdP (GhcPass p)) -> SDoc)
-> (LIEWrappedName (IdP (GhcPass p))
-> IEWrappedName (IdP (GhcPass p)))
-> LIEWrappedName (IdP (GhcPass p))
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LIEWrappedName (IdP (GhcPass p)) -> IEWrappedName (IdP (GhcPass p))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [LIEWrappedName (IdP (GhcPass p))]
withs)
in [SDoc]
bs [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [String -> SDoc
text String
".."] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [SDoc]
as
ppr (IEModuleContents XIEModuleContents (GhcPass p)
_ Located ModuleName
mod')
= String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> Located ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr Located ModuleName
mod'
ppr (IEGroup XIEGroup (GhcPass p)
_ Int
n HsDocString
_) = String -> SDoc
text (String
"<IEGroup: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">")
ppr (IEDoc XIEDoc (GhcPass p)
_ HsDocString
doc) = HsDocString -> SDoc
forall a. Outputable a => a -> SDoc
ppr HsDocString
doc
ppr (IEDocNamed XIEDocNamed (GhcPass p)
_ String
string) = String -> SDoc
text (String
"<IEDocNamed: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
string String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">")
ppr (XIE XXIE (GhcPass p)
x) = NoExtCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr XXIE (GhcPass p)
NoExtCon
x
instance (HasOccName name) => HasOccName (IEWrappedName name) where
occName :: IEWrappedName name -> OccName
occName IEWrappedName name
w = name -> OccName
forall name. HasOccName name => name -> OccName
occName (IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
w)
instance (OutputableBndr name) => OutputableBndr (IEWrappedName name) where
pprBndr :: BindingSite -> IEWrappedName name -> SDoc
pprBndr BindingSite
bs IEWrappedName name
w = BindingSite -> name -> SDoc
forall a. OutputableBndr a => BindingSite -> a -> SDoc
pprBndr BindingSite
bs (IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
w)
pprPrefixOcc :: IEWrappedName name -> SDoc
pprPrefixOcc IEWrappedName name
w = name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc (IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
w)
pprInfixOcc :: IEWrappedName name -> SDoc
pprInfixOcc IEWrappedName name
w = name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprInfixOcc (IEWrappedName name -> name
forall name. IEWrappedName name -> name
ieWrappedName IEWrappedName name
w)
instance (OutputableBndr name) => Outputable (IEWrappedName name) where
ppr :: IEWrappedName name -> SDoc
ppr (IEName Located name
n) = name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc (Located name -> SrcSpanLess (Located name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located name
n)
ppr (IEPattern Located name
n) = String -> SDoc
text String
"pattern" SDoc -> SDoc -> SDoc
<+> name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc (Located name -> SrcSpanLess (Located name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located name
n)
ppr (IEType Located name
n) = String -> SDoc
text String
"type" SDoc -> SDoc -> SDoc
<+> name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc (Located name -> SrcSpanLess (Located name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located name
n)
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
pprImpExp :: name -> SDoc
pprImpExp name
name = SDoc
type_pref SDoc -> SDoc -> SDoc
<+> name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc name
name
where
occ :: OccName
occ = name -> OccName
forall name. HasOccName name => name -> OccName
occName name
name
type_pref :: SDoc
type_pref | OccName -> Bool
isTcOcc OccName
occ Bool -> Bool -> Bool
&& OccName -> Bool
isSymOcc OccName
occ = String -> SDoc
text String
"type"
| Bool
otherwise = SDoc
empty