{-# LANGUAGE TupleSections #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.StgToJS.Deps
-- Copyright   :  (c) The University of Glasgow 2001
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Jeffrey Young  <jeffrey.young@iohk.io>
--                Luite Stegeman <luite.stegeman@iohk.io>
--                Sylvain Henry  <sylvain.henry@iohk.io>
--                Josh Meredith  <josh.meredith@iohk.io>
-- Stability   :  experimental
--
-- Module to calculate the transitive dependencies of a module
-----------------------------------------------------------------------------

module GHC.StgToJS.Deps
  ( genDependencyData
  )
where

import GHC.Prelude

import GHC.StgToJS.Object
import GHC.StgToJS.Types
import GHC.StgToJS.Ids

import GHC.JS.Ident

import GHC.Types.Id
import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Types.Name

import GHC.Unit.Module

import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic

import GHC.Data.FastString

import Data.Map (Map)
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.IntSet as IS
import qualified GHC.Data.Word64Map as WM
import GHC.Data.Word64Map (Word64Map)
import Data.Array
import Data.Word
import Control.Monad

import Control.Monad.Trans.Class
import Control.Monad.Trans.State

data DependencyDataCache = DDC
  { DependencyDataCache -> Word64Map Unit
ddcModule :: !(Word64Map Unit)               -- ^ Unique Module -> Unit
  , DependencyDataCache -> Word64Map ExportedFun
ddcId     :: !(Word64Map ExportedFun)        -- ^ Unique Id     -> ExportedFun (only to other modules)
  , DependencyDataCache -> Map OtherSymb ExportedFun
ddcOther  :: !(Map OtherSymb ExportedFun)
  }

-- | Generate module dependency data
--
-- Generate the object's dependency data, taking care that package and module names
-- are only stored once
genDependencyData
  :: HasDebugCallStack
  => Module
  -> [LinkableUnit]
  -> G BlockInfo
genDependencyData :: HasDebugCallStack => Module -> [LinkableUnit] -> G BlockInfo
genDependencyData Module
mod [LinkableUnit]
units = do
    ds <- StateT
  DependencyDataCache G [(Int, BlockDeps, Bool, [ExportedFun])]
-> DependencyDataCache
-> StateT GenState IO [(Int, BlockDeps, Bool, [ExportedFun])]
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (((LinkableUnit, Int)
 -> StateT
      DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun]))
-> [(LinkableUnit, Int)]
-> StateT
     DependencyDataCache G [(Int, BlockDeps, Bool, [ExportedFun])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((LinkableUnit
 -> Int
 -> StateT
      DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun]))
-> (LinkableUnit, Int)
-> StateT
     DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun])
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry LinkableUnit
-> Int
-> StateT
     DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun])
