| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
HsImpExp
Synopsis
- type LImportDecl pass = Located (ImportDecl pass)
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclSourceSrc :: SourceText
- ideclName :: Located ModuleName
- ideclPkgQual :: Maybe StringLiteral
- ideclSource :: Bool
- ideclSafe :: Bool
- ideclQualified :: Bool
- 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 pass -> IdP pass
- ieNames :: IE pass -> [IdP pass]
- 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
data ImportDecl pass Source #
Import Declaration
A single Haskell import declaration.
Constructors
Fields
- ideclExt :: XCImportDecl pass
- ideclSourceSrc :: SourceText
- ideclName :: Located ModuleName
Module name.
- ideclPkgQual :: Maybe StringLiteral
Package qualifier.
- ideclSource :: Bool
True = {-# SOURCE #-} import
- ideclSafe :: Bool
True => safe import
- ideclQualified :: Bool
True => qualified
- ideclImplicit :: Bool
True => implicit import (of Prelude)
- ideclAs :: Maybe (Located ModuleName)
as Module
- ideclHiding :: Maybe (Bool, Located [LIE pass])
(True => hiding, names)
Instances
Instance details
Defined in HsInstances
Methods
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 :: (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) #
Instance details
Defined in HsInstances
Methods
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 :: (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) #
Instance details
Defined in HsInstances
Methods
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 :: (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) #
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.
Constructors
Instances
Instance details
Defined in HsImpExp
Methods
(==) :: IEWrappedName name -> IEWrappedName name -> Bool #
(/=) :: IEWrappedName name -> IEWrappedName name -> Bool #
Instance details
Defined in HsImpExp
Methods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName name -> c (IEWrappedName name) #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName name) #
toConstr :: IEWrappedName name -> Constr #
dataTypeOf :: IEWrappedName name -> DataType #
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)) #
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName name)) #
gmapT :: (forall b. Data b => b -> b) -> IEWrappedName name -> IEWrappedName name #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r #
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r #
gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) #
Instance details
Defined in HsImpExp
Methods
pprBndr :: BindingSite -> IEWrappedName name -> SDoc Source #
pprPrefixOcc :: IEWrappedName name -> SDoc Source #
pprInfixOcc :: IEWrappedName name -> SDoc Source #
bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int Source #
type LIEWrappedName name = Located (IEWrappedName name) Source #
Located name with possible adornment
- AnnKeywordId s : AnnType ,
AnnPattern
Arguments
Located Import or Export
Imported or exported entity.
Constructors
Imported or exported Thing with Absent list
The thing is a Class/Type (can't tell)
- AnnKeywordId s : AnnPattern ,
AnnType ,AnnVal
Imported or exported Thing with All imported or exported
The thing is a ClassType and the All refers to methodsconstructors
AnnKeywordIds :AnnOpen,AnnDotdot,AnnClose,AnnType
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]
- AnnKeywordId s : AnnOpen ,
AnnClose ,
AnnComma ,
AnnType
Imported or exported module contents
(Export Only)
Instances
Instance details
Defined in HsInstances
Methods
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 :: (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) #
Instance details
Defined in HsInstances
Methods
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 :: (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) #
Instance details
Defined in HsInstances
Methods
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 :: (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 IEWildcard Source #
Imported or Exported Wildcard
Instances
Instance details
Defined in HsImpExp
Instance details
Defined in HsImpExp
Methods
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 :: (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 #
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 #