070526e2f75916d8c926644c98f9398f19f0cd2f
[ghc-hetmet.git] / compiler / basicTypes / Id.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[Id]{@Ids@: Value and constructor identifiers}
6
7 \begin{code}
8 module Id (
9         Id, DictId,
10
11         -- Simple construction
12         mkGlobalId, mkLocalId, mkLocalIdWithInfo, 
13         mkSysLocal, mkUserLocal, mkVanillaGlobal,
14         mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal,
15         mkWorkerId, mkExportedLocalId,
16
17         -- Taking an Id apart
18         idName, idType, idUnique, idInfo,
19         isId, globalIdDetails, idPrimRep,
20         recordSelectorFieldLabel,
21
22         -- Modifying an Id
23         setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, 
24         setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
25         zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, transferPolyIdInfo,
26
27         -- Predicates
28         isImplicitId, isDeadBinder, isDictId, isStrictId,
29         isExportedId, isLocalId, isGlobalId,
30         isRecordSelector, isNaughtyRecordSelector,
31         isClassOpId_maybe,
32         isPrimOpId, isPrimOpId_maybe, 
33         isFCallId, isFCallId_maybe,
34         isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon,
35         isBottomingId, idIsFrom,
36         isTickBoxOp, isTickBoxOp_maybe,
37         hasNoBinding, 
38
39         -- Inline pragma stuff
40         idInlinePragma, setInlinePragma, modifyInlinePragma, 
41
42
43         -- One shot lambda stuff
44         isOneShotBndr, isOneShotLambda, isStateHackType,
45         setOneShotLambda, clearOneShotLambda,
46
47         -- IdInfo stuff
48         setIdUnfolding,
49         setIdArity,
50         setIdNewDemandInfo, 
51         setIdNewStrictness, zapIdNewStrictness,
52         setIdWorkerInfo,
53         setIdSpecialisation,
54         setIdCafInfo,
55         setIdOccInfo,
56
57 #ifdef OLD_STRICTNESS
58         idDemandInfo, 
59         idStrictness, 
60         idCprInfo,
61         setIdStrictness, 
62         setIdDemandInfo, 
63         setIdCprInfo,
64 #endif
65
66         idArity, 
67         idNewDemandInfo, idNewDemandInfo_maybe,
68         idNewStrictness, idNewStrictness_maybe, 
69         idWorkerInfo,
70         idUnfolding,
71         idSpecialisation, idCoreRules, idHasRules,
72         idCafInfo,
73         idLBVarInfo,
74         idOccInfo,
75
76 #ifdef OLD_STRICTNESS
77         newStrictnessFromOld    -- Temporary
78 #endif
79
80     ) where
81
82 #include "HsVersions.h"
83
84 import CoreSyn
85 import BasicTypes
86 import qualified Var
87 import Var hiding (mkLocalId, mkGlobalId, mkExportedLocalId)
88 import TyCon
89 import Type
90 import TcType
91 import TysPrim
92 import IdInfo 
93 #ifdef OLD_STRICTNESS
94 import qualified Demand
95 #endif
96 import DataCon
97 import NewDemand
98 import Name
99 import Module
100 import Class
101 import PrimOp
102 import ForeignCall
103 import OccName
104 import Maybes
105 import SrcLoc
106 import Outputable
107 import Unique
108 import FastString
109 import StaticFlags
110
111 -- infixl so you can say (id `set` a `set` b)
112 infixl  1 `setIdUnfolding`,
113           `setIdArity`,
114           `setIdNewDemandInfo`,
115           `setIdNewStrictness`,
116           `setIdWorkerInfo`,
117           `setIdSpecialisation`,
118           `setInlinePragma`,
119           `idCafInfo`
120 #ifdef OLD_STRICTNESS
121           ,`idCprInfo`
122           ,`setIdStrictness`
123           ,`setIdDemandInfo`
124 #endif
125 \end{code}
126
127
128
129 %************************************************************************
130 %*                                                                      *
131 \subsection{Simple Id construction}
132 %*                                                                      *
133 %************************************************************************
134
135 Absolutely all Ids are made by mkId.  It is just like Var.mkId,
136 but in addition it pins free-tyvar-info onto the Id's type, 
137 where it can easily be found.
138
139 Note [Free type variables]
140 ~~~~~~~~~~~~~~~~~~~~~~~~~~
141 At one time we cached the free type variables of the type of an Id
142 at the root of the type in a TyNote.  The idea was to avoid repeating
143 the free-type-variable calculation.  But it turned out to slow down
144 the compiler overall. I don't quite know why; perhaps finding free
145 type variables of an Id isn't all that common whereas applying a 
146 substitution (which changes the free type variables) is more common.
147 Anyway, we removed it in March 2008.
148
149 \begin{code}
150 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
151 mkLocalIdWithInfo name ty info = Var.mkLocalId name ty info
152         -- Note [Free type variables]
153
154 mkExportedLocalId :: Name -> Type -> Id
155 mkExportedLocalId name ty = Var.mkExportedLocalId name ty vanillaIdInfo
156         -- Note [Free type variables]
157
158 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
159 mkGlobalId details name ty info = Var.mkGlobalId details name ty info
160 \end{code}
161
162 \begin{code}
163 mkLocalId :: Name -> Type -> Id
164 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
165
166 -- SysLocal: for an Id being created by the compiler out of thin air...
167 mkSysLocal :: FastString -> Unique -> Type -> Id
168 mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty
169
170
171 -- UserLocal: an Id with a name the user might recognize...
172 mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id
173 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
174
175 mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName    uniq occ loc) ty
176 mkVanillaGlobal             = mkGlobalId VanillaGlobal
177 \end{code}
178
179 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
180 @Uniques@, but that's OK because the templates are supposed to be
181 instantiated before use.
182  
183 \begin{code}
184 -- "Wild Id" typically used when you need a binder that you don't expect to use
185 mkWildId :: Type -> Id
186 mkWildId ty = mkSysLocal (fsLit "wild") (mkBuiltinUnique 1) ty
187
188 mkWorkerId :: Unique -> Id -> Type -> Id
189 -- A worker gets a local name.  CoreTidy will externalise it if necessary.
190 mkWorkerId uniq unwrkr ty
191   = mkLocalId wkr_name ty
192   where
193     wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcSpan unwrkr)
194
195 -- "Template locals" typically used in unfoldings
196 mkTemplateLocals :: [Type] -> [Id]
197 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
198
199 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
200 -- The Int gives the starting point for unique allocation
201 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
202
203 mkTemplateLocal :: Int -> Type -> Id
204 mkTemplateLocal i ty = mkSysLocal (fsLit "tpl") (mkBuiltinUnique i) ty
205 \end{code}
206
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection[Id-general-funs]{General @Id@-related functions}
211 %*                                                                      *
212 %************************************************************************
213
214 \begin{code}
215 setIdType :: Id -> Type -> Id
216         -- Add free tyvar info to the type
217 setIdType id ty = seqType ty `seq` Var.setIdType id ty
218
219 idPrimRep :: Id -> PrimRep
220 idPrimRep id = typePrimRep (idType id)
221 \end{code}
222
223
224 %************************************************************************
225 %*                                                                      *
226 \subsection{Special Ids}
227 %*                                                                      *
228 %************************************************************************
229
230 \begin{code}
231 recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)
232 recordSelectorFieldLabel id
233   = case globalIdDetails id of
234         RecordSelId { sel_tycon = tycon, sel_label = lbl } -> (tycon,lbl)
235         _ -> panic "recordSelectorFieldLabel"
236
237 isRecordSelector        :: Var -> Bool
238 isNaughtyRecordSelector :: Var -> Bool
239 isPrimOpId              :: Var -> Bool
240 isFCallId               :: Var -> Bool
241 isDataConWorkId         :: Var -> Bool
242 hasNoBinding            :: Var -> Bool
243
244 isClassOpId_maybe       :: Var -> Maybe Class
245 isPrimOpId_maybe        :: Var -> Maybe PrimOp
246 isFCallId_maybe         :: Var -> Maybe ForeignCall
247 isDataConWorkId_maybe   :: Var -> Maybe DataCon
248
249 isRecordSelector id = case globalIdDetails id of
250                         RecordSelId {}  -> True
251                         _               -> False
252
253 isNaughtyRecordSelector id = case globalIdDetails id of
254                         RecordSelId { sel_naughty = n } -> n
255                         _                               -> False
256
257 isClassOpId_maybe id = case globalIdDetails id of
258                         ClassOpId cls -> Just cls
259                         _other        -> Nothing
260
261 isPrimOpId id = case globalIdDetails id of
262                         PrimOpId _ -> True
263                         _          -> False
264
265 isPrimOpId_maybe id = case globalIdDetails id of
266                         PrimOpId op -> Just op
267                         _           -> Nothing
268
269 isFCallId id = case globalIdDetails id of
270                         FCallId _ -> True
271                         _         -> False
272
273 isFCallId_maybe id = case globalIdDetails id of
274                         FCallId call -> Just call
275                         _            -> Nothing
276
277 isDataConWorkId id = case globalIdDetails id of
278                         DataConWorkId _ -> True
279                         _               -> False
280
281 isDataConWorkId_maybe id = case globalIdDetails id of
282                         DataConWorkId con -> Just con
283                         _                 -> Nothing
284
285 isDataConId_maybe :: Id -> Maybe DataCon
286 isDataConId_maybe id = case globalIdDetails id of
287                          DataConWorkId con -> Just con
288                          DataConWrapId con -> Just con
289                          _                 -> Nothing
290
291 idDataCon :: Id -> DataCon
292 -- Get from either the worker or the wrapper to the DataCon
293 -- Currently used only in the desugarer
294 --       INVARIANT: idDataCon (dataConWrapId d) = d
295 -- (Remember, dataConWrapId can return either the wrapper or the worker.)
296 idDataCon id = case globalIdDetails id of
297                   DataConWorkId con -> con
298                   DataConWrapId con -> con
299                   _                 -> pprPanic "idDataCon" (ppr id)
300
301
302 isDictId :: Id -> Bool
303 isDictId id = isDictTy (idType id)
304
305 -- hasNoBinding returns True of an Id which may not have a
306 -- binding, even though it is defined in this module.  
307 -- Data constructor workers used to be things of this kind, but
308 -- they aren't any more.  Instead, we inject a binding for 
309 -- them at the CorePrep stage. 
310 -- EXCEPT: unboxed tuples, which definitely have no binding
311 hasNoBinding id = case globalIdDetails id of
312                         PrimOpId _       -> True        -- See Note [Primop wrappers]
313                         FCallId _        -> True
314                         DataConWorkId dc -> isUnboxedTupleCon dc
315                         _                -> False
316
317 isImplicitId :: Id -> Bool
318         -- isImplicitId tells whether an Id's info is implied by other
319         -- declarations, so we don't need to put its signature in an interface
320         -- file, even if it's mentioned in some other interface unfolding.
321 isImplicitId id
322   = case globalIdDetails id of
323         RecordSelId {}  -> True
324         FCallId _       -> True
325         PrimOpId _      -> True
326         ClassOpId _     -> True
327         DataConWorkId _ -> True
328         DataConWrapId _ -> True
329                 -- These are are implied by their type or class decl;
330                 -- remember that all type and class decls appear in the interface file.
331                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
332                 -- it carries version info for the instance decl
333         _               -> False
334
335 idIsFrom :: Module -> Id -> Bool
336 idIsFrom mod id = nameIsLocalOrFrom mod (idName id)
337 \end{code}
338
339 Note [Primop wrappers]
340 ~~~~~~~~~~~~~~~~~~~~~~
341 Currently hasNoBinding claims that PrimOpIds don't have a curried
342 function definition.  But actually they do, in GHC.PrimopWrappers,
343 which is auto-generated from prelude/primops.txt.pp.  So actually, hasNoBinding
344 could return 'False' for PrimOpIds.
345
346 But we'd need to add something in CoreToStg to swizzle any unsaturated
347 applications of GHC.Prim.plusInt# to GHC.PrimopWrappers.plusInt#.
348
349 Nota Bene: GHC.PrimopWrappers is needed *regardless*, because it's
350 used by GHCi, which does not implement primops direct at all.
351
352
353
354 \begin{code}
355 isDeadBinder :: Id -> Bool
356 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
357                   | otherwise = False   -- TyVars count as not dead
358 \end{code}
359
360 \begin{code}
361 isTickBoxOp :: Id -> Bool
362 isTickBoxOp id = 
363   case globalIdDetails id of
364     TickBoxOpId _    -> True
365     _                -> False
366
367 isTickBoxOp_maybe :: Id -> Maybe TickBoxOp
368 isTickBoxOp_maybe id = 
369   case globalIdDetails id of
370     TickBoxOpId tick -> Just tick
371     _                -> Nothing
372 \end{code}
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection{IdInfo stuff}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381         ---------------------------------
382         -- ARITY
383 idArity :: Id -> Arity
384 idArity id = arityInfo (idInfo id)
385
386 setIdArity :: Id -> Arity -> Id
387 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
388
389 #ifdef OLD_STRICTNESS
390         ---------------------------------
391         -- (OLD) STRICTNESS 
392 idStrictness :: Id -> StrictnessInfo
393 idStrictness id = strictnessInfo (idInfo id)
394
395 setIdStrictness :: Id -> StrictnessInfo -> Id
396 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
397 #endif
398
399 -- isBottomingId returns true if an application to n args would diverge
400 isBottomingId :: Id -> Bool
401 isBottomingId id = isBottomingSig (idNewStrictness id)
402
403 idNewStrictness_maybe :: Id -> Maybe StrictSig
404 idNewStrictness :: Id -> StrictSig
405
406 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
407 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
408
409 setIdNewStrictness :: Id -> StrictSig -> Id
410 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
411
412 zapIdNewStrictness :: Id -> Id
413 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
414 \end{code}
415
416 This predicate says whether the id has a strict demand placed on it or
417 has a type such that it can always be evaluated strictly (e.g., an
418 unlifted type, but see the comment for isStrictType).  We need to
419 check separately whether <id> has a so-called "strict type" because if
420 the demand for <id> hasn't been computed yet but <id> has a strict
421 type, we still want (isStrictId <id>) to be True.
422 \begin{code}
423 isStrictId :: Id -> Bool
424 isStrictId id
425   = ASSERT2( isId id, text "isStrictId: not an id: " <+> ppr id )
426            (isStrictDmd (idNewDemandInfo id)) || 
427            (isStrictType (idType id))
428
429         ---------------------------------
430         -- WORKER ID
431 idWorkerInfo :: Id -> WorkerInfo
432 idWorkerInfo id = workerInfo (idInfo id)
433
434 setIdWorkerInfo :: Id -> WorkerInfo -> Id
435 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
436
437         ---------------------------------
438         -- UNFOLDING
439 idUnfolding :: Id -> Unfolding
440 idUnfolding id = unfoldingInfo (idInfo id)
441
442 setIdUnfolding :: Id -> Unfolding -> Id
443 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
444
445 #ifdef OLD_STRICTNESS
446         ---------------------------------
447         -- (OLD) DEMAND
448 idDemandInfo :: Id -> Demand.Demand
449 idDemandInfo id = demandInfo (idInfo id)
450
451 setIdDemandInfo :: Id -> Demand.Demand -> Id
452 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
453 #endif
454
455 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
456 idNewDemandInfo       :: Id -> NewDemand.Demand
457
458 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
459 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
460
461 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
462 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
463
464         ---------------------------------
465         -- SPECIALISATION
466 idSpecialisation :: Id -> SpecInfo
467 idSpecialisation id = specInfo (idInfo id)
468
469 idCoreRules :: Id -> [CoreRule]
470 idCoreRules id = specInfoRules (idSpecialisation id)
471
472 idHasRules :: Id -> Bool
473 idHasRules id = not (isEmptySpecInfo (idSpecialisation id))
474
475 setIdSpecialisation :: Id -> SpecInfo -> Id
476 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
477
478         ---------------------------------
479         -- CAF INFO
480 idCafInfo :: Id -> CafInfo
481 #ifdef OLD_STRICTNESS
482 idCafInfo id = case cgInfo (idInfo id) of
483                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
484                   info     -> cgCafInfo info
485 #else
486 idCafInfo id = cafInfo (idInfo id)
487 #endif
488
489 setIdCafInfo :: Id -> CafInfo -> Id
490 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
491
492         ---------------------------------
493         -- CPR INFO
494 #ifdef OLD_STRICTNESS
495 idCprInfo :: Id -> CprInfo
496 idCprInfo id = cprInfo (idInfo id)
497
498 setIdCprInfo :: Id -> CprInfo -> Id
499 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
500 #endif
501
502         ---------------------------------
503         -- Occcurrence INFO
504 idOccInfo :: Id -> OccInfo
505 idOccInfo id = occInfo (idInfo id)
506
507 setIdOccInfo :: Id -> OccInfo -> Id
508 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
509 \end{code}
510
511
512         ---------------------------------
513         -- INLINING
514 The inline pragma tells us to be very keen to inline this Id, but it's still
515 OK not to if optimisation is switched off.
516
517 \begin{code}
518 idInlinePragma :: Id -> InlinePragInfo
519 idInlinePragma id = inlinePragInfo (idInfo id)
520
521 setInlinePragma :: Id -> InlinePragInfo -> Id
522 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
523
524 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
525 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
526 \end{code}
527
528
529         ---------------------------------
530         -- ONE-SHOT LAMBDAS
531 \begin{code}
532 idLBVarInfo :: Id -> LBVarInfo
533 idLBVarInfo id = lbvarInfo (idInfo id)
534
535 isOneShotBndr :: Id -> Bool
536 -- This one is the "business end", called externally.
537 -- Its main purpose is to encapsulate the Horrible State Hack
538 isOneShotBndr id = isOneShotLambda id || isStateHackType (idType id)
539
540 isStateHackType :: Type -> Bool
541 isStateHackType ty
542   | opt_NoStateHack 
543   = False
544   | otherwise
545   = case splitTyConApp_maybe ty of
546         Just (tycon,_) -> tycon == statePrimTyCon
547         _              -> False
548         -- This is a gross hack.  It claims that 
549         -- every function over realWorldStatePrimTy is a one-shot
550         -- function.  This is pretty true in practice, and makes a big
551         -- difference.  For example, consider
552         --      a `thenST` \ r -> ...E...
553         -- The early full laziness pass, if it doesn't know that r is one-shot
554         -- will pull out E (let's say it doesn't mention r) to give
555         --      let lvl = E in a `thenST` \ r -> ...lvl...
556         -- When `thenST` gets inlined, we end up with
557         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
558         -- and we don't re-inline E.
559         --
560         -- It would be better to spot that r was one-shot to start with, but
561         -- I don't want to rely on that.
562         --
563         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
564         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
565
566
567 -- The OneShotLambda functions simply fiddle with the IdInfo flag
568 isOneShotLambda :: Id -> Bool
569 isOneShotLambda id = case idLBVarInfo id of
570                        IsOneShotLambda  -> True
571                        NoLBVarInfo      -> False
572
573 setOneShotLambda :: Id -> Id
574 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
575
576 clearOneShotLambda :: Id -> Id
577 clearOneShotLambda id 
578   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
579   | otherwise          = id                     
580
581 -- But watch out: this may change the type of something else
582 --      f = \x -> e
583 -- If we change the one-shot-ness of x, f's type changes
584 \end{code}
585
586 \begin{code}
587 zapInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id
588 zapInfo zapper id = maybeModifyIdInfo (zapper (idInfo id)) id
589
590 zapLamIdInfo :: Id -> Id
591 zapLamIdInfo = zapInfo zapLamInfo
592
593 zapDemandIdInfo :: Id -> Id
594 zapDemandIdInfo = zapInfo zapDemandInfo
595
596 zapFragileIdInfo :: Id -> Id
597 zapFragileIdInfo = zapInfo zapFragileInfo 
598 \end{code}
599
600 Note [transferPolyIdInfo]
601 ~~~~~~~~~~~~~~~~~~~~~~~~~
602 Suppose we have
603
604    f = /\a. let g = rhs in ...
605
606 where g has interesting strictness information.  Then if we float thus
607
608    g' = /\a. rhs
609    f = /\a. ...[g' a/g]
610
611 we *do not* want to lose the strictness information on g.  Nor arity.
612
613 It's simple to retain strictness and arity, but not so simple to retain
614         worker info
615         rules
616 so we simply discard those.  Sooner or later this may bite us.
617
618 This transfer is used in two places: 
619         FloatOut (long-distance let-floating)
620         SimplUtils.abstractFloats (short-distance let-floating)
621
622 \begin{code}
623 transferPolyIdInfo :: Id -> Id -> Id
624 transferPolyIdInfo old_id new_id
625   = modifyIdInfo transfer new_id
626   where
627     old_info = idInfo old_id
628     transfer new_info = new_info `setNewStrictnessInfo` (newStrictnessInfo old_info)
629                                  `setArityInfo` (arityInfo old_info)
630 \end{code}
631