Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 name)
- | IEThingAbs (LIEWrappedName name)
- | IEThingAll (LIEWrappedName name)
- | IEThingWith (LIEWrappedName name) IEWildcard [LIEWrappedName name] [Located (FieldLbl name)]
- | IEModuleContents (Located ModuleName)
- | IEGroup Int HsDocString
- | IEDoc HsDocString
- | IEDocNamed String
- data IEWildcard
- ieName :: IE name -> name
- ieNames :: IE a -> [a]
- 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 | |
|
Data name => Data (ImportDecl name) # | |
(OutputableBndr name, HasOccName name) => Outputable (ImportDecl name) # | |
simpleImportDecl :: ModuleName -> ImportDecl name Source #
data IEWrappedName name Source #
A name in an import or export specfication which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement.
Eq name => Eq (IEWrappedName name) # | |
Data name => Data (IEWrappedName name) # | |
(OutputableBndr name, HasOccName name) => OutputableBndr (IEWrappedName name) # | |
(HasOccName name, OutputableBndr name) => Outputable (IEWrappedName name) # | |
HasOccName name => HasOccName (IEWrappedName name) # | |
type LIEWrappedName name = Located (IEWrappedName name) Source #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern
Imported or exported entity.
IEVar (LIEWrappedName name) | Imported or Exported Variable |
IEThingAbs (LIEWrappedName name) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
IEThingAll (LIEWrappedName name) | Imported or exported Thing with All imported or exported The thing is a ClassType and the All refers to methodsconstructors |
IEThingWith (LIEWrappedName name) IEWildcard [LIEWrappedName name] [Located (FieldLbl 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 |
Eq name => Eq (IE name) # | |
Data name => Data (IE name) # | |
(HasOccName name, OutputableBndr name) => Outputable (IE name) # | |
data IEWildcard Source #
Imported or Exported Wildcard
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 #