[project @ 2004-01-05 08:20: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 SrcLoc           ( Located(..), unLoc )
18 \end{code}
19
20 %************************************************************************
21 %*                                                                      *
22 \subsection{Free variables}
23 %*                                                                      *
24 %************************************************************************
25
26 These free-variable finders returns tycons and classes too.
27
28 \begin{code}
29 charTyCon_name, listTyCon_name, parrTyCon_name :: Name
30 charTyCon_name    = getName charTyCon
31 listTyCon_name    = getName listTyCon
32 parrTyCon_name    = getName parrTyCon
33
34 tupleTyCon_name :: Boxity -> Int -> Name
35 tupleTyCon_name boxity n = getName (tupleTyCon boxity n)
36
37 extractHsTyVars :: LHsType Name -> NameSet
38 extractHsTyVars x = filterNameSet isTyVarName (extractHsTyNames x)
39
40 extractFunDepNames :: FunDep Name -> NameSet
41 extractFunDepNames (ns1, ns2) = mkNameSet ns1 `unionNameSets` mkNameSet ns2
42
43 extractHsTyNames   :: LHsType Name -> NameSet
44 extractHsTyNames ty
45   = getl ty
46   where
47     getl (L _ ty) = get ty
48
49     get (HsAppTy ty1 ty2)      = getl ty1 `unionNameSets` getl ty2
50     get (HsListTy ty)          = unitNameSet listTyCon_name `unionNameSets` getl ty
51     get (HsPArrTy ty)          = unitNameSet parrTyCon_name `unionNameSets` getl ty
52     get (HsTupleTy con tys)    = extractHsTyNames_s tys
53     get (HsFunTy ty1 ty2)      = getl ty1 `unionNameSets` getl ty2
54     get (HsPredTy p)           = extractHsPredTyNames (unLoc p)
55     get (HsOpTy ty1 op ty2)    = getl ty1 `unionNameSets` getl ty2 `unionNameSets` unitNameSet (unLoc op)
56     get (HsParTy ty)           = getl ty
57     get (HsNumTy n)            = emptyNameSet
58     get (HsTyVar tv)           = unitNameSet tv
59     get (HsSpliceTy _)         = emptyNameSet   -- Type splices mention no type variables
60     get (HsKindSig ty k)       = getl ty
61     get (HsForAllTy _ tvs 
62                     ctxt ty)   = (extractHsCtxtTyNames ctxt
63                                          `unionNameSets` getl ty)
64                                             `minusNameSet`
65                                   mkNameSet (hsLTyVarNames tvs)
66
67 extractHsTyNames_s  :: [LHsType Name] -> NameSet
68 extractHsTyNames_s tys = foldr (unionNameSets . extractHsTyNames) emptyNameSet tys
69
70 extractHsCtxtTyNames :: LHsContext Name -> NameSet
71 extractHsCtxtTyNames (L _ ctxt)
72   = foldr (unionNameSets . extractHsPredTyNames . unLoc) emptyNameSet ctxt
73
74 -- You don't import or export implicit parameters,
75 -- so don't mention the IP names
76 extractHsPredTyNames (HsClassP cls tys)
77   = unitNameSet cls `unionNameSets` extractHsTyNames_s tys
78 extractHsPredTyNames (HsIParam n ty)
79   = extractHsTyNames ty
80 \end{code}
81
82
83 %************************************************************************
84 %*                                                                      *
85 \subsection{Free variables of declarations}
86 %*                                                                      *
87 %************************************************************************
88
89 Return the Names that must be in scope if we are to use this declaration.
90 In all cases this is set up for interface-file declarations:
91         - for class decls we ignore the bindings
92         - for instance decls likewise, plus the pragmas
93         - for rule decls, we ignore HsRules
94         - for data decls, we ignore derivings
95
96         *** See "THE NAMING STORY" in HsDecls ****
97
98 \begin{code}
99 ----------------
100 hsSigsFVs :: [LSig Name] -> FreeVars
101 hsSigsFVs sigs = plusFVs (map (hsSigFVs.unLoc) sigs)
102
103 hsSigFVs (Sig v ty)         = extractHsTyNames ty
104 hsSigFVs (SpecInstSig ty)   = extractHsTyNames ty
105 hsSigFVs (SpecSig v ty)     = extractHsTyNames ty
106 hsSigFVs other              = emptyFVs
107
108 ----------------
109 conDeclFVs (L _ (ConDecl _ tyvars context details))
110   = delFVs (map hsLTyVarName tyvars) $
111     extractHsCtxtTyNames context          `plusFV`
112     conDetailsFVs details
113
114 conDetailsFVs (PrefixCon btys)    = plusFVs (map bangTyFVs btys)
115 conDetailsFVs (InfixCon bty1 bty2) = bangTyFVs bty1 `plusFV` bangTyFVs bty2
116 conDetailsFVs (RecCon flds)        = plusFVs [bangTyFVs bty | (_, bty) <- flds]
117
118 bangTyFVs bty = extractHsTyNames (getBangType (unLoc bty))
119 \end{code}
120
121
122 %************************************************************************
123 %*                                                                      *
124 \subsection{A few functions on generic defintions
125 %*                                                                      *
126 %************************************************************************
127
128 These functions on generics are defined over Matches Name, which is
129 why they are here and not in HsMatches.
130
131 \begin{code}
132 maybeGenericMatch :: LMatch Name -> Maybe (HsType Name, LMatch Name)
133   -- Tells whether a Match is for a generic definition
134   -- and extract the type from a generic match and put it at the front
135
136 maybeGenericMatch (L loc (Match (L _ (TypePat (L _ ty)) : pats) sig_ty grhss))
137   = Just (ty, L loc (Match pats sig_ty grhss))
138
139 maybeGenericMatch other_match = Nothing
140 \end{code}