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