Haddockify 'IE'.
[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 {-# OPTIONS -fno-warn-incomplete-patterns #-}
10 -- The above warning supression flag is a temporary kludge.
11 -- While working on this module you are encouraged to remove it and fix
12 -- any warnings in the module. See
13 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
14 -- for details
15
16 module HsImpExp where
17
18 import Module           ( ModuleName )
19 import HsDoc            ( HsDoc )
20
21 import Outputable
22 import FastString
23 import SrcLoc           ( Located(..) )
24 \end{code}
25
26 %************************************************************************
27 %*                                                                      *
28 \subsection{Import and export declaration lists}
29 %*                                                                      *
30 %************************************************************************
31
32 One per \tr{import} declaration in a module.
33 \begin{code}
34 type LImportDecl name = Located (ImportDecl name)
35
36 -- | A single Haskell @import@ declaration.
37 data ImportDecl name
38   = ImportDecl {
39       ideclName      :: Located ModuleName, -- ^ Module name.
40       ideclPkgQual   :: Maybe FastString,   -- ^ Package qualifier.
41       ideclSource    :: Bool,               -- ^ True <=> {-# SOURCE #-} import
42       ideclQualified :: Bool,               -- ^ True => qualified
43       ideclAs        :: Maybe ModuleName,   -- ^ as Module
44       ideclHiding    :: Maybe (Bool, [LIE name]) -- ^ (True => hiding, names)
45     }
46 \end{code}
47
48 \begin{code}
49 instance (Outputable name) => Outputable (ImportDecl name) where
50     ppr (ImportDecl mod pkg from qual as spec)
51       = hang (hsep [ptext (sLit "import"), ppr_imp from, 
52                     pp_qual qual, pp_pkg pkg, ppr mod, pp_as as])
53              4 (pp_spec spec)
54       where
55         pp_pkg Nothing  = empty
56         pp_pkg (Just p) = doubleQuotes (ftext p)
57
58         pp_qual False   = empty
59         pp_qual True    = ptext (sLit "qualified")
60
61         pp_as Nothing   = empty
62         pp_as (Just a)  = ptext (sLit "as ") <+> ppr a
63
64         ppr_imp True  = ptext (sLit "{-# SOURCE #-}")
65         ppr_imp False = empty
66
67         pp_spec Nothing = empty
68         pp_spec (Just (False, spec))
69                         = parens (interpp'SP spec)
70         pp_spec (Just (True, spec))
71                         = ptext (sLit "hiding") <+> parens (interpp'SP spec)
72 \end{code}
73
74 %************************************************************************
75 %*                                                                      *
76 \subsection{Imported and exported entities}
77 %*                                                                      *
78 %************************************************************************
79
80 \begin{code}
81 type LIE name = Located (IE name)
82
83 -- | Imported or exported entity.
84 data IE name
85   = IEVar               name
86   | IEThingAbs          name             -- ^ Class/Type (can't tell)
87   | IEThingAll          name             -- ^ Class/Type plus all methods/constructors
88   | IEThingWith         name [name]      -- ^ Class/Type plus some methods/constructors
89   | IEModuleContents    ModuleName       -- ^ (Export Only)
90   | IEGroup             Int (HsDoc name) -- ^ Doc section heading
91   | IEDoc               (HsDoc name)     -- ^ Some documentation
92   | IEDocNamed          String           -- ^ Reference to named doc
93 \end{code}
94
95 \begin{code}
96 ieName :: IE name -> name
97 ieName (IEVar n)         = n
98 ieName (IEThingAbs  n)   = n
99 ieName (IEThingWith n _) = n
100 ieName (IEThingAll  n)   = n
101
102 ieNames :: IE a -> [a]
103 ieNames (IEVar            n   ) = [n]
104 ieNames (IEThingAbs       n   ) = [n]
105 ieNames (IEThingAll       n   ) = [n]
106 ieNames (IEThingWith      n ns) = n:ns
107 ieNames (IEModuleContents _   ) = []
108 ieNames (IEGroup          _ _ ) = []
109 ieNames (IEDoc            _   ) = []
110 ieNames (IEDocNamed       _   ) = []        
111 \end{code}
112
113 \begin{code}
114 instance (Outputable name) => Outputable (IE name) where
115     ppr (IEVar          var)    = pprHsVar var
116     ppr (IEThingAbs     thing)  = ppr thing
117     ppr (IEThingAll     thing)  = hcat [ppr thing, text "(..)"]
118     ppr (IEThingWith thing withs)
119         = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs)))
120     ppr (IEModuleContents mod)
121         = ptext (sLit "module") <+> ppr mod
122     ppr (IEGroup n _)           = text ("<IEGroup: " ++ (show n) ++ ">")
123     ppr (IEDoc doc)             = ppr doc
124     ppr (IEDocNamed string)     = text ("<IEDocNamed: " ++ string ++ ">")
125 \end{code}
126
127