1 {-# LANGUAGE ViewPatterns #-}
5 This module contains code which maintains and manipulates the
6 fixity environment during renaming.
9 module RnFixity
( MiniFixityEnv
,
11 lookupFixityRn
, lookupFixityRn_help
,
12 lookupFieldFixityRn
, lookupTyFixityRn
) where
24 import BasicTypes
( Fixity
(..), FixityDirection
(..), minPrecedence
,
25 defaultFixity
, SourceText
(..) )
30 import Data
.Function
( on
)
34 *********************************************************
38 *********************************************************
40 Note [Fixity signature lookup]
41 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
42 A fixity declaration like
46 can refer to a value-level operator, e.g.:
48 (?) :: String -> String -> String
50 or a type-level operator, like:
52 data (?) a b = A a | B b
54 so we extend the lookup of the reader name '?' to the TcClsName namespace, as
55 well as the original namespace.
57 The extended lookup is also used in other places, like resolution of
58 deprecation declarations, and lookup of names in GHCi.
61 --------------------------------
62 type MiniFixityEnv
= FastStringEnv
(Located Fixity
)
63 -- Mini fixity env for the names we're about
64 -- to bind, in a single binding group
66 -- It is keyed by the *FastString*, not the *OccName*, because
67 -- the single fixity decl infix 3 T
68 -- affects both the data constructor T and the type constrctor T
70 -- We keep the location so that if we find
71 -- a duplicate, we can report it sensibly
73 --------------------------------
74 -- Used for nested fixity decls to bind names along with their fixities.
75 -- the fixities are given as a UFM from an OccName's FastString to a fixity decl
77 addLocalFixities
:: MiniFixityEnv
-> [Name
] -> RnM a
-> RnM a
78 addLocalFixities mini_fix_env names thing_inside
79 = extendFixityEnv
(mapMaybe find_fixity names
) thing_inside
82 = case lookupFsEnv mini_fix_env
(occNameFS occ
) of
83 Just lfix
-> Just
(name
, FixItem occ
(unLoc lfix
))
86 occ
= nameOccName name
89 --------------------------------
90 lookupFixity is a bit strange.
92 * Nested local fixity decls are put in the local fixity env, which we
95 * Imported fixities are found in the PIT
97 * Top-level fixity decls in this module may be for Names that are
98 either Global (constructors, class operations)
99 or Local/Exported (everything else)
100 (See notes with RnNames.getLocalDeclBinders for why we have this split.)
101 We put them all in the local fixity environment
104 lookupFixityRn
:: Name
-> RnM Fixity
105 lookupFixityRn name
= lookupFixityRn
' name
(nameOccName name
)
107 lookupFixityRn
' :: Name
-> OccName
-> RnM Fixity
108 lookupFixityRn
' name
= fmap snd . lookupFixityRn_help
' name
110 -- | 'lookupFixityRn_help' returns @(True, fixity)@ if it finds a 'Fixity'
111 -- in a local environment or from an interface file. Otherwise, it returns
112 -- @(False, fixity)@ (e.g., for unbound 'Name's or 'Name's without
113 -- user-supplied fixity declarations).
114 lookupFixityRn_help
:: Name
115 -> RnM
(Bool, Fixity
)
116 lookupFixityRn_help name
=
117 lookupFixityRn_help
' name
(nameOccName name
)
119 lookupFixityRn_help
' :: Name
121 -> RnM
(Bool, Fixity
)
122 lookupFixityRn_help
' name occ
124 = return (False, Fixity NoSourceText minPrecedence InfixL
)
125 -- Minimise errors from ubound names; eg
127 -- where 'foo' is not in scope, should not give an error (Trac #7937)
130 = do { local_fix_env
<- getFixityEnv
131 ; case lookupNameEnv local_fix_env name
of {
132 Just
(FixItem _ fix
) -> return (True, fix
) ;
135 do { this_mod
<- getModule
136 ; if nameIsLocalOrFrom this_mod name
137 -- Local (and interactive) names are all in the
138 -- fixity env, and don't have entries in the HPT
139 then return (False, defaultFixity
)
140 else lookup_imported
} } }
143 -- For imported names, we have to get their fixities by doing a
144 -- loadInterfaceForName, and consulting the Ifaces that comes back
145 -- from that, because the interface file for the Name might not
146 -- have been loaded yet. Why not? Suppose you import module A,
147 -- which exports a function 'f', thus;
148 -- module CurrentModule where
150 -- module A( f ) where
152 -- Then B isn't loaded right away (after all, it's possible that
153 -- nothing from B will be used). When we come across a use of
154 -- 'f', we need to know its fixity, and it's then, and only
155 -- then, that we load B.hi. That is what's happening here.
157 -- loadInterfaceForName will find B.hi even if B is a hidden module,
158 -- and that's what we want.
159 = do { iface
<- loadInterfaceForName doc name
160 ; let mb_fix
= mi_fix_fn iface occ
161 ; let msg
= case mb_fix
of
163 text
"looking up name" <+> ppr name
164 <+> text
"in iface, but found no fixity for it."
165 <+> text
"Using default fixity instead."
167 text
"looking up name in iface and found:"
168 <+> vcat
[ppr name
, ppr f
]
169 ; traceRn
"lookupFixityRn_either:" msg
170 ; return (maybe (False, defaultFixity
) (\f -> (True, f
)) mb_fix
) }
172 doc
= text
"Checking fixity for" <+> ppr name
175 lookupTyFixityRn
:: Located Name
-> RnM Fixity
176 lookupTyFixityRn
= lookupFixityRn
. unLoc
178 -- | Look up the fixity of a (possibly ambiguous) occurrence of a record field
179 -- selector. We use 'lookupFixityRn'' so that we can specifiy the 'OccName' as
180 -- the field label, which might be different to the 'OccName' of the selector
181 -- 'Name' if @DuplicateRecordFields@ is in use (Trac #1173). If there are
182 -- multiple possible selectors with different fixities, generate an error.
183 lookupFieldFixityRn
:: AmbiguousFieldOcc GhcRn
-> RnM Fixity
184 lookupFieldFixityRn
(Unambiguous n lrdr
)
185 = lookupFixityRn
' n
(rdrNameOcc
(unLoc lrdr
))
186 lookupFieldFixityRn
(Ambiguous _ lrdr
) = get_ambiguous_fixity
(unLoc lrdr
)
188 get_ambiguous_fixity
:: RdrName
-> RnM Fixity
189 get_ambiguous_fixity rdr_name
= do
190 traceRn
"get_ambiguous_fixity" (ppr rdr_name
)
191 rdr_env
<- getGlobalRdrEnv
192 let elts
= lookupGRE_RdrName rdr_name rdr_env
194 fixities
<- groupBy ((==) `on`
snd) . zip elts
195 <$> mapM lookup_gre_fixity elts
198 -- There should always be at least one fixity.
199 -- Something's very wrong if there are no fixity candidates, so panic
200 [] -> panic
"get_ambiguous_fixity: no candidates for a given RdrName"
201 [ (_
, fix
):_
] -> return fix
202 ambigs
-> addErr
(ambiguous_fixity_err rdr_name ambigs
)
203 >> return (Fixity NoSourceText minPrecedence InfixL
)
205 lookup_gre_fixity gre
= lookupFixityRn
' (gre_name gre
) (greOccName gre
)
207 ambiguous_fixity_err rn ambigs
208 = vcat
[ text
"Ambiguous fixity for record field" <+> quotes
(ppr rn
)
209 , hang
(text
"Conflicts: ") 2 . vcat
.
210 map format_ambig
$ concat ambigs
]
212 format_ambig
(elt
, fix
) = hang
(ppr fix
)
213 2 (pprNameProvenance elt
)
214 lookupFieldFixityRn
(XAmbiguousFieldOcc
{}) = panic
"lookupFieldFixityRn"