[project @ 1999-03-02 18:31:51 by sof]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsImpExp.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[HsImpExp]{Abstract syntax: imports, exports, interfaces}
5
6 \begin{code}
7 module HsImpExp where
8
9 #include "HsVersions.h"
10
11 import Module           ( Module, pprModule, moduleIfaceFlavour, bootFlavour )
12 import Outputable
13 import SrcLoc           ( SrcLoc )
14 \end{code}
15
16 %************************************************************************
17 %*                                                                      *
18 \subsection{Import and export declaration lists}
19 %*                                                                      *
20 %************************************************************************
21
22 One per \tr{import} declaration in a module.
23 \begin{code}
24 data ImportDecl name
25   = ImportDecl    Module                        -- module name
26                   Bool                          -- True => qualified
27                   (Maybe Module)                -- as Module
28                   (Maybe (Bool, [IE name]))     -- (True => hiding, names)
29                   SrcLoc
30 \end{code}
31
32 \begin{code}
33 instance (Outputable name) => Outputable (ImportDecl name) where
34     ppr (ImportDecl mod qual as spec _)
35       = hang (hsep [ptext SLIT("import"), pp_src, 
36                     pp_qual qual, pprModule mod, pp_as as])
37              4 (pp_spec spec)
38       where
39         pp_src | bootFlavour (moduleIfaceFlavour mod) = ptext SLIT("{-# SOURCE #-}")
40                | otherwise                            = empty
41
42         pp_qual False   = empty
43         pp_qual True    = ptext SLIT("qualified")
44
45         pp_as Nothing   = empty
46         pp_as (Just a)  = ptext SLIT("as ") <+> pprModule a
47
48         pp_spec Nothing = empty
49         pp_spec (Just (False, spec))
50                         = parens (interpp'SP spec)
51         pp_spec (Just (True, spec))
52                         = ptext SLIT("hiding") <+> parens (interpp'SP 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 (Outputable name) => Outputable (IE name) where
80     ppr (IEVar          var)    = ppr var
81     ppr (IEThingAbs     thing)  = ppr thing
82     ppr (IEThingAll     thing)  = hcat [ppr thing, text "(..)"]
83     ppr (IEThingWith thing withs)
84         = ppr thing <> parens (fsep (punctuate comma (map ppr withs)))
85     ppr (IEModuleContents mod)
86         = ptext SLIT("module") <+> pprModule mod
87 \end{code}
88