78e417c6e66fcba4d1ed13d8131c6536244b8075
[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 import Char             ( isAlpha )
25 \end{code}
26
27 %************************************************************************
28 %*                                                                      *
29 \subsection{Import and export declaration lists}
30 %*                                                                      *
31 %************************************************************************
32
33 One per \tr{import} declaration in a module.
34 \begin{code}
35 type LImportDecl name = Located (ImportDecl name)
36
37 data ImportDecl name
38   = ImportDecl    (Located ModuleName)          -- module name
39                   Bool                          -- True <=> {-# SOURCE #-} import
40                   Bool                          -- True => qualified
41                   (Maybe ModuleName)            -- as Module
42                   (Maybe (Bool, [LIE name]))    -- (True => hiding, names)
43 \end{code}
44
45 \begin{code}
46 instance (Outputable name) => Outputable (ImportDecl name) where
47     ppr (ImportDecl mod from qual as spec)
48       = hang (hsep [ptext (sLit "import"), ppr_imp from, 
49                     pp_qual qual, ppr mod, pp_as as])
50              4 (pp_spec spec)
51       where
52         pp_qual False   = empty
53         pp_qual True    = ptext (sLit "qualified")
54
55         pp_as Nothing   = empty
56         pp_as (Just a)  = ptext (sLit "as ") <+> ppr a
57
58         ppr_imp True  = ptext (sLit "{-# SOURCE #-}")
59         ppr_imp False = empty
60
61         pp_spec Nothing = empty
62         pp_spec (Just (False, spec))
63                         = parens (interpp'SP spec)
64         pp_spec (Just (True, spec))
65                         = ptext (sLit "hiding") <+> parens (interpp'SP spec)
66
67 ideclName :: ImportDecl name -> Located ModuleName
68 ideclName (ImportDecl mod_nm _ _ _ _) = mod_nm
69 \end{code}
70
71 %************************************************************************
72 %*                                                                      *
73 \subsection{Imported and exported entities}
74 %*                                                                      *
75 %************************************************************************
76
77 \begin{code}
78 type LIE name = Located (IE name)
79
80 data IE name
81   = IEVar               name
82   | IEThingAbs          name             -- Class/Type (can't tell)
83   | IEThingAll          name             -- Class/Type plus all methods/constructors
84   | IEThingWith         name [name]      -- Class/Type plus some methods/constructors
85   | IEModuleContents    ModuleName       -- (Export Only)
86   | IEGroup             Int (HsDoc name) -- Doc section heading
87   | IEDoc               (HsDoc name)     -- Some documentation
88   | IEDocNamed          String           -- Reference to named doc
89 \end{code}
90
91 \begin{code}
92 ieName :: IE name -> name
93 ieName (IEVar n)         = n
94 ieName (IEThingAbs  n)   = n
95 ieName (IEThingWith n _) = n
96 ieName (IEThingAll  n)   = n
97
98 ieNames :: IE a -> [a]
99 ieNames (IEVar            n   ) = [n]
100 ieNames (IEThingAbs       n   ) = [n]
101 ieNames (IEThingAll       n   ) = [n]
102 ieNames (IEThingWith      n ns) = n:ns
103 ieNames (IEModuleContents _   ) = []
104 ieNames (IEGroup          _ _ ) = []
105 ieNames (IEDoc            _   ) = []
106 ieNames (IEDocNamed       _   ) = []        
107 \end{code}
108
109 \begin{code}
110 instance (Outputable name) => Outputable (IE name) where
111     ppr (IEVar          var)    = pprHsVar var
112     ppr (IEThingAbs     thing)  = ppr thing
113     ppr (IEThingAll     thing)  = hcat [ppr thing, text "(..)"]
114     ppr (IEThingWith thing withs)
115         = ppr thing <> parens (fsep (punctuate comma (map pprHsVar withs)))
116     ppr (IEModuleContents mod)
117         = ptext (sLit "module") <+> ppr mod
118     ppr (IEGroup n _)           = text ("<IEGroup: " ++ (show n) ++ ">")
119     ppr (IEDoc doc)             = ppr doc
120     ppr (IEDocNamed string)     = text ("<IEDocNamed: " ++ string ++ ">")
121 \end{code}
122
123 \begin{code}
124 pprHsVar :: Outputable name => name -> SDoc
125 pprHsVar v | isOperator ppr_v = parens ppr_v
126            | otherwise        = ppr_v
127            where
128              ppr_v = ppr v
129
130 isOperator :: SDoc -> Bool
131 isOperator ppr_v 
132   = case showSDocUnqual ppr_v of
133         ('(':_)   -> False              -- (), (,) etc
134         ('[':_)   -> False              -- []
135         ('$':c:_) -> not (isAlpha c)    -- Don't treat $d as an operator
136         (':':c:_) -> not (isAlpha c)    -- Don't treat :T as an operator
137         ('_':_)   -> False              -- Not an operator
138         (c:_)     -> not (isAlpha c)    -- Starts with non-alpha
139         _         -> False
140     -- We use (showSDoc (ppr v)), rather than isSymOcc (getOccName v) simply so
141     -- that we don't need NamedThing in the context of all these functions.
142     -- Gruesome, but simple.
143 \end{code}
144