2169b1a3b6a7cee09b8c899f782a6294c239a528
[ghc-hetmet.git] / 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,
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 BasicTypes       ( Fixity, DeprecTxt )
36 import HsUtils
37
38 -- others:
39 import IfaceSyn         ( IfaceBinding )
40 import Outputable
41 import SrcLoc           ( Located(..) )
42 import Module           ( Module, ModuleName )
43 \end{code}
44
45 All we actually declare here is the top-level structure for a module.
46 \begin{code}
47 data HsModule name
48   = HsModule
49         (Maybe (Located ModuleName))-- Nothing => "module X where" is omitted
50                                 --      (in which case the next field is Nothing too)
51         (Maybe [LIE name])      -- Export list; Nothing => export list omitted, so export everything
52                                 -- Just [] => export *nothing*
53                                 -- Just [...] => as you would expect...
54         [LImportDecl name]      -- We snaffle interesting stuff out of the
55                                 -- imported interfaces early on, adding that
56                                 -- info to TyDecls/etc; so this list is
57                                 -- often empty, downstream.
58         [LHsDecl name]          -- Type, class, value, and interface signature decls
59         (Maybe DeprecTxt)       -- reason/explanation for deprecation of this module
60
61 data HsExtCore name     -- Read from Foo.hcr
62   = HsExtCore
63         Module
64         [TyClDecl name] -- Type declarations only; just as in Haskell source,
65                         -- so that we can infer kinds etc
66         [IfaceBinding]  -- And the bindings
67 \end{code}
68
69 \begin{code}
70 instance (OutputableBndr name)
71         => Outputable (HsModule name) where
72
73     ppr (HsModule Nothing _ imports decls _)
74       = pp_nonnull imports $$ pp_nonnull decls
75
76     ppr (HsModule (Just name) exports imports decls deprec)
77       = vcat [
78             case exports of
79               Nothing -> pp_header (ptext SLIT("where"))
80               Just es -> vcat [
81                            pp_header lparen,
82                            nest 8 (fsep (punctuate comma (map ppr es))),
83                            nest 4 (ptext SLIT(") where"))
84                           ],
85             pp_nonnull imports,
86             pp_nonnull decls
87         ]
88       where
89         pp_header rest = case deprec of
90            Nothing -> pp_modname <+> rest
91            Just d -> vcat [ pp_modname, ppr d, rest ]
92
93         pp_modname = ptext SLIT("module") <+> ppr name
94
95 pp_nonnull [] = empty
96 pp_nonnull xs = vcat (map ppr xs)
97 \end{code}