ghc-6.10.2: The GHC APIContentsIndex
HsSyn
Synopsis
module HsBinds
module HsDecls
module HsExpr
module HsImpExp
module HsLit
module HsPat
module HsTypes
module HsUtils
module HsDoc
data Fixity
data HsModule name = HsModule {
hsmodName :: Maybe (Located ModuleName)
hsmodExports :: Maybe [LIE name]
hsmodImports :: [LImportDecl name]
hsmodDecls :: [LHsDecl name]
hsmodDeprecMessage :: Maybe WarningTxt
hsmodHaddockModInfo :: HaddockModInfo name
hsmodHaddockModDescr :: Maybe (HsDoc name)
}
data HsExtCore name = HsExtCore Module [TyClDecl name] [IfaceBinding]
data HaddockModInfo name = HaddockModInfo {
hmi_description :: Maybe (HsDoc name)
hmi_portability :: Maybe String
hmi_stability :: Maybe String
hmi_maintainer :: Maybe String
}
emptyHaddockModInfo :: HaddockModInfo a
Documentation
module HsBinds
module HsDecls
module HsExpr
module HsImpExp
module HsLit
module HsPat
module HsTypes
module HsUtils
module HsDoc
data Fixity
show/hide Instances
data HsModule name
All we actually declare here is the top-level structure for a module.
Constructors
HsModule
hsmodName :: Maybe (Located ModuleName)Nothing: "module X where" is omitted (in which case the next field is Nothing too)
hsmodExports :: Maybe [LIE name]

Export list

  • Nothing: export list omitted, so export everything
  • Just []: export nothing
  • Just [...]: as you would expect...
hsmodImports :: [LImportDecl name]We snaffle interesting stuff out of the imported interfaces early on, adding that info to TyDecls/etc; so this list is often empty, downstream.
hsmodDecls :: [LHsDecl name]Type, class, value, and interface signature decls
hsmodDeprecMessage :: Maybe WarningTxtreason/explanation for warning/deprecation of this module
hsmodHaddockModInfo :: HaddockModInfo nameHaddock module info
hsmodHaddockModDescr :: Maybe (HsDoc name)Haddock module description
show/hide Instances
data HsExtCore name
Constructors
HsExtCore Module [TyClDecl name] [IfaceBinding]
data HaddockModInfo name
Constructors
HaddockModInfo
hmi_description :: Maybe (HsDoc name)
hmi_portability :: Maybe String
hmi_stability :: Maybe String
hmi_maintainer :: Maybe String
emptyHaddockModInfo :: HaddockModInfo a
Produced by Haddock version 2.4.2