Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type LImportDecl pass = XRec pass (ImportDecl pass)
- data ImportDeclQualifiedStyle
- data IsBootInterface
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclName :: XRec pass ModuleName
- ideclPkgQual :: ImportDeclPkgQual pass
- ideclSource :: IsBootInterface
- ideclSafe :: Bool
- ideclQualified :: ImportDeclQualifiedStyle
- ideclAs :: Maybe (XRec pass ModuleName)
- ideclImportList :: Maybe (ImportListInterpretation, XRec pass [LIE pass])
- | XImportDecl !(XXImportDecl pass)
- = ImportDecl {
- data ImportListInterpretation
- type LIE pass = XRec pass (IE pass)
- type ExportDoc pass = LHsDoc pass
- data IE pass
- = IEVar (XIEVar pass) (LIEWrappedName pass) (Maybe (ExportDoc pass))
- | IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass) (Maybe (ExportDoc pass))
- | IEThingAll (XIEThingAll pass) (LIEWrappedName pass) (Maybe (ExportDoc pass))
- | IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard [LIEWrappedName pass] (Maybe (ExportDoc pass))
- | IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)
- | IEGroup (XIEGroup pass) Int (LHsDoc pass)
- | IEDoc (XIEDoc pass) (LHsDoc pass)
- | IEDocNamed (XIEDocNamed pass) String
- | XIE !(XXIE pass)
- data IEWildcard
- data IEWrappedName p
- = IEName (XIEName p) (LIdP p)
- | IEDefault (XIEDefault p) (LIdP p)
- | IEPattern (XIEPattern p) (LIdP p)
- | IEType (XIEType p) (LIdP p)
- | XIEWrappedName !(XXIEWrappedName p)
- type LIEWrappedName p = XRec p (IEWrappedName p)
Documentation
type LImportDecl pass = XRec pass (ImportDecl pass) Source #
Located Import Declaration
data ImportDeclQualifiedStyle Source #
If/how an import is qualified
.
QualifiedPre |
|
QualifiedPost |
|
NotQualified | Not qualified. |
Instances
data IsBootInterface Source #
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.
Instances
data ImportDecl pass Source #
Import Declaration
A single Haskell import
declaration.
ImportDecl | |
| |
XImportDecl !(XXImportDecl pass) |
Instances
(OutputableBndrId p, Outputable (Anno (IE (GhcPass p))), Outputable (ImportDeclPkgQual (GhcPass p))) => Outputable (ImportDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
Data (ImportDecl GhcPs) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) # toConstr :: ImportDecl GhcPs -> Constr # dataTypeOf :: ImportDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # | |
Data (ImportDecl GhcRn) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) # toConstr :: ImportDecl GhcRn -> Constr # dataTypeOf :: ImportDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # | |
Data (ImportDecl GhcTc) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) # toConstr :: ImportDecl GhcTc -> Constr # dataTypeOf :: ImportDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # | |
type Anno (ImportDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp |
data ImportListInterpretation Source #
Whether the import list is exactly what to import, or whether hiding
was
used, and therefore everything but what was listed should be imported
Instances
Imported or exported entity.
IEVar (XIEVar pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) | Imported or exported variable module Mod ( test ) import Mod ( test ) |
IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) | Imported or exported Thing with absent subordinate list The thing is a Class/Type (can't tell) module Mod ( Test ) import Mod ( Test ) |
IEThingAll (XIEThingAll pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) | Imported or exported thing with wildcard subordinate list (e.g. The thing is a Class/Type and the All refers to methods/constructors module Mod ( Test(..) ) import Mod ( Test(..) ) |
IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard [LIEWrappedName pass] (Maybe (ExportDoc pass)) | Imported or exported thing with explicit subordinate list. The thing is a Class/Type (can't tell) and the imported or exported things are its children. module Mod ( Test(f, g) ) import Mod ( Test(f, g) ) |
IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName) | Export of entire module. Can only occur in export list. module Mod ( module Mod2 ) |
IEGroup (XIEGroup pass) Int (LHsDoc pass) | A Haddock section in an export list. module Mod ( -- * Section heading ... ) |
IEDoc (XIEDoc pass) (LHsDoc pass) | A bit of unnamed documentation. module Mod ( -- | Documentation ... ) |
IEDocNamed (XIEDocNamed pass) String | A reference to a named documentation chunk. module Mod ( -- $chunkName ... ) |
XIE !(XXIE pass) |
Instances
OutputableBndrId p => Outputable (IE (GhcPass p)) Source # | |
Data (IE GhcPs) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) # toConstr :: IE GhcPs -> Constr # dataTypeOf :: IE GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # | |
Data (IE GhcRn) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) # toConstr :: IE GhcRn -> Constr # dataTypeOf :: IE GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # | |
Data (IE GhcTc) Source # | |
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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) # toConstr :: IE GhcTc -> Constr # dataTypeOf :: IE GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # | |
Eq (IE GhcPs) Source # | |
Eq (IE GhcRn) Source # | |
Eq (IE GhcTc) Source # | |
type Anno (LocatedA (IE (GhcPass p))) Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno (IE (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno [LocatedA (IE (GhcPass p))] Source # | |
Defined in GHC.Hs.ImpExp |
data IEWildcard Source #
Wildcard in an import or export sublist, like the ..
in
import Mod ( T(Mk1, Mk2, ..) )
.
NoIEWildcard | no wildcard in this list |
IEWildcard Int | wildcard after the given # of items in this list
The |
Instances
Data IEWildcard Source # | |
Defined in Language.Haskell.Syntax.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IEWildcard # toConstr :: IEWildcard -> Constr # dataTypeOf :: IEWildcard -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard) # gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard # gmapQl :: (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 # gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # | |
Eq IEWildcard Source # | |
Defined in Language.Haskell.Syntax.ImpExp (==) :: IEWildcard -> IEWildcard -> Bool # (/=) :: IEWildcard -> IEWildcard -> Bool # |
data IEWrappedName p 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.
IEName (XIEName p) (LIdP p) | unadorned name, e.g |
IEDefault (XIEDefault p) (LIdP p) |
|
IEPattern (XIEPattern p) (LIdP p) | pattern X exactprint: the location of |
IEType (XIEType p) (LIdP p) | type (:+:) exactprint: the location of |
XIEWrappedName !(XXIEWrappedName p) |
Instances
type LIEWrappedName p = XRec p (IEWrappedName p) Source #
Located name with possible adornment