[project @ 2003-10-09 11:58:39 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnHsSyn.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1996-1998
3 %
4 \section[RnHsSyn]{Specialisations of the @HsSyn@ syntax for the renamer}
5
6 \begin{code}
7 module RnHsSyn where
8
9 #include "HsVersions.h"
10
11 import HsSyn
12 import Class            ( FunDep )
13 import TysWiredIn       ( tupleTyCon, listTyCon, parrTyCon, charTyCon )
14 import Name             ( Name, getName, isTyVarName )
15 import NameSet
16 import BasicTypes       ( Boxity )
17 import Outputable
18 \end{code}
19
20
21 \begin{code}
22 type RenamedHsDecl              = HsDecl                Name
23 type RenamedArithSeqInfo        = ArithSeqInfo          Name
24 type RenamedClassOpSig          = Sig                   Name
25 type RenamedConDecl             = ConDecl               Name
26 type RenamedContext             = HsContext             Name
27 type RenamedRuleDecl            = RuleDecl              Name
28 type RenamedTyClDecl            = TyClDecl              Name
29 type RenamedDefaultDecl         = DefaultDecl           Name
30 type RenamedForeignDecl         = ForeignDecl           Name
31 type RenamedGRHS                = GRHS                  Name
32 type RenamedGRHSs               = GRHSs                 Name
33 type RenamedHsBinds             = HsBinds               Name
34 type RenamedHsExpr              = HsExpr                Name
35 type RenamedInstDecl            = InstDecl              Name
36 type RenamedMatchContext        = HsMatchContext        Name
37 type RenamedMatch               = Match                 Name
38 type RenamedMonoBinds           = MonoBinds             Name
39 type RenamedPat                 = InPat                 Name
40 type RenamedHsType              = HsType                Name
41 type RenamedHsPred              = HsPred                Name
42 type RenamedRecordBinds         = HsRecordBinds         Name
43 type RenamedSig                 = Sig                   Name
44 type RenamedStmt                = Stmt                  Name
45 type RenamedFixitySig           = FixitySig             Name
46 type RenamedDeprecation         = DeprecDecl            Name
47 type RenamedHsCmd               = HsCmd                 Name
48 type RenamedHsCmdTop            = HsCmdTop              Name
49 \end{code}
50
51 %************************************************************************
52 %*                                                                      *
53 \subsection{Free variables}
54 %*                                                                      *
55 %************************************************************************
56
57 These free-variable finders returns tycons and classes too.
58
59 \begin{code}
60 charTyCon_name, listTyCon_name, parrTyCon_name :: Name
61 charTyCon_name    = getName charTyCon
62 listTyCon_name    = getName listTyCon
63 parrTyCon_name    = getName parrTyCon
64
65 tupleTyCon_name :: Boxity -> Int -> Name
66 tupleTyCon_name boxity n = getName (tupleTyCon boxity n)
67
68 extractHsTyVars :: RenamedHsType -> NameSet
69 extractHsTyVars x = filterNameSet isTyVarName (extractHsTyNames x)
70
71 extractFunDepNames :: FunDep Name -> NameSet
72 extractFunDepNames (ns1, ns2) = mkNameSet ns1 `unionNameSets` mkNameSet ns2
73
74 extractHsTyNames   :: RenamedHsType -> NameSet
75 extractHsTyNames ty
76   = get ty
77   where
78     get (HsAppTy ty1 ty2)      = get ty1 `unionNameSets` get ty2
79     get (HsListTy ty)          = unitNameSet listTyCon_name `unionNameSets` get ty
80     get (HsPArrTy ty)          = unitNameSet parrTyCon_name `unionNameSets` get ty
81     get (HsTupleTy con tys)    = extractHsTyNames_s tys
82     get (HsFunTy ty1 ty2)      = get ty1 `unionNameSets` get ty2
83     get (HsPredTy p)           = extractHsPredTyNames p
84     get (HsOpTy ty1 op ty2)    = get ty1 `unionNameSets` get ty2 `unionNameSets` unitNameSet op
85     get (HsParTy ty)           = get ty
86     get (HsNumTy n)            = emptyNameSet
87     get (HsTyVar tv)           = unitNameSet tv
88     get (HsKindSig ty k)       = get ty
89     get (HsForAllTy (Just tvs) 
90                     ctxt ty)   = (extractHsCtxtTyNames ctxt `unionNameSets` get ty)
91                                             `minusNameSet`
92                                   mkNameSet (hsTyVarNames tvs)
93     get ty@(HsForAllTy Nothing _ _) = pprPanic "extractHsTyNames" (ppr ty)
94
95 extractHsTyNames_s  :: [RenamedHsType] -> NameSet
96 extractHsTyNames_s tys = foldr (unionNameSets . extractHsTyNames) emptyNameSet tys
97
98 extractHsCtxtTyNames :: RenamedContext -> NameSet
99 extractHsCtxtTyNames ctxt = foldr (unionNameSets . extractHsPredTyNames) emptyNameSet ctxt
100
101 -- You don't import or export implicit parameters,
102 -- so don't mention the IP names
103 extractHsPredTyNames (HsClassP cls tys)
104   = unitNameSet cls `unionNameSets` extractHsTyNames_s tys
105 extractHsPredTyNames (HsIParam n ty)
106   = extractHsTyNames ty
107 \end{code}
108
109
110 %************************************************************************
111 %*                                                                      *
112 \subsection{Free variables of declarations}
113 %*                                                                      *
114 %************************************************************************
115
116 Return the Names that must be in scope if we are to use this declaration.
117 In all cases this is set up for interface-file declarations:
118         - for class decls we ignore the bindings
119         - for instance decls likewise, plus the pragmas
120         - for rule decls, we ignore HsRules
121         - for data decls, we ignore derivings
122
123         *** See "THE NAMING STORY" in HsDecls ****
124
125 \begin{code}
126 ----------------
127 hsSigsFVs sigs = plusFVs (map hsSigFVs sigs)
128
129 hsSigFVs (Sig v ty _)       = extractHsTyNames ty
130 hsSigFVs (SpecInstSig ty _) = extractHsTyNames ty
131 hsSigFVs (SpecSig v ty _)   = extractHsTyNames ty
132 hsSigFVs other              = emptyFVs
133
134 ----------------
135 conDeclFVs (ConDecl _ tyvars context details _)
136   = delFVs (map hsTyVarName tyvars) $
137     extractHsCtxtTyNames context          `plusFV`
138     conDetailsFVs details
139
140 conDetailsFVs (PrefixCon btys)    = plusFVs (map bangTyFVs btys)
141 conDetailsFVs (InfixCon bty1 bty2) = bangTyFVs bty1 `plusFV` bangTyFVs bty2
142 conDetailsFVs (RecCon flds)        = plusFVs [bangTyFVs bty | (_, bty) <- flds]
143
144 bangTyFVs bty = extractHsTyNames (getBangType bty)
145 \end{code}
146
147
148 %************************************************************************
149 %*                                                                      *
150 \subsection{A few functions on generic defintions
151 %*                                                                      *
152 %************************************************************************
153
154 These functions on generics are defined over RenamedMatches, which is
155 why they are here and not in HsMatches.
156
157 \begin{code}
158 maybeGenericMatch :: RenamedMatch -> Maybe (RenamedHsType, RenamedMatch)
159   -- Tells whether a Match is for a generic definition
160   -- and extract the type from a generic match and put it at the front
161
162 maybeGenericMatch (Match (TypePat ty : pats) sig_ty grhss)
163   = Just (ty, Match pats sig_ty grhss)
164
165 maybeGenericMatch other_match = Nothing
166 \end{code}