oneDep) [(LinkableUnit, Int)]
blocks)
                     (Word64Map Unit
-> Word64Map ExportedFun
-> Map OtherSymb ExportedFun
-> DependencyDataCache
DDC Word64Map Unit
forall a. Word64Map a
WM.empty Word64Map ExportedFun
forall a. Word64Map a
WM.empty Map OtherSymb ExportedFun
forall k a. Map k a
M.empty)
    return $ BlockInfo
      { bi_module     = mod
      , bi_must_link  = IS.fromList [ n | (n, _, True, _) <- ds ]
      , bi_exports    = M.fromList $ (\(Int
n,BlockDeps
_,Bool
_,[ExportedFun]
es) -> (ExportedFun -> (ExportedFun, Int))
-> [ExportedFun] -> [(ExportedFun, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (,Int
n) [ExportedFun]
es) =<< ds
      , bi_block_deps = listArray (0, length blocks-1) (map (\(Int
_,BlockDeps
deps,Bool
_,[ExportedFun]
_) -> BlockDeps
deps) ds)
      }
  where
      -- Id -> Block
      unitIdExports :: UniqFM Id Int
      unitIdExports :: UniqFM Id Int
unitIdExports = [(Id, Int)] -> UniqFM Id Int
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM ([(Id, Int)] -> UniqFM Id Int) -> [(Id, Int)] -> UniqFM Id Int
forall a b. (a -> b) -> a -> b
$
                      ((LinkableUnit, Int) -> [(Id, Int)])
-> [(LinkableUnit, Int)] -> [(Id, Int)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(LinkableUnit
u,Int
n) -> (Id -> (Id, Int)) -> [Id] -> [(Id, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (,Int
n) (LinkableUnit -> [Id]
luIdExports LinkableUnit
u)) [(LinkableUnit, Int)]
blocks

      -- OtherSymb -> Block
      unitOtherExports :: Map OtherSymb Int
      unitOtherExports :: Map OtherSymb Int
unitOtherExports = [(OtherSymb, Int)] -> Map OtherSymb Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(OtherSymb, Int)] -> Map OtherSymb Int)
-> [(OtherSymb, Int)] -> Map OtherSymb Int
forall a b. (a -> b) -> a -> b
$
                         ((LinkableUnit, Int) -> [(OtherSymb, Int)])
-> [(LinkableUnit, Int)] -> [(OtherSymb, Int)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(LinkableUnit
u,Int
n) -> (OtherSymb -> (OtherSymb, Int))
-> [OtherSymb] -> [(OtherSymb, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (,Int
n)
                                                  ((FastString -> OtherSymb) -> [FastString] -> [OtherSymb]
forall a b. (a -> b) -> [a] -> [b]
map (Module -> FastString -> OtherSymb
OtherSymb Module
mod)
                                                       (LinkableUnit -> [FastString]
luOtherExports LinkableUnit
u)))
                                   [(LinkableUnit, Int)]
blocks

      blocks :: [(LinkableUnit, Int)]
      blocks :: [(LinkableUnit, Int)]
blocks = [LinkableUnit] -> [Int] -> [(LinkableUnit, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [LinkableUnit]
units [Int
0..]

      -- generate the list of exports and set of dependencies for one unit
      oneDep :: LinkableUnit
             -> Int
             -> StateT DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun])
      oneDep :: LinkableUnit
-> Int
-> StateT
     DependencyDataCache G (Int, BlockDeps, Bool, [ExportedFun])
oneDep (LinkableUnit ObjBlock
_ [Id]
idExports [FastString]
otherExports [Id]
idDeps [Unique]
pseudoIdDeps [OtherSymb]
otherDeps Bool
req [ForeignJSRef]
_frefs) Int
n = do
        (edi, bdi) <- (Id -> StateT DependencyDataCache G (Either ExportedFun Int))
-> [Id] -> StateT DependencyDataCache G ([ExportedFun], [Int])
forall (m :: * -> *) a b c.
Monad m =>
(a -> m (Either b c)) -> [a] -> m ([b], [c])
partitionWithM (Int -> Id -> StateT DependencyDataCache G (Either ExportedFun Int)
lookupIdFun Int
n) [Id]
idDeps
        (edo, bdo) <- partitionWithM lookupOtherFun otherDeps
        (edp, bdp) <- partitionWithM (lookupPseudoIdFun n) pseudoIdDeps
        expi <- mapM lookupExportedId (filter isExportedId idExports)
        expo <- mapM lookupExportedOther otherExports
        -- fixme thin deps, remove all transitive dependencies!
        let bdeps = BlockDeps
                      { blockBlockDeps :: [Int]
blockBlockDeps = BlockIds -> [Int]
IS.toList (BlockIds -> [Int]) -> ([Int] -> BlockIds) -> [Int] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> BlockIds
IS.fromList ([Int] -> BlockIds) -> ([Int] -> [Int]) -> [Int] -> BlockIds
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/=Int
n) ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ [Int]
bdi[Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++[Int]
bdo[Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++[Int]
bdp
                      , blockFunDeps :: [ExportedFun]
blockFunDeps   = Set ExportedFun -> [ExportedFun]
forall a. Set a -> [a]
S.toList (Set ExportedFun -> [ExportedFun])
-> ([ExportedFun] -> Set ExportedFun)
-> [ExportedFun]
-> [ExportedFun]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ExportedFun] -> Set ExportedFun
forall a. Ord a => [a] -> Set a
S.fromList ([ExportedFun] -> [ExportedFun]) -> [ExportedFun] -> [ExportedFun]
forall a b. (a -> b) -> a -> b
$ [ExportedFun]
edi[ExportedFun] -> [ExportedFun] -> [ExportedFun]
forall a. [a] -> [a] -> [a]
++[ExportedFun]
edo[ExportedFun] -> [ExportedFun] -> [ExportedFun]
forall a. [a] -> [a] -> [a]
++[ExportedFun]
edp
                      }
        return (n, bdeps, req, expi++expo)

      idModule :: Id -> Maybe Module
      idModule :: Id -> Maybe Module
idModule Id
i = Name -> Maybe Module
nameModule_maybe (Id -> Name
forall a. NamedThing a => a -> Name
getName Id
i) Maybe Module -> (Module -> Maybe Module) -> Maybe Module
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Module
m ->
                   Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Module
m Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
mod) Maybe () -> Maybe Module -> Maybe Module
forall a b. Maybe a -> Maybe b -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Module -> Maybe Module
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return Module
m

      lookupPseudoIdFun :: Int -> Unique
                        -> StateT DependencyDataCache G (Either ExportedFun Int)
      lookupPseudoIdFun :: Int
-> Unique -> StateT DependencyDataCache G (Either ExportedFun Int)
lookupPseudoIdFun Int
_n Unique
u =
        case UniqFM Id Int -> Unique -> Maybe Int
forall {k} (key :: k) elt. UniqFM key elt -> Unique -> Maybe elt
lookupUFM_Directly UniqFM Id Int
unitIdExports Unique
u of
          Just Int
k -> Either ExportedFun Int
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. a -> StateT DependencyDataCache G a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either ExportedFun Int
forall a b. b -> Either a b
Right Int
k)
          Maybe Int
_      -> String -> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. HasCallStack => String -> a
panic String
"lookupPseudoIdFun"

      -- get the function for an Id from the cache, add it if necessary
      -- result: Left Object.ExportedFun   if function refers to another module
      --         Right blockNumber if function refers to current module
      --
      --         assumes function is internal to the current block if it's
      --         from teh current module and not in the unitIdExports map.
      lookupIdFun :: Int -> Id
                  -> StateT DependencyDataCache G (Either ExportedFun Int)
      lookupIdFun :: Int -> Id -> StateT DependencyDataCache G (Either ExportedFun Int)
lookupIdFun Int
n Id
i = case UniqFM Id Int -> Id -> Maybe Int
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM Id Int
unitIdExports Id
i of
        Just Int
k  -> Either ExportedFun Int
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. a -> StateT DependencyDataCache G a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either ExportedFun Int
forall a b. b -> Either a b
Right Int
k)
        Maybe Int
Nothing -> case Id -> Maybe Module
idModule Id
i of
          Maybe Module
Nothing -> Either ExportedFun Int
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. a -> StateT DependencyDataCache G a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either ExportedFun Int
forall a b. b -> Either a b
Right Int
n)
          Just Module
