never executed always true always false
1 {-# LANGUAGE DeriveFunctor #-}
2 -- | This data structure holds an updateable environment which is used
3 -- when compiling module loops.
4 module GHC.Driver.Env.KnotVars( KnotVars(..)
5 , emptyKnotVars
6 , knotVarsFromModuleEnv
7 , knotVarElems
8 , lookupKnotVars
9 , knotVarsWithout
10 ) where
11
12 import GHC.Prelude
13 import GHC.Unit.Types ( Module )
14 import GHC.Unit.Module.Env
15 import Data.Maybe
16 import GHC.Utils.Outputable
17
18 -- See Note [Why is KnotVars not a ModuleEnv]
19 -- See Note [KnotVars invariants]
20 data KnotVars a = KnotVars { kv_domain :: [Module] -- Domain of the function , Note [KnotVars: Why store the domain?]
21 -- Invariant: kv_lookup is surjective relative to kv_domain
22 , kv_lookup :: Module -> Maybe a -- Lookup function
23 }
24 | NoKnotVars
25 deriving Functor
26
27 instance Outputable (KnotVars a) where
28 ppr NoKnotVars = text "NoKnot"
29 ppr (KnotVars dom _lookup) = text "Knotty:" <+> ppr dom
30
31 emptyKnotVars :: KnotVars a
32 emptyKnotVars = NoKnotVars
33
34 knotVarsFromModuleEnv :: ModuleEnv a -> KnotVars a
35 knotVarsFromModuleEnv me | isEmptyModuleEnv me = NoKnotVars
36 knotVarsFromModuleEnv me = KnotVars (moduleEnvKeys me) (lookupModuleEnv me)
37
38 knotVarElems :: KnotVars a -> [a]
39 knotVarElems (KnotVars keys lookup) = mapMaybe lookup keys
40 knotVarElems NoKnotVars = []
41
42 lookupKnotVars :: KnotVars a -> Module -> Maybe a
43 lookupKnotVars (KnotVars _ lookup) x = lookup x
44 lookupKnotVars NoKnotVars _ = Nothing
45
46 knotVarsWithout :: Module -> KnotVars a -> KnotVars a
47 knotVarsWithout this_mod (KnotVars loop_mods lkup) = KnotVars
48 (filter (/= this_mod) loop_mods)
49 (\that_mod -> if that_mod == this_mod then Nothing else lkup that_mod)
50 knotVarsWithout _ NoKnotVars = NoKnotVars
51
52 {-
53 Note [Why is KnotVars not a ModuleEnv]
54 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
55
56 Initially 'KnotVars' was just a 'ModuleEnv a' but there is one tricky use of
57 the data structure in 'mkDsEnvs' which required this generalised structure.
58
59 In interactive mode the TypeEnvs from all the previous statements are merged
60 togethed into one big TypeEnv. 'dsLookupVar' relies on `tcIfaceVar'. The normal
61 lookup functions either look in the HPT or EPS but there is no entry for the `Ghci<N>` modules
62 in either, so the whole merged TypeEnv for all previous Ghci* is stored in the
63 `if_rec_types` variable and then lookup checks there in the case of any interactive module.
64
65 This is a misuse of the `if_rec_types` variable which might be fixed in future if the
66 Ghci<N> modules are just placed into the HPT like normal modules with implicit imports
67 between them.
68
69 Note [KnotVars: Why store the domain?]
70 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
71
72 Normally there's a 'Module' at hand to tell us which 'TypeEnv' we want to interrogate
73 at a particular time, apart from one case, when constructing the in-scope set
74 when linting an unfolding. In this case the whole environemnt is needed to tell us
75 everything that's in-scope at top-level in the loop because whilst we are linting unfoldings
76 the top-level identifiers from modules in the cycle might not be globalised properly yet.
77
78 This could be refactored so that the lint functions knew about 'KnotVars' and delayed
79 this check until deciding whether a variable was local or not.
80
81
82 Note [KnotVars invariants]
83 ~~~~~~~~~~~~~~~~~~~~~~~~~~
84
85 There is a simple invariant which should hold for the KnotVars constructor:
86
87 * At the end of upsweep, there should be no live KnotVars
88
89 This invariant is difficult to test but easy to check using ghc-debug. The usage of
90 NoKnotVars is intended to make this invariant easier to check.
91
92 The most common situation where a KnotVars is retained accidently is if a HscEnv
93 which contains reference to a KnotVars is used during interface file loading. The
94 thunks created during this process will retain a reference to the KnotVars. In theory,
95 all these references should be removed by 'typecheckLoop' as that retypechecks all
96 interface files in the loop without using KnotVars.
97
98 At the time of writing (MP: Oct 21) the invariant doesn't actually hold but also
99 doesn't seem to have too much of a negative consequence on compiler residency.
100 In theory it could be quite bad as each KnotVars may retain a stale reference to an entire TypeEnv.
101
102 See #20491
103 -}
104