[project @ 2003-12-16 16:24:42 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section{Haskell abstract syntax definition}
5
6 This module glues together the pieces of the Haskell abstract syntax,
7 which is declared in the various \tr{Hs*} modules.  This module,
8 therefore, is almost nothing but re-exporting.
9
10 \begin{code}
11 module HsSyn (
12         module HsBinds,
13         module HsDecls,
14         module HsExpr,
15         module HsImpExp,
16         module HsLit,
17         module HsPat,
18         module HsTypes,
19         module HsUtils,
20         Fixity, NewOrData, 
21
22         HsModule(..), HsExtCore(..)
23      ) where
24
25 #include "HsVersions.h"
26
27 -- friends:
28 import HsDecls          
29 import HsBinds
30 import HsExpr
31 import HsImpExp
32 import HsLit
33 import HsPat
34 import HsTypes
35 import HscTypes         ( DeprecTxt )
36 import BasicTypes       ( Fixity, NewOrData )
37 import HsUtils
38
39 -- others:
40 import IfaceSyn         ( IfaceBinding )
41 import Outputable
42 import SrcLoc           ( Located(..), unLoc, noLoc )
43 import Module           ( Module )
44 import Bag              ( Bag, foldrBag )
45 \end{code}
46
47 All we actually declare here is the top-level structure for a module.
48 \begin{code}
49 data HsModule name
50   = HsModule
51         (Maybe (Located Module))-- Nothing => "module X where" is omitted
52                                 --      (in which case the next field is Nothing too)
53         (Maybe [LIE name])      -- Export list; Nothing => export list omitted, so export everything
54                                 -- Just [] => export *nothing*
55                                 -- Just [...] => as you would expect...
56         [LImportDecl name]      -- We snaffle interesting stuff out of the
57                                 -- imported interfaces early on, adding that
58                                 -- info to TyDecls/etc; so this list is
59                                 -- often empty, downstream.
60         [LHsDecl name]  -- Type, class, value, and interface signature decls
61         (Maybe DeprecTxt)       -- reason/explanation for deprecation of this module
62
63 data HsExtCore name     -- Read from Foo.hcr
64   = HsExtCore
65         Module
66         [TyClDecl name] -- Type declarations only; just as in Haskell source,
67                         -- so that we can infer kinds etc
68         [IfaceBinding]  -- And the bindings
69 \end{code}
70
71 \begin{code}
72 instance (OutputableBndr name)
73         => Outputable (HsModule name) where
74
75     ppr (HsModule Nothing _ imports decls _)
76       = pp_nonnull imports $$ pp_nonnull decls
77
78     ppr (HsModule (Just name) exports imports decls deprec)
79       = vcat [
80             case exports of
81               Nothing -> pp_header (ptext SLIT("where"))
82               Just es -> vcat [
83                            pp_header lparen,
84                            nest 8 (fsep (punctuate comma (map ppr es))),
85                            nest 4 (ptext SLIT(") where"))
86                           ],
87             pp_nonnull imports,
88             pp_nonnull decls
89         ]
90       where
91         pp_header rest = case deprec of
92            Nothing -> pp_modname <+> rest
93            Just d -> vcat [ pp_modname, ppr d, rest ]
94
95         pp_modname = ptext SLIT("module") <+> ppr name
96
97 pp_nonnull [] = empty
98 pp_nonnull xs = vcat (map ppr xs)
99 \end{code}