m ->
            let k :: Word64
k = Unique -> Word64
getKey (Unique -> Word64) -> (Id -> Unique) -> Id -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Unique
forall a. Uniquable a => a -> Unique
getUnique (Id -> Word64) -> Id -> Word64
forall a b. (a -> b) -> a -> b
$ Id
i
                addEntry :: StateT DependencyDataCache G ExportedFun
                addEntry :: StateT DependencyDataCache G ExportedFun
addEntry = do
                  idTxt <- Ident -> FastString
identFS (Ident -> FastString)
-> StateT DependencyDataCache G Ident
-> StateT DependencyDataCache G FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> G Ident -> StateT DependencyDataCache G Ident
forall (m :: * -> *) a.
Monad m =>
m a -> StateT DependencyDataCache m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Id -> G Ident
identForId Id
i)
                  lookupExternalFun (Just k) (OtherSymb m idTxt)
            in  if Module
m Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
mod
                   then String
-> SDoc -> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"local id not found" (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
m)
                    else ExportedFun -> Either ExportedFun Int
forall a b. a -> Either a b
Left (ExportedFun -> Either ExportedFun Int)
-> StateT DependencyDataCache G ExportedFun
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
                            mr <- (DependencyDataCache -> Maybe ExportedFun)
-> StateT DependencyDataCache G (Maybe ExportedFun)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets (Word64 -> Word64Map ExportedFun -> Maybe ExportedFun
forall a. Word64 -> Word64Map a -> Maybe a
WM.lookup Word64
k (Word64Map ExportedFun -> Maybe ExportedFun)
-> (DependencyDataCache -> Word64Map ExportedFun)
-> DependencyDataCache
-> Maybe ExportedFun
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DependencyDataCache -> Word64Map ExportedFun
ddcId)
                            maybe addEntry return mr

      -- get the function for an OtherSymb from the cache, add it if necessary
      lookupOtherFun :: OtherSymb
                     -> StateT DependencyDataCache G (Either ExportedFun Int)
      lookupOtherFun :: OtherSymb -> StateT DependencyDataCache G (Either ExportedFun Int)
