| Safe Haskell | Ignore | 
|---|---|
| Language | GHC2021 | 
GHC.Hs.ImpExp
Contents
Synopsis
- module Language.Haskell.Syntax.ImpExp
- data XImportDeclPass = XImportDeclPass {}
- data EpAnnImportDecl = EpAnnImportDecl {}
- importDeclQualifiedStyle :: Maybe EpaLocation -> Maybe EpaLocation -> (Maybe EpaLocation, ImportDeclQualifiedStyle)
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- simpleImportDecl :: ModuleName -> ImportDecl GhcPs
- ieName :: IE (GhcPass p) -> IdP (GhcPass p)
- ieWrappedName :: IEWrappedName (GhcPass p) -> IdP (GhcPass p)
- ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)]
- ieDeprecation :: forall p. IsPass p => IE (GhcPass p) -> Maybe (WarningTxt (GhcPass p))
- ieWrappedLName :: IEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- lieWrappedName :: LIEWrappedName (GhcPass p) -> IdP (GhcPass p)
- ieLWrappedName :: LIEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- replaceWrappedName :: IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn
- replaceLWrappedName :: LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
- exportDocstring :: LHsDoc pass -> SDoc
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
Documentation
data XImportDeclPass Source #
Constructors
| XImportDeclPass | |
| Fields 
 | |
Instances
| Data XImportDeclPass Source # | |
| Defined in GHC.Hs.ImpExp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XImportDeclPass -> c XImportDeclPass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XImportDeclPass # toConstr :: XImportDeclPass -> Constr # dataTypeOf :: XImportDeclPass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XImportDeclPass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XImportDeclPass) # gmapT :: (forall b. Data b => b -> b) -> XImportDeclPass -> XImportDeclPass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r # gmapQ :: (forall d. Data d => d -> u) -> XImportDeclPass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> XImportDeclPass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass # | |
data EpAnnImportDecl Source #
Constructors
| EpAnnImportDecl | |
Instances
| Data EpAnnImportDecl Source # | |
| Defined in GHC.Hs.ImpExp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnnImportDecl -> c EpAnnImportDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnImportDecl # toConstr :: EpAnnImportDecl -> Constr # dataTypeOf :: EpAnnImportDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnImportDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnImportDecl) # gmapT :: (forall b. Data b => b -> b) -> EpAnnImportDecl -> EpAnnImportDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnImportDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnImportDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> EpAnnImportDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnImportDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl # | |
| NoAnn EpAnnImportDecl Source # | |
| Defined in GHC.Hs.ImpExp Methods | |
importDeclQualifiedStyle :: Maybe EpaLocation -> Maybe EpaLocation -> (Maybe EpaLocation, ImportDeclQualifiedStyle) Source #
Given two possible located qualified tokens, compute a style
 (in a conforming Haskell program only one of the two can be not
 Nothing). This is called from GHC.Parser.
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool Source #
Convenience function to answer the question if an import decl. is qualified.
ieWrappedName :: IEWrappedName (GhcPass p) -> IdP (GhcPass p) Source #
ieDeprecation :: forall p. IsPass p => IE (GhcPass p) -> Maybe (WarningTxt (GhcPass p)) Source #
ieWrappedLName :: IEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
lieWrappedName :: LIEWrappedName (GhcPass p) -> IdP (GhcPass p) Source #
ieLWrappedName :: LIEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
exportDocstring :: LHsDoc pass -> SDoc Source #
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc Source #