Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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)]
- 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
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
Documentation
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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XImportDeclPass Source # toConstr :: XImportDeclPass -> Constr Source # dataTypeOf :: XImportDeclPass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XImportDeclPass) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XImportDeclPass) Source # gmapT :: (forall b. Data b => b -> b) -> XImportDeclPass -> XImportDeclPass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XImportDeclPass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> XImportDeclPass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> XImportDeclPass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XImportDeclPass -> m XImportDeclPass Source # |
data EpAnnImportDecl Source #
Instances
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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnImportDecl Source # toConstr :: EpAnnImportDecl -> Constr Source # dataTypeOf :: EpAnnImportDecl -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnImportDecl) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnImportDecl) Source # gmapT :: (forall b. Data b => b -> b) -> EpAnnImportDecl -> EpAnnImportDecl Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnImportDecl -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnImportDecl -> r Source # gmapQ :: (forall d. Data d => d -> u) -> EpAnnImportDecl -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnImportDecl -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnImportDecl -> m EpAnnImportDecl Source # |
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 #
ieWrappedLName :: IEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
lieWrappedName :: LIEWrappedName (GhcPass p) -> IdP (GhcPass p) Source #
ieLWrappedName :: LIEWrappedName (GhcPass p) -> LIdP (GhcPass p) Source #
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc Source #