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