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