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