[project @ 1996-12-19 09:10:02 by simonpj]
[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
61 \begin{code}
62 data IE name
63   = IEVar               name
64   | IEThingAbs          name            -- Class/Type (can't tell)
65   | IEThingAll          name            -- Class/Type plus all methods/constructors
66   | IEThingWith         name [name]     -- Class/Type plus some methods/constructors
67   | IEModuleContents    Module          -- (Export Only)
68 \end{code}
69
70 \begin{code}
71 ieName :: IE name -> name
72 ieName (IEVar n)         = n
73 ieName (IEThingAbs  n)   = n
74 ieName (IEThingWith n _) = n
75 ieName (IEThingAll  n)   = n
76 \end{code}
77
78 \begin{code}
79 instance (NamedThing name, Outputable name) => Outputable (IE name) where
80     ppr sty (IEVar      var)    = pprNonSym sty var
81     ppr sty (IEThingAbs thing)  = ppr sty thing
82     ppr sty (IEThingAll thing)
83         = ppBesides [ppr sty thing, ppStr "(..)"]
84     ppr sty (IEThingWith thing withs)
85         = ppBeside (ppr sty thing)
86             (ppParens (ppInterleave ppComma (map (pprNonSym sty) withs)))
87     ppr sty (IEModuleContents mod)
88         = ppBeside (ppPStr SLIT("module ")) (ppPStr mod)
89 \end{code}
90