39093f25502eff967f971a79b3a42a3371e9115b
[ghc-hetmet.git] / compiler / hsSyn / HsSyn.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section{Haskell abstract syntax definition}
6
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.
10
11 \begin{code}
12 {-# LANGUAGE DeriveDataTypeable #-}
13
14 module HsSyn (
15         module HsBinds,
16         module HsDecls,
17         module HsExpr,
18         module HsImpExp,
19         module HsLit,
20         module HsPat,
21         module HsTypes,
22         module HsUtils,
23         module HsDoc,
24         Fixity,
25
26         HsModule(..), HsExtCore(..),
27 ) where
28
29 -- friends:
30 import HsDecls          
31 import HsBinds
32 import HsExpr
33 import HsImpExp
34 import HsLit
35 import HsPat
36 import HsTypes
37 import BasicTypes       ( Fixity, WarningTxt )
38 import HsUtils
39 import HsDoc
40
41 -- others:
42 import IfaceSyn         ( IfaceBinding )
43 import Outputable
44 import SrcLoc           ( Located(..) )
45 import Module           ( Module, ModuleName )
46 import FastString
47
48 -- libraries:
49 import Data.Data hiding ( Fixity )
50 \end{code}
51
52 \begin{code}
53 -- | All we actually declare here is the top-level structure for a module.
54 data HsModule name
55   = HsModule {
56       hsmodName :: Maybe (Located ModuleName),
57         -- ^ @Nothing@: \"module X where\" is omitted (in which case the next
58         --     field is Nothing too)
59       hsmodExports :: Maybe [LIE name],
60         -- ^ Export list
61         --
62         --  - @Nothing@: export list omitted, so export everything
63         --
64         --  - @Just []@: export /nothing/
65         --
66         --  - @Just [...]@: as you would expect...
67         --
68       hsmodImports :: [LImportDecl name],
69         -- ^ We snaffle interesting stuff out of the imported interfaces early
70         -- on, adding that info to TyDecls/etc; so this list is often empty,
71         -- downstream.
72       hsmodDecls :: [LHsDecl name],
73         -- ^ Type, class, value, and interface signature decls
74       hsmodDeprecMessage :: Maybe WarningTxt,
75         -- ^ reason\/explanation for warning/deprecation of this module
76       hsmodHaddockModHeader :: Maybe LHsDocString
77         -- ^ Haddock module info and description, unparsed
78    } deriving (Data, Typeable)
79
80 data HsExtCore name     -- Read from Foo.hcr
81   = HsExtCore
82         Module
83         [TyClDecl name] -- Type declarations only; just as in Haskell source,
84                         -- so that we can infer kinds etc
85         [IfaceBinding]  -- And the bindings
86 \end{code}
87
88
89 \begin{code}
90 instance Outputable Char where
91   ppr c = text [c]
92
93 instance (OutputableBndr name)
94         => Outputable (HsModule name) where
95
96     ppr (HsModule Nothing _ imports decls _ mbDoc)
97       = pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
98
99     ppr (HsModule (Just name) exports imports decls deprec mbDoc)
100       = vcat [
101             pp_mb mbDoc,
102             case exports of
103               Nothing -> pp_header (ptext (sLit "where"))
104               Just es -> vcat [
105                            pp_header lparen,
106                            nest 8 (fsep (punctuate comma (map ppr es))),
107                            nest 4 (ptext (sLit ") where"))
108                           ],
109             pp_nonnull imports,
110             pp_nonnull decls
111           ]
112       where
113         pp_header rest = case deprec of
114            Nothing -> pp_modname <+> rest
115            Just d -> vcat [ pp_modname, ppr d, rest ]
116
117         pp_modname = ptext (sLit "module") <+> ppr name
118
119 pp_mb :: Outputable t => Maybe t -> SDoc
120 pp_mb (Just x) = ppr x 
121 pp_mb Nothing  = empty
122
123 pp_nonnull :: Outputable t => [t] -> SDoc
124 pp_nonnull [] = empty
125 pp_nonnull xs = vcat (map ppr xs)
126 \end{code}