{-# LANGUAGE DeriveFunctor #-}
-- | This data structure holds an updateable environment which is used
-- when compiling module loops.
module GHC.Driver.Env.KnotVars( KnotVars(..)
                              , emptyKnotVars
                              , knotVarsFromModuleEnv
                              , knotVarElems
                              , lookupKnotVars
                              , knotVarsWithout
                              ) where

import GHC.Prelude
import GHC.Unit.Types ( Module )
import GHC.Unit.Module.Env
import Data.Maybe
import GHC.Utils.Outputable

-- See Note [Why is KnotVars not a ModuleEnv]
-- See Note [KnotVars invariants]
data KnotVars a = KnotVars { forall a. KnotVars a -> [Module]
kv_domain :: [Module] -- Domain of the function , Note [KnotVars: Why store the domain?]
                           -- Invariant: kv_lookup is surjective relative to kv_domain
                           , forall a. KnotVars a -> Module -> Maybe a
kv_lookup :: Module -> Maybe a -- Lookup function
                           }
                | NoKnotVars
                           deriving (forall a b. (a -> b) -> KnotVars a -> KnotVars b)
-> (forall a b. a -> KnotVars b -> KnotVars a) -> Functor KnotVars
forall a b. a -> KnotVars b -> KnotVars a
forall a b. (a -> b) -> KnotVars a -> KnotVars b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> KnotVars a -> KnotVars b
fmap :: forall a b. (a -> b) -> KnotVars a -> KnotVars b
$c<$ :: forall a b. a -> KnotVars b -> KnotVars a
<$ :: forall a b. a -> KnotVars b -> KnotVars a
Functor

instance Outputable (KnotVars a) where
  ppr :: KnotVars a -> SDoc
ppr KnotVars a
NoKnotVars = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NoKnot"
  ppr (KnotVars [Module]
dom Module -> Maybe a
_lookup) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Knotty:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [Module] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Module]
dom

emptyKnotVars :: KnotVars a
emptyKnotVars :: forall a. KnotVars a
emptyKnotVars = KnotVars a
forall a. KnotVars a
NoKnotVars

knotVarsFromModuleEnv :: ModuleEnv a -> KnotVars a
knotVarsFromModuleEnv :: forall a. ModuleEnv a -> KnotVars a
knotVarsFromModuleEnv ModuleEnv a
me | ModuleEnv a -> Bool
forall a. ModuleEnv a -> Bool
isEmptyModuleEnv ModuleEnv a
me = KnotVars a
forall a. KnotVars a
NoKnotVars
knotVarsFromModuleEnv ModuleEnv a
me = [Module] -> (Module -> Maybe a) -> KnotVars a
forall a. [Module] -> (Module -> Maybe a) -> KnotVars a
KnotVars (ModuleEnv a -> [Module]
forall a. ModuleEnv a -> [Module]
moduleEnvKeys ModuleEnv a
me) (ModuleEnv a -> Module -> Maybe a
forall a. ModuleEnv a -> Module -> Maybe a
lookupModuleEnv ModuleEnv a
me)

knotVarElems :: KnotVars a -> [a]
knotVarElems :: forall a. KnotVars a -> [a]
knotVarElems (KnotVars [Module]
keys Module -> Maybe a
lookup) = (Module -> Maybe a) -> [Module] -> [a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Module -> Maybe a
lookup [Module]
keys
knotVarElems KnotVars a
NoKnotVars = []

lookupKnotVars :: KnotVars a -> Module -> Maybe a
lookupKnotVars :: forall a. KnotVars a -> Module -> Maybe a
lookupKnotVars (KnotVars [Module]
_ Module -> Maybe a
lookup) Module
x = Module -> Maybe a
lookup Module
x
lookupKnotVars KnotVars a
NoKnotVars Module
_ = Maybe a
forall a. Maybe a
Nothing

knotVarsWithout :: Module -> KnotVars a -> KnotVars a
knotVarsWithout :: forall a. Module -> KnotVars a -> KnotVars a
knotVarsWithout Module
this_mod (KnotVars [Module]
loop_mods Module -> Maybe a
lkup) = [Module] -> (Module -> Maybe a) -> KnotVars a
forall a. [Module] -> (Module -> Maybe a) -> KnotVars a
KnotVars
  ((Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filter (Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
this_mod) [Module]
loop_mods)
  (\Module
that_mod -> if Module
that_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
this_mod then Maybe a
forall a. Maybe a
Nothing else Module -> Maybe a
lkup Module
that_mod)
knotVarsWithout Module
_ KnotVars a
NoKnotVars = KnotVars a
forall a. KnotVars a
NoKnotVars

{-
Note [Why is KnotVars not a ModuleEnv]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Initially 'KnotVars' was just a 'ModuleEnv a' but there is one tricky use of
the data structure in 'mkDsEnvs' which required this generalised structure.

In interactive mode the TypeEnvs from all the previous statements are merged
together into one big TypeEnv. 'dsLookupVar' relies on `tcIfaceVar'. The normal
lookup functions either look in the HPT or EPS but there is no entry for the `Ghci<N>` modules
in either, so the whole merged TypeEnv for all previous Ghci* is stored in the
`if_rec_types` variable and then lookup checks there in the case of any interactive module.

This is a misuse of the `if_rec_types` variable which might be fixed in future if the
Ghci<N> modules are just placed into the HPT like normal modules with implicit imports
between them.

Note [KnotVars: Why store the domain?]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Normally there's a 'Module' at hand to tell us which 'TypeEnv' we want to interrogate
at a particular time, apart from one case, when constructing the in-scope set
when linting an unfolding. In this case the whole environment is needed to tell us
everything that's in-scope at top-level in the loop because whilst we are linting unfoldings
the top-level identifiers from modules in the cycle might not be globalised properly yet.

This could be refactored so that the lint functions knew about 'KnotVars' and delayed
this check until deciding whether a variable was local or not.


Note [KnotVars invariants]
~~~~~~~~~~~~~~~~~~~~~~~~~~

There is a simple invariant which should hold for the KnotVars constructor:

* At the end of upsweep, there should be no live KnotVars

This invariant is difficult to test but easy to check using ghc-debug. The usage of
NoKnotVars is intended to make this invariant easier to check.

The most common situation where a KnotVars is retained accidentally is if a HscEnv
which contains reference to a KnotVars is used during interface file loading. The
thunks created during this process will retain a reference to the KnotVars. In theory,
all these references should be removed by 'maybeRehydrateAfter' as that rehydrates all
interface files in the loop without using KnotVars.

At the time of writing (MP: Oct 21) the invariant doesn't actually hold but also
doesn't seem to have too much of a negative consequence on compiler residency.
In theory it could be quite bad as each KnotVars may retain a stale reference to an entire TypeEnv.

See #20491
-}