add support for <{..}> and ~~> syntax as well as typing for Kappa-calculus
[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(..), CodeFlavor(..)
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
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
54 data CodeFlavor = LambdaFlavor | KappaFlavor
55
56 -- | All we actually declare here is the top-level structure for a module.
57 data HsModule name
58   = HsModule {
59       hsmodName :: Maybe (Located ModuleName),
60         -- ^ @Nothing@: \"module X where\" is omitted (in which case the next
61         --     field is Nothing too)
62       hsmodExports :: Maybe [LIE name],
63         -- ^ Export list
64         --
65         --  - @Nothing@: export list omitted, so export everything
66         --
67         --  - @Just []@: export /nothing/
68         --
69         --  - @Just [...]@: as you would expect...
70         --
71       hsmodImports :: [LImportDecl name],
72         -- ^ We snaffle interesting stuff out of the imported interfaces early
73         -- on, adding that info to TyDecls/etc; so this list is often empty,
74         -- downstream.
75       hsmodDecls :: [LHsDecl name],
76         -- ^ Type, class, value, and interface signature decls
77       hsmodDeprecMessage :: Maybe WarningTxt,
78         -- ^ reason\/explanation for warning/deprecation of this module
79       hsmodHaddockModHeader :: Maybe LHsDocString
80         -- ^ Haddock module info and description, unparsed
81    } deriving (Data, Typeable)
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}