031bf93a3f2872533008cdd0fee984d155100ae6
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsImpExp.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[HsImpExp]{Abstract syntax: imports, exports, interfaces}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module HsImpExp where
10
11 import Ubiq
12
13 import Outputable
14 import PprStyle         ( PprStyle(..) )
15 import Pretty
16 import SrcLoc           ( SrcLoc )
17 \end{code}
18
19 %************************************************************************
20 %*                                                                      *
21 \subsection{Import and export declaration lists}
22 %*                                                                      *
23 %************************************************************************
24
25 One per \tr{import} declaration in a module.
26 \begin{code}
27 data ImportDecl name
28   = ImportDecl    Module                        -- module name
29                   Bool                          -- qualified?
30                   (Maybe Module)                -- as Module
31                   (Maybe (Bool, [IE name]))     -- (hiding?, names)
32                   SrcLoc
33 \end{code}
34
35 \begin{code}
36 instance (Outputable name) => Outputable (ImportDecl name) where
37     ppr sty (ImportDecl mod qual as spec _)
38       = ppHang (ppCat [ppStr "import", pp_qual qual, ppPStr mod, pp_as as])
39              4 (pp_spec spec)
40       where
41         pp_qual False   = ppNil
42         pp_qual True    = ppStr "qualified"
43
44         pp_as Nothing   = ppNil
45         pp_as (Just a)  = ppCat [ppStr "as", ppPStr a]
46
47         pp_spec Nothing = ppNil
48         pp_spec (Just (False, spec))
49                         = ppBesides [ppStr "(", interpp'SP sty spec, ppStr ")"]
50         pp_spec (Just (True, spec))
51                         = ppBesides [ppStr "hiding (", interpp'SP sty spec, ppStr ")"]
52
53 \end{code}
54
55 %************************************************************************
56 %*                                                                      *
57 \subsection{Imported and exported entities}
58 %*                                                                      *
59 %************************************************************************
60 \begin{code}
61 data IE name
62   = IEVar               name
63   | IEThingAbs          name            -- Constructor/Type/Class (can't tell)
64   | IEThingAll          name            -- Class/Type plus all methods/constructors
65   | IEThingWith         name [name]     -- Class/Type plus some methods/constructors
66   | IEModuleContents    Module          -- (Export Only)
67 \end{code}
68
69 \begin{code}
70 instance (Outputable name) => Outputable (IE name) where
71     ppr sty (IEVar      var)    = ppr sty var
72     ppr sty (IEThingAbs thing)  = ppr sty thing
73     ppr sty (IEThingAll thing)
74         = ppBesides [ppr sty thing, ppStr "(..)"]
75     ppr sty (IEThingWith thing withs)
76         = ppBesides [ppr sty thing, ppLparen, ppInterleave ppComma (map (ppr sty) withs), ppRparen]
77     ppr sty (IEModuleContents mod)
78         = ppBeside (ppPStr SLIT("module ")) (ppPStr mod)
79 \end{code}