Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- module Language.Haskell.Syntax.ImpExp
- exportDocstring :: LHsDoc pass -> SDoc
- ieDeprecation :: forall (p :: Pass). IsPass p => IE (GhcPass p) -> Maybe (WarningTxt (GhcPass p))
- ieLWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- ieName :: forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p)
- ieNames :: forall (p :: Pass). IE (GhcPass p) -> [IdP (GhcPass p)]
- ieWrappedLName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> LIdP (GhcPass p)
- ieWrappedName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
- importDeclQualifiedStyle :: Maybe (EpToken "qualified") -> Maybe (EpToken "qualified") -> (Maybe (EpToken "qualified"), ImportDeclQualifiedStyle)
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- lieWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> IdP (GhcPass p)
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
- replaceLWrappedName :: LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
- replaceWrappedName :: IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn
- simpleImportDecl :: ModuleName -> ImportDecl GhcPs
- data EpAnnImportDecl = EpAnnImportDecl {
- importDeclAnnImport :: EpToken "import"
- importDeclAnnPragma :: Maybe (EpaLocation, EpToken "#-}")
- importDeclAnnSafe :: Maybe (EpToken "safe")
- importDeclAnnQualified :: Maybe (EpToken "qualified")
- importDeclAnnPackage :: Maybe EpaLocation
- importDeclAnnAs :: Maybe (EpToken "as")
- type IEThingWithAnns = (EpToken "(", EpToken "..", EpToken ",", EpToken ")")
- data XImportDeclPass = XImportDeclPass {}
Documentation
exportDocstring :: LHsDoc pass -> SDoc Source #
ieDeprecation :: forall (p :: Pass). IsPass p => IE (GhcPass p) -> Maybe (WarningTxt (GhcPass p)) Source #
ieLWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
ieWrappedLName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
ieWrappedName :: forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p) Source #
importDeclQualifiedStyle :: Maybe (EpToken "qualified") -> Maybe (EpToken "qualified") -> (Maybe (EpToken "qualified"), 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.
lieWrappedName :: forall (p :: Pass). LIEWrappedName (GhcPass p) -> IdP (GhcPass p) Source #
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc Source #
data EpAnnImportDecl Source #
EpAnnImportDecl | |
|
Instances
NoAnn EpAnnImportDecl Source # | |
Defined in GHC.Hs.ImpExp | |
Data EpAnnImportDecl Source # | |
Defined in GHC.Hs.ImpExp 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 # |
data XImportDeclPass Source #
XImportDeclPass | |
|
Instances
Data XImportDeclPass Source # | |
Defined in GHC.Hs.ImpExp 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 # |