Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type LImportDecl name = Located (ImportDecl name)
- data ImportDecl name = ImportDecl {
- 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 name])
- simpleImportDecl :: ModuleName -> ImportDecl name
- data IEWrappedName name
- type LIEWrappedName name = Located (IEWrappedName name)
- type LIE name = Located (IE name)
- data IE name
- = IEVar (LIEWrappedName (IdP name))
- | IEThingAbs (LIEWrappedName (IdP name))
- | IEThingAll (LIEWrappedName (IdP name))
- | IEThingWith (LIEWrappedName (IdP name)) IEWildcard [LIEWrappedName (IdP name)] [Located (FieldLbl (IdP name))]
- | IEModuleContents (Located ModuleName)
- | IEGroup Int HsDocString
- | IEDoc HsDocString
- | IEDocNamed String
- data IEWildcard
- ieName :: IE pass -> IdP pass
- ieNames :: IE pass -> [IdP pass]
- ieWrappedName :: IEWrappedName 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
type LImportDecl name Source #
= Located (ImportDecl name) | When in a list this may have |
Located Import Declaration
data ImportDecl name Source #
Import Declaration
A single Haskell import
declaration.
ImportDecl | |
|
Instances
DataId name => Data (ImportDecl name) Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl name -> c (ImportDecl name) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl name) Source # toConstr :: ImportDecl name -> Constr Source # dataTypeOf :: ImportDecl name -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl name)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl name)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl name -> ImportDecl name Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl name -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl name -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl name -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl name -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl name -> m (ImportDecl name) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl name -> m (ImportDecl name) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl name -> m (ImportDecl name) Source # | |
OutputableBndrId pass => Outputable (ImportDecl pass) Source # | |
simpleImportDecl :: ModuleName -> ImportDecl name 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.
Instances
Eq name => Eq (IEWrappedName name) Source # | |
(==) :: IEWrappedName name -> IEWrappedName name -> Bool # (/=) :: IEWrappedName name -> IEWrappedName name -> Bool # | |
Data name => Data (IEWrappedName name) Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName name -> c (IEWrappedName name) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName name) Source # toConstr :: IEWrappedName name -> Constr Source # dataTypeOf :: IEWrappedName name -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName name)) Source # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName name -> IEWrappedName name Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) Source # | |
OutputableBndr name => OutputableBndr (IEWrappedName name) Source # | |
pprBndr :: BindingSite -> IEWrappedName name -> SDoc Source # pprPrefixOcc :: IEWrappedName name -> SDoc Source # pprInfixOcc :: IEWrappedName name -> SDoc Source # bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int Source # | |
OutputableBndr name => Outputable (IEWrappedName name) Source # | |
HasOccName name => HasOccName (IEWrappedName name) Source # | |
occName :: IEWrappedName name -> OccName Source # |
type LIEWrappedName name = Located (IEWrappedName name) Source #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern
Imported or exported entity.
IEVar (LIEWrappedName (IdP name)) | Imported or Exported Variable |
IEThingAbs (LIEWrappedName (IdP name)) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
IEThingAll (LIEWrappedName (IdP name)) | Imported or exported Thing with All imported or exported The thing is a ClassType and the All refers to methodsconstructors |
IEThingWith (LIEWrappedName (IdP name)) IEWildcard [LIEWrappedName (IdP name)] [Located (FieldLbl (IdP name))] | 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 (Located ModuleName) | Imported or exported module contents (Export Only) |
IEGroup Int HsDocString | Doc section heading |
IEDoc HsDocString | Some documentation |
IEDocNamed String | Reference to named doc deriving (Eq, Data) |
Instances
(Eq name, Eq (IdP name)) => Eq (IE name) Source # | |
DataId name => Data (IE name) Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE name -> c (IE name) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE name) Source # toConstr :: IE name -> Constr Source # dataTypeOf :: IE name -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE name)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE name)) Source # gmapT :: (forall b. Data b => b -> b) -> IE name -> IE name Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE name -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE name -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE name -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE name -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE name -> m (IE name) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE name -> m (IE name) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE name -> m (IE name) Source # | |
OutputableBndrId pass => Outputable (IE pass) Source # | |
data IEWildcard Source #
Imported or Exported Wildcard
Instances
Eq IEWildcard Source # | |
(==) :: IEWildcard -> IEWildcard -> Bool # (/=) :: IEWildcard -> IEWildcard -> Bool # | |
Data IEWildcard Source # | |
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 :: (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 # |
ieWrappedName :: IEWrappedName 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 #