Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type LImportDecl pass = Located (ImportDecl pass)
- data ImportDeclQualifiedStyle
- importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclSourceSrc :: SourceText
- ideclName :: Located ModuleName
- ideclPkgQual :: Maybe StringLiteral
- ideclSource :: Bool
- ideclSafe :: Bool
- ideclQualified :: ImportDeclQualifiedStyle
- ideclImplicit :: Bool
- ideclAs :: Maybe (Located ModuleName)
- ideclHiding :: Maybe (Bool, Located [LIE pass])
- | XImportDecl (XXImportDecl pass)
- = ImportDecl {
- simpleImportDecl :: ModuleName -> ImportDecl (GhcPass p)
- data IEWrappedName name
- 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)
- data IEWildcard
- ieName :: IE (GhcPass p) -> IdP (GhcPass p)
- ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)]
- ieWrappedName :: IEWrappedName name -> name
- lieWrappedName :: LIEWrappedName name -> name
- ieLWrappedName :: LIEWrappedName name -> Located name
- replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2
- replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
Documentation
type LImportDecl pass Source #
= Located (ImportDecl pass) | When in a list this may have |
Located Import Declaration
data ImportDeclQualifiedStyle Source #
If/how an import is qualified
.
QualifiedPre |
|
QualifiedPost |
|
NotQualified | Not qualified. |
Instances
importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle Source #
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool Source #
Convenience function to answer the question if an import decl. is qualified.
data ImportDecl pass Source #
Import Declaration
A single Haskell import
declaration.
ImportDecl | |
| |
XImportDecl (XXImportDecl pass) |
Instances
Data (ImportDecl GhcTc) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcTc -> c (ImportDecl GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) Source # toConstr :: ImportDecl GhcTc -> Constr Source # dataTypeOf :: ImportDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # | |
Data (ImportDecl GhcRn) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcRn -> c (ImportDecl GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) Source # toConstr :: ImportDecl GhcRn -> Constr Source # dataTypeOf :: ImportDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # | |
Data (ImportDecl GhcPs) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcPs -> c (ImportDecl GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) Source # toConstr :: ImportDecl GhcPs -> Constr Source # dataTypeOf :: ImportDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # | |
OutputableBndrId p => Outputable (ImportDecl (GhcPass p)) # | |
Defined in GHC.Hs.ImpExp |
simpleImportDecl :: ModuleName -> ImportDecl (GhcPass p) Source #
data IEWrappedName name Source #
A name in an import or export specification which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement.
Instances
Eq name => Eq (IEWrappedName name) # | |
Defined in GHC.Hs.ImpExp (==) :: IEWrappedName name -> IEWrappedName name -> Bool # (/=) :: IEWrappedName name -> IEWrappedName name -> Bool # | |
Data name => Data (IEWrappedName name) # | |
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName name -> c (IEWrappedName name) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName name) Source # toConstr :: IEWrappedName name -> Constr Source # dataTypeOf :: IEWrappedName name -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName name)) Source # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName name -> IEWrappedName name Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # | |
OutputableBndr name => OutputableBndr (IEWrappedName name) # | |
Defined in GHC.Hs.ImpExp pprBndr :: BindingSite -> IEWrappedName name -> SDoc Source # pprPrefixOcc :: IEWrappedName name -> SDoc Source # pprInfixOcc :: IEWrappedName name -> SDoc Source # bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int Source # | |
OutputableBndr name => Outputable (IEWrappedName name) # | |
Defined in GHC.Hs.ImpExp | |
HasOccName name => HasOccName (IEWrappedName name) # | |
Defined in GHC.Hs.ImpExp occName :: IEWrappedName name -> OccName Source # |
type LIEWrappedName name = Located (IEWrappedName name) Source #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern
Imported or exported entity.
IEVar (XIEVar pass) (LIEWrappedName (IdP pass)) | Imported or Exported Variable |
IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with All imported or exported The thing is a ClassType and the All refers to methodsconstructors |
IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP 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]
- |
IEModuleContents (XIEModuleContents pass) (Located ModuleName) | Imported or exported module contents (Export Only) |
IEGroup (XIEGroup pass) Int HsDocString | Doc section heading |
IEDoc (XIEDoc pass) HsDocString | Some documentation |
IEDocNamed (XIEDocNamed pass) String | Reference to named doc |
XIE (XXIE pass) |
Instances
Eq (IE GhcTc) # | |
Eq (IE GhcRn) # | |
Eq (IE GhcPs) # | |
Data (IE GhcTc) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcTc -> c (IE GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) Source # toConstr :: IE GhcTc -> Constr Source # dataTypeOf :: IE GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # | |
Data (IE GhcRn) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcRn -> c (IE GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) Source # toConstr :: IE GhcRn -> Constr Source # dataTypeOf :: IE GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # | |
Data (IE GhcPs) # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcPs -> c (IE GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) Source # toConstr :: IE GhcPs -> Constr Source # dataTypeOf :: IE GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # | |
OutputableBndrId p => Outputable (IE (GhcPass p)) # | |
data IEWildcard Source #
Imported or Exported Wildcard
Instances
Eq IEWildcard # | |
Defined in GHC.Hs.ImpExp (==) :: IEWildcard -> IEWildcard -> Bool # (/=) :: IEWildcard -> IEWildcard -> Bool # | |
Data IEWildcard # | |
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IEWildcard Source # toConstr :: IEWildcard -> Constr Source # dataTypeOf :: IEWildcard -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard) Source # gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source # |
ieWrappedName :: IEWrappedName name -> name Source #
lieWrappedName :: LIEWrappedName name -> name Source #
ieLWrappedName :: LIEWrappedName name -> Located name Source #
replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2 Source #
replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2 Source #
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc Source #