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