Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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)
- data IE pass
- = IEVar (XIEVar pass) (LIEWrappedName pass)
- | IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass)
- | IEThingAll (XIEThingAll pass) (LIEWrappedName pass)
- | IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard [LIEWrappedName 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)
- | IEPattern (XIEPattern p) (LIdP p)
- | IEType (XIEType p) (LIdP p)
- | XIEWrappedName !(XXIEWrappedName p)
- type LIEWrappedName p = XRec p (IEWrappedName p)
Documentation
type LImportDecl pass Source #
= XRec pass (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
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
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) 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 # | |
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) 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 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) 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 # | |
(OutputableBndrId p, Outputable (Anno (IE (GhcPass p))), Outputable (ImportDeclPkgQual (GhcPass p))) => Outputable (ImportDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
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) | 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)
- |
IEThingAll (XIEThingAll pass) (LIEWrappedName 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 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]
- |
IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName) | Imported or exported module contents (Export Only) |
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) |
Instances
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) 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 # | |
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) 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 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) 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 # | |
OutputableBndrId p => Outputable (IE (GhcPass p)) Source # | |
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 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 # | |
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. The
Annotation
is the location of the adornment in
the original source.
IEName (XIEName p) (LIdP p) | no extra |
IEPattern (XIEPattern p) (LIdP p) | pattern X |
IEType (XIEType p) (LIdP p) | type (:+:) |
XIEWrappedName !(XXIEWrappedName p) |
Instances
type LIEWrappedName p = XRec p (IEWrappedName p) Source #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern