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