[project @ 1996-06-05 06:44:31 by partain]
[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 IMP_Ubiq()
12
13 import Name             ( pprNonSym )
14 import Outputable
15 import PprStyle         ( PprStyle(..) )
16 import Pretty
17 import SrcLoc           ( SrcLoc )
18 \end{code}
19
20 %************************************************************************
21 %*                                                                      *
22 \subsection{Import and export declaration lists}
23 %*                                                                      *
24 %************************************************************************
25
26 One per \tr{import} declaration in a module.
27 \begin{code}
28 data ImportDecl name
29   = ImportDecl    Module                        -- module name
30                   Bool                          -- True => qualified
31                   (Maybe Module)                -- as Module
32                   (Maybe (Bool, [IE name]))     -- (True => hiding, names)
33                   SrcLoc
34 \end{code}
35
36 \begin{code}
37 instance (NamedThing name, Outputable name) => Outputable (ImportDecl name) where
38     ppr sty (ImportDecl mod qual as spec _)
39       = ppHang (ppCat [ppPStr SLIT("import"), pp_qual qual, ppPStr mod, pp_as as])
40              4 (pp_spec spec)
41       where
42         pp_qual False   = ppNil
43         pp_qual True    = ppPStr SLIT("qualified")
44
45         pp_as Nothing   = ppNil
46         pp_as (Just a)  = ppBeside (ppPStr SLIT("as ")) (ppPStr a)
47
48         pp_spec Nothing = ppNil
49         pp_spec (Just (False, spec))
50                         = ppParens (interpp'SP sty spec)
51         pp_spec (Just (True, spec))
52                         = ppBeside (ppPStr SLIT("hiding ")) (ppParens (interpp'SP sty spec))
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            -- Class/Type (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 (NamedThing name, Outputable name) => Outputable (IE name) where
71     ppr sty (IEVar      var)    = pprNonSym 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         = ppBeside (ppr sty thing)
77             (ppParens (ppInterleave ppComma (map (pprNonSym sty) withs)))
78     ppr sty (IEModuleContents mod)
79         = ppBeside (ppPStr SLIT("module ")) (ppPStr mod)
80 \end{code}