lookupOtherFun od :: OtherSymb
od@(OtherSymb Module
m FastString
idTxt) =
        case OtherSymb -> Map OtherSymb Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup OtherSymb
od Map OtherSymb Int
unitOtherExports of
          Just Int
n  -> Either ExportedFun Int
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. a -> StateT DependencyDataCache G a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either ExportedFun Int
forall a b. b -> Either a b
Right Int
n)
          Maybe Int
Nothing | Module
m Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
mod -> String
-> SDoc -> StateT DependencyDataCache G (Either ExportedFun Int)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"genDependencyData.lookupOtherFun: unknown local other id:" (FastString -> SDoc
forall doc. IsLine doc => FastString -> doc
ftext FastString
idTxt)
          Maybe Int
Nothing ->  ExportedFun -> Either ExportedFun Int
forall a b. a -> Either a b
Left (ExportedFun -> Either ExportedFun Int)
-> StateT DependencyDataCache G ExportedFun
-> StateT DependencyDataCache G (Either ExportedFun Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (StateT DependencyDataCache G ExportedFun
-> (ExportedFun -> StateT DependencyDataCache G ExportedFun)
-> Maybe ExportedFun
-> StateT DependencyDataCache G ExportedFun
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Word64
-> OtherSymb -> StateT DependencyDataCache G ExportedFun
lookupExternalFun Maybe Word64
forall a. Maybe a
Nothing OtherSymb
od) ExportedFun -> StateT DependencyDataCache G ExportedFun
forall a. a -> StateT DependencyDataCache G a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ExportedFun -> StateT DependencyDataCache G ExportedFun)
-> StateT DependencyDataCache G (Maybe ExportedFun)
-> StateT DependencyDataCache G ExportedFun
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
                        (DependencyDataCache -> Maybe ExportedFun)
-> StateT DependencyDataCache G (Maybe ExportedFun)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets (OtherSymb -> Map OtherSymb ExportedFun -> Maybe ExportedFun
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup OtherSymb
od (Map OtherSymb ExportedFun -> Maybe ExportedFun)
-> (DependencyDataCache -> Map OtherSymb ExportedFun)
-> DependencyDataCache
-> Maybe ExportedFun
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DependencyDataCache -> Map OtherSymb ExportedFun
ddcOther))

      lookupExportedId :: Id -> StateT DependencyDataCache G ExportedFun
      lookupExportedId :: Id -> StateT DependencyDataCache G ExportedFun
lookupExportedId Id
i = do
        idTxt <- Ident -> FastString
