2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 \section[HsBinds]{Abstract syntax: top-level bindings and signatures}
6 Datatype for: @HsBinds@, @Bind@, @Sig@, @MonoBinds@.
11 #include "HsVersions.h"
13 import {-# SOURCE #-} HsExpr ( HsExpr, pprExpr,
18 import HsImpExp ( ppr_var )
19 import HsTypes ( HsType )
20 import CoreSyn ( CoreExpr )
21 import PprCore ( {- instance Outputable (Expr a) -} )
25 import PrelNames ( isUnboundName )
26 import NameSet ( NameSet, elemNameSet, nameSetToList )
27 import BasicTypes ( RecFlag(..), Fixity )
29 import SrcLoc ( SrcLoc )
31 import Class ( DefMeth (..) )
34 %************************************************************************
36 \subsection{Bindings: @HsBinds@}
38 %************************************************************************
40 The following syntax may produce new syntax which is not part of the input,
41 and which is instead a translation of the input to the typechecker.
42 Syntax translations are marked TRANSLATION in comments. New empty
43 productions are useful in development but may not appear in the final
46 Collections of bindings, created by dependency analysis and translation:
49 data HsBinds id pat -- binders and bindees
52 | ThenBinds (HsBinds id pat)
55 | MonoBind (MonoBinds id pat)
56 [Sig id] -- Empty on typechecker output
61 nullBinds :: HsBinds id pat -> Bool
63 nullBinds EmptyBinds = True
64 nullBinds (ThenBinds b1 b2) = nullBinds b1 && nullBinds b2
65 nullBinds (MonoBind b _ _) = nullMonoBinds b
67 mkMonoBind :: MonoBinds id pat -> [Sig id] -> RecFlag -> HsBinds id pat
68 mkMonoBind EmptyMonoBinds _ _ = EmptyBinds
69 mkMonoBind mbinds sigs is_rec = MonoBind mbinds sigs is_rec
73 instance (Outputable pat, Outputable id) =>
74 Outputable (HsBinds id pat) where
75 ppr binds = ppr_binds binds
77 ppr_binds EmptyBinds = empty
78 ppr_binds (ThenBinds binds1 binds2)
79 = ppr_binds binds1 $$ ppr_binds binds2
80 ppr_binds (MonoBind bind sigs is_rec)
86 ppr_isrec = getPprStyle $ \ sty ->
87 if userStyle sty then empty else
89 Recursive -> ptext SLIT("{- rec -}")
90 NonRecursive -> ptext SLIT("{- nonrec -}")
93 %************************************************************************
95 \subsection{Bindings: @MonoBinds@}
97 %************************************************************************
99 Global bindings (where clauses)
102 data MonoBinds id pat
105 | AndMonoBinds (MonoBinds id pat)
108 | FunMonoBind id -- Used for both functions f x = e
109 -- and variables f = \x -> e
110 -- Reason: the Match stuff lets us have an optional
111 -- result type sig f :: a->a = ...mentions a...
112 Bool -- True => infix declaration
116 | PatMonoBind pat -- The pattern is never a simple variable;
117 -- That case is done by FunMonoBind
121 | VarMonoBind id -- TRANSLATION
124 | CoreMonoBind id -- TRANSLATION
125 CoreExpr -- No zonking; this is a final CoreExpr with Ids and Types!
127 | AbsBinds -- Binds abstraction; TRANSLATION
128 [TyVar] -- Type variables
130 [([TyVar], id, id)] -- (type variables, polymorphic, momonmorphic) triples
131 NameSet -- Set of *polymorphic* variables that have an INLINE pragma
132 (MonoBinds id pat) -- The "business end"
134 -- Creates bindings for *new* (polymorphic, overloaded) locals
135 -- in terms of *old* (monomorphic, non-overloaded) ones.
137 -- See section 9 of static semantics paper for more details.
138 -- (You can get a PhD for explaining the True Meaning
139 -- of this last construct.)
151 f1p = /\ tvs -> \ [d1,d2] -> letrec DBINDS and BIND
154 gp = ...same again, with gm instead of fm
156 This is a pretty bad translation, because it duplicates all the bindings.
157 So the desugarer tries to do a better job:
159 fp = /\ [a,b] -> \ [d1,d2] -> case tp [a,b] [d1,d2] of
163 p = /\ [a,b] -> \ [d1,d2] -> letrec DBINDS and BIND
167 -- We keep the invariant that a MonoBinds is only empty
168 -- if it is exactly EmptyMonoBinds
170 nullMonoBinds :: MonoBinds id pat -> Bool
171 nullMonoBinds EmptyMonoBinds = True
172 nullMonoBinds other_monobind = False
174 andMonoBinds :: MonoBinds id pat -> MonoBinds id pat -> MonoBinds id pat
175 andMonoBinds EmptyMonoBinds mb = mb
176 andMonoBinds mb EmptyMonoBinds = mb
177 andMonoBinds mb1 mb2 = AndMonoBinds mb1 mb2
179 andMonoBindList :: [MonoBinds id pat] -> MonoBinds id pat
180 andMonoBindList binds
183 loop1 [] = EmptyMonoBinds
184 loop1 (EmptyMonoBinds : binds) = loop1 binds
185 loop1 (b:bs) = loop2 b bs
189 loop2 acc (EmptyMonoBinds : bs) = loop2 acc bs
190 loop2 acc (b:bs) = loop2 (acc `AndMonoBinds` b) bs
195 instance (Outputable id, Outputable pat) =>
196 Outputable (MonoBinds id pat) where
197 ppr mbind = ppr_monobind mbind
200 ppr_monobind :: (Outputable id, Outputable pat) => MonoBinds id pat -> SDoc
201 ppr_monobind EmptyMonoBinds = empty
202 ppr_monobind (AndMonoBinds binds1 binds2)
203 = ppr_monobind binds1 $$ ppr_monobind binds2
205 ppr_monobind (PatMonoBind pat grhss locn) = pprPatBind pat grhss
206 ppr_monobind (FunMonoBind fun inf matches locn) = pprFunBind fun matches
207 -- ToDo: print infix if appropriate
209 ppr_monobind (VarMonoBind name expr)
210 = sep [ppr name <+> equals, nest 4 (pprExpr expr)]
212 ppr_monobind (CoreMonoBind name expr)
213 = sep [ppr name <+> equals, nest 4 (ppr expr)]
215 ppr_monobind (AbsBinds tyvars dictvars exports inlines val_binds)
216 = sep [ptext SLIT("AbsBinds"),
217 brackets (interpp'SP tyvars),
218 brackets (interpp'SP dictvars),
219 brackets (sep (punctuate comma (map ppr exports))),
220 brackets (interpp'SP (nameSetToList inlines))]
222 nest 4 (ppr val_binds)
225 %************************************************************************
227 \subsection{@Sig@: type signatures and value-modifying user pragmas}
229 %************************************************************************
231 It is convenient to lump ``value-modifying'' user-pragmas (e.g.,
232 ``specialise this function to these four types...'') in with type
233 signatures. Then all the machinery to move them into place, etc.,
238 = Sig name -- a bog-std type signature
242 | ClassOpSig name -- Selector name
243 (DefMeth name) -- Default-method info
244 -- See "THE NAMING STORY" in HsDecls
248 | SpecSig name -- specialise a function or datatype ...
249 (HsType name) -- ... to these types
252 | InlineSig name -- INLINE f
256 | NoInlineSig name -- NOINLINE f
260 | SpecInstSig (HsType name) -- (Class tys); should be a specialisation of the
261 -- current instance decl
264 | FixSig (FixitySig name) -- Fixity declaration
267 data FixitySig name = FixitySig name Fixity SrcLoc
269 instance Eq name => Eq (FixitySig name) where
270 (FixitySig n1 f1 _) == (FixitySig n2 f2 _) = n1==n2 && f1==f2
274 okBindSig :: NameSet -> Sig Name -> Bool
275 okBindSig ns (ClassOpSig _ _ _ _) = False
276 okBindSig ns sig = sigForThisGroup ns sig
278 okClsDclSig :: NameSet -> Sig Name -> Bool
279 okClsDclSig ns (Sig _ _ _) = False
280 okClsDclSig ns sig = sigForThisGroup ns sig
282 okInstDclSig :: NameSet -> Sig Name -> Bool
283 okInstDclSig ns (Sig _ _ _) = False
284 okInstDclSig ns (FixSig _) = False
285 okInstDclSig ns (SpecInstSig _ _) = True
286 okInstDclSig ns sig = sigForThisGroup ns sig
288 sigForThisGroup ns sig
289 = case sigName sig of
291 Just n | isUnboundName n -> True -- Don't complain about an unbound name again
292 | otherwise -> n `elemNameSet` ns
294 sigName :: Sig name -> Maybe name
295 sigName (Sig n _ _) = Just n
296 sigName (ClassOpSig n _ _ _) = Just n
297 sigName (SpecSig n _ _) = Just n
298 sigName (InlineSig n _ _) = Just n
299 sigName (NoInlineSig n _ _) = Just n
300 sigName (FixSig (FixitySig n _ _)) = Just n
301 sigName other = Nothing
303 isFixitySig :: Sig name -> Bool
304 isFixitySig (FixSig _) = True
305 isFixitySig _ = False
307 isClassOpSig :: Sig name -> Bool
308 isClassOpSig (ClassOpSig _ _ _ _) = True
309 isClassOpSig _ = False
311 isPragSig :: Sig name -> Bool
312 -- Identifies pragmas
313 isPragSig (SpecSig _ _ _) = True
314 isPragSig (InlineSig _ _ _) = True
315 isPragSig (NoInlineSig _ _ _) = True
316 isPragSig (SpecInstSig _ _) = True
317 isPragSig other = False
321 hsSigDoc (Sig _ _ loc) = (SLIT("type signature"),loc)
322 hsSigDoc (ClassOpSig _ _ _ loc) = (SLIT("class-method type signature"), loc)
323 hsSigDoc (SpecSig _ _ loc) = (SLIT("SPECIALISE pragma"),loc)
324 hsSigDoc (InlineSig _ _ loc) = (SLIT("INLINE pragma"),loc)
325 hsSigDoc (NoInlineSig _ _ loc) = (SLIT("NOINLINE pragma"),loc)
326 hsSigDoc (SpecInstSig _ loc) = (SLIT("SPECIALISE instance pragma"),loc)
327 hsSigDoc (FixSig (FixitySig _ _ loc)) = (SLIT("fixity declaration"), loc)
331 instance (Outputable name) => Outputable (Sig name) where
332 ppr sig = ppr_sig sig
334 ppr_sig :: Outputable name => Sig name -> SDoc
335 ppr_sig (Sig var ty _)
336 = sep [ppr var <+> dcolon, nest 4 (ppr ty)]
338 ppr_sig (ClassOpSig var dm ty _)
339 = getPprStyle $ \ sty ->
341 then sep [ ppr var <+> pp_dm <+> dcolon, nest 4 (ppr ty) ]
342 else sep [ ppr_var var <+> dcolon,
344 nest 4 (pp_dm_comment) ]
347 DefMeth _ -> equals -- Default method indicator
348 GenDefMeth -> semi -- Generic method indicator
349 NoDefMeth -> empty -- No Method at all
350 pp_dm_comment = case dm of
351 DefMeth _ -> text "{- has default method -}"
352 GenDefMeth -> text "{- has generic method -}"
353 NoDefMeth -> empty -- No Method at all
355 ppr_sig (SpecSig var ty _)
356 = sep [ hsep [text "{-# SPECIALIZE", ppr var, dcolon],
357 nest 4 (ppr ty <+> text "#-}")
360 ppr_sig (InlineSig var phase _)
361 = hsep [text "{-# INLINE", ppr_phase phase, ppr var, text "#-}"]
363 ppr_sig (NoInlineSig var phase _)
364 = hsep [text "{-# NOINLINE", ppr_phase phase, ppr var, text "#-}"]
366 ppr_sig (SpecInstSig ty _)
367 = hsep [text "{-# SPECIALIZE instance", ppr ty, text "#-}"]
369 ppr_sig (FixSig fix_sig) = ppr fix_sig
372 instance Outputable name => Outputable (FixitySig name) where
373 ppr (FixitySig name fixity loc) = sep [ppr fixity, ppr name]
375 ppr_phase :: Maybe Int -> SDoc
376 ppr_phase Nothing = empty
377 ppr_phase (Just n) = int n
380 Checking for distinct signatures; oh, so boring
384 eqHsSig :: Sig Name -> Sig Name -> Bool
385 eqHsSig (Sig n1 _ _) (Sig n2 _ _) = n1 == n2
386 eqHsSig (InlineSig n1 _ _) (InlineSig n2 _ _) = n1 == n2
387 eqHsSig (NoInlineSig n1 _ _) (NoInlineSig n2 _ _) = n1 == n2
389 eqHsSig (SpecInstSig ty1 _) (SpecInstSig ty2 _) = ty1 == ty2
390 eqHsSig (SpecSig n1 ty1 _) (SpecSig n2 ty2 _) =
391 -- may have many specialisations for one value;
392 -- but not ones that are exactly the same...
393 (n1 == n2) && (ty1 == ty2)
395 eqHsSig _other1 _other2 = False