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