identFS (Ident -> FastString)
-> StateT DependencyDataCache G Ident
-> StateT DependencyDataCache G FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> G Ident -> StateT DependencyDataCache G Ident
forall (m :: * -> *) a.
Monad m =>
m a -> StateT DependencyDataCache m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Id -> G Ident
identForId Id
i)
        lookupExternalFun (Just . getKey . getUnique $ i) (OtherSymb mod idTxt)

      lookupExportedOther :: FastString -> StateT DependencyDataCache G ExportedFun
      lookupExportedOther :: FastString -> StateT DependencyDataCache G ExportedFun
lookupExportedOther = Maybe Word64
-> OtherSymb -> StateT DependencyDataCache G ExportedFun
lookupExternalFun Maybe Word64
forall a. Maybe a
Nothing (OtherSymb -> StateT DependencyDataCache G ExportedFun)
-> (FastString -> OtherSymb)
-> FastString
-> StateT DependencyDataCache G ExportedFun
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> FastString -> OtherSymb
OtherSymb Module
mod

      -- lookup a dependency to another module, add to the id cache if there's
      -- an id key, otherwise add to other cache
      lookupExternalFun :: Maybe Word64
                        -> OtherSymb -> StateT DependencyDataCache G ExportedFun
      lookupExternalFun :: Maybe Word64
-> OtherSymb -> StateT DependencyDataCache G ExportedFun
lookupExternalFun Maybe Word64
mbIdKey od :: OtherSymb
od@(OtherSymb Module
m FastString
idTxt) = do
        let mk :: Word64
mk        = Unique -> Word64
getKey (Unique -> Word64) -> (Module -> Unique) -> Module -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> Unique
forall a. Uniquable a => a -> Unique
getUnique (Module -> Word64) -> Module -> Word64
forall a b. (a -> b) -> a -> b
$ Module
m
            mpk :: Unit
mpk       = Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m
            exp_fun :: ExportedFun
exp_fun   = Module -> LexicalFastString -> ExportedFun
ExportedFun Module
m (FastString -> LexicalFastString
LexicalFastString FastString
idTxt)
            addCache :: StateT DependencyDataCache G ExportedFun
addCache  = do
              ms <- (DependencyDataCache -> Word64Map Unit)
-> StateT DependencyDataCache G (Word64Map Unit)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets DependencyDataCache -> Word64Map Unit
ddcModule
              let !cache' = Word64 -> Unit -> Word64Map Unit -> Word64Map Unit
forall a. Word64 -> a -> Word64Map a -> Word64Map a
WM.insert Word64
mk Unit
mpk Word64Map Unit
ms
              modify (\DependencyDataCache
s -> DependencyDataCache
s { ddcModule = cache'})
              pure exp_fun
        f <- do
          mbm <- (DependencyDataCache -> Bool) -> StateT DependencyDataCache G Bool
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
gets (Word64 -> Word64Map Unit -> Bool
forall a. Word64 -> Word64Map a -> Bool
WM.member Word64
mk (Word64Map Unit -> Bool)
-> (DependencyDataCache -> Word64Map Unit)
-> DependencyDataCache
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DependencyDataCache -> Word64Map Unit
ddcModule)
          case mbm of
            Bool
False -> StateT DependencyDataCache G ExportedFun
addCache
            Bool
True  -> ExportedFun -> StateT DependencyDataCache G ExportedFun
forall a. a -> StateT DependencyDataCache G a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExportedFun
exp_fun

        case mbIdKey of
          Maybe Word64
Nothing -> (DependencyDataCache -> DependencyDataCache)
-> StateT DependencyDataCache G ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify (\DependencyDataCache
s -> DependencyDataCache
s { ddcOther = M.insert od f (ddcOther s) })
          Just Word64
k  -> (DependencyDataCache -> DependencyDataCache)
-> StateT DependencyDataCache G ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify (\DependencyDataCache
s -> DependencyDataCache
s { ddcId    = WM.insert k f (ddcId s) })

        return f