Fix warnings
[ghc-hetmet.git] / compiler / hsSyn / HsImpExp.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 HsImpExp: Abstract syntax: imports, exports, interfaces
7
8 \begin{code}
9 {-# LANGUAGE DeriveDataTypeable #-}
10
11 module HsImpExp where
12
13 import Module           ( ModuleName )
14 import HsDoc            ( HsDocString )
15
16 import Outputable
17 import FastString
18 import SrcLoc
19
20 import Data.Data
21 \end{code}
22
23 %************************************************************************
24 %*                                                                      *
25 \subsection{Import and export declaration lists}
26 %*                                                                      *
27 %************************************************************************
28
29 One per \tr{import} declaration in a module.
30 \begin{code}
31 type LImportDecl name = Located (ImportDecl name)
32
33 -- | A single Haskell @import@ declaration.
34 data ImportDecl name
35   = ImportDecl {
36       ideclName      :: Located ModuleName, -- ^ Module name.
37       ideclPkgQual   :: Maybe FastString,   -- ^ Package qualifier.
38       ideclSource    :: Bool,               -- ^ True <=> {-# SOURCE #-} import
39       ideclQualified :: Bool,               -- ^ True => qualified
40       ideclAs        :: Maybe ModuleName,   -- ^ as Module
41       ideclHiding    :: Maybe (Bool, [LIE name]) -- ^ (True => hiding, names)
42     } deriving (Data, Typeable)
43
44 simpleImportDecl :: ModuleName -> ImportDecl name
45 simpleImportDecl mn = ImportDecl {
46       ideclName      = noLoc mn,
47       ideclPkgQual   = Nothing,
48       ideclSource    = False,
49       ideclQualified = False,
50       ideclAs        = Nothing,
51       ideclHiding    = Nothing
52     }
53 \end{code}
54
55 \begin{code}
56 instance (Outputable name) => Outputable (ImportDecl name) where
57     ppr (ImportDecl mod pkg from qual as spec)
58       = hang (hsep [ptext (sLit "import"), ppr_imp from, 
59                     pp_qual qual, pp_pkg pkg, ppr mod, pp_as as])
60              4 (pp_spec spec)
61       where
62         pp_pkg Nothing  = empty
63         pp_pkg (Just p) = doubleQuotes (ftext p)
64
65         pp_qual False   = empty
66         pp_qual True    = ptext (sLit "qualified")
67
68         pp_as Nothing   = empty
69         pp_as (Just a)  = ptext (sLit "as") <+> ppr a
70
71         ppr_imp True  = ptext (sLit "{-# SOURCE #-}")
72         ppr_imp False = empty
73
74         pp_spec Nothing             = empty
75         pp_spec (Just (False, ies)) = ppr_ies ies
76         pp_spec (Just (True,  ies)) = ptext (sLit "hiding") <+> ppr_ies ies
77
78         ppr_ies []  = ptext (sLit "()")
79         ppr_ies ies = char '(' <+> interpp'SP ies <+> char ')'
80 \end{code}
81
82 %************************************************************************
83 %*                                                                      *
84 \subsection{Imported and exported entities}
85 %*                                                                      *
86 %************************************************************************
87
88 \begin{code}
89 type LIE name = Located (IE name)
90
91 -- | Imported or exported entity.
92 data IE name
93   = IEVar               name
94   | IEThingAbs          name             -- ^ Class/Type (can't tell)
95   | IEThingAll          name             -- ^ Class/Type plus all methods/constructors
96   | IEThingWith         name [name]      -- ^ Class/Type plus some methods/constructors
97   | IEModuleContents    ModuleName       -- ^ (Export Only)
98   | IEGroup             Int HsDocString  -- ^ Doc section heading
99   | IEDoc               HsDocString      -- ^ Some documentation
100   | IEDocNamed          String           -- ^ Reference to named doc
101   deriving (Data, Typeable)
102 \end{code}
103
104 \begin{code}
105 ieName :: IE name -> name
106 ieName (IEVar n)         = n
107 ieName (IEThingAbs  n)   = n
108 ieName (IEThingWith n _) = n
109 ieName (IEThingAll  n)   = n
110 ieName _ = panic "ieName failed pattern match!"
111
112 ieNames :: IE a -> [a]
113 ieNames (IEVar            n   ) = [n]
114 ieNames (IEThingAbs       n   ) = [n]
115 ieNames (IEThingAll       n   ) = [n]
116 ieNames (IEThingWith      n ns) = n:ns
117 ieNames (IEModuleContents _   ) = []
118 ieNames (IEGroup          _ _ ) = []
119 ieNames (IEDoc            _   ) = []
120 ieNames (IEDocNamed       _   ) = []        
121 \end{code}
122
123 \begin{code}
124 instance (Outputable name) => Outputable (IE name) where
125     ppr (IEVar          var)    = pprHsVar var
126     ppr (IEThingAbs     thing)  = ppr thing
127     ppr (IEThingAll     thing)  = hcat [ppr thing, text "(..)"]
128     ppr (IEThingWith thing withs)
129         = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs)))
130     ppr (IEModuleContents mod')
131         = ptext (sLit "module") <+> ppr mod'
132     ppr (IEGroup n _)           = text ("<IEGroup: " ++ (show n) ++ ">")
133     ppr (IEDoc doc)             = ppr doc
134     ppr (IEDocNamed string)     = text ("<IEDocNamed: " ++ string ++ ">")
135 \end{code}
136
137