2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
5 \section{Haskell abstract syntax definition}
7 This module glues together the pieces of the Haskell abstract syntax,
8 which is declared in the various \tr{Hs*} modules. This module,
9 therefore, is almost nothing but re-exporting.
13 -- The above warning supression flag is a temporary kludge.
14 -- While working on this module you are encouraged to remove it and fix
15 -- any warnings in the module. See
16 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
31 HsModule(..), HsExtCore(..),
37 #include "HsVersions.h"
47 import BasicTypes ( Fixity, DeprecTxt )
52 import IfaceSyn ( IfaceBinding )
54 import SrcLoc ( Located(..) )
55 import Module ( Module, ModuleName )
58 All we actually declare here is the top-level structure for a module.
62 (Maybe (Located ModuleName))-- Nothing => "module X where" is omitted
63 -- (in which case the next field is Nothing too)
64 (Maybe [LIE name]) -- Export list; Nothing => export list omitted, so export everything
65 -- Just [] => export *nothing*
66 -- Just [...] => as you would expect...
67 [LImportDecl name] -- We snaffle interesting stuff out of the
68 -- imported interfaces early on, adding that
69 -- info to TyDecls/etc; so this list is
70 -- often empty, downstream.
71 [LHsDecl name] -- Type, class, value, and interface signature decls
72 (Maybe DeprecTxt) -- reason/explanation for deprecation of this module
73 (HaddockModInfo name) -- Haddock module info
74 (Maybe (HsDoc name)) -- Haddock module description
76 data HaddockModInfo name = HaddockModInfo {
77 hmi_description :: Maybe (HsDoc name),
78 hmi_portability :: Maybe String,
79 hmi_stability :: Maybe String,
80 hmi_maintainer :: Maybe String
83 emptyHaddockModInfo :: HaddockModInfo a
84 emptyHaddockModInfo = HaddockModInfo {
85 hmi_description = Nothing,
86 hmi_portability = Nothing,
87 hmi_stability = Nothing,
88 hmi_maintainer = Nothing
91 data HsExtCore name -- Read from Foo.hcr
94 [TyClDecl name] -- Type declarations only; just as in Haskell source,
95 -- so that we can infer kinds etc
96 [IfaceBinding] -- And the bindings
101 instance Outputable Char where
104 instance (OutputableBndr name)
105 => Outputable (HsModule name) where
107 ppr (HsModule Nothing _ imports decls _ _ mbDoc)
108 = pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
110 ppr (HsModule (Just name) exports imports decls deprec _ mbDoc)
114 Nothing -> pp_header (ptext SLIT("where"))
117 nest 8 (fsep (punctuate comma (map ppr es))),
118 nest 4 (ptext SLIT(") where"))
124 pp_header rest = case deprec of
125 Nothing -> pp_modname <+> rest
126 Just d -> vcat [ pp_modname, ppr d, rest ]
128 pp_modname = ptext SLIT("module") <+> ppr name
130 pp_mb (Just x) = ppr x
131 pp_mb Nothing = empty
133 pp_nonnull [] = empty
134 pp_nonnull xs = vcat (map ppr xs)