ghc-6.12.1: The GHC APISource codeContentsIndex
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
hsmodHaddockModHeader :: Maybe LHsDocString
}
data HsExtCore name = HsExtCore Module [TyClDecl name] [IfaceBinding]
Documentation
module HsBinds
module HsDecls
module HsExpr
module HsImpExp
module HsLit
module HsPat
module HsTypes
module HsUtils
module HsDoc
data Fixity Source
show/hide Instances
data HsModule name Source
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
hsmodHaddockModHeader :: Maybe LHsDocStringHaddock module info and description, unparsed
show/hide Instances
data HsExtCore name Source
Constructors
HsExtCore Module [TyClDecl name] [IfaceBinding]
Produced by Haddock version 2.6.0