[Git][ghc/ghc][wip/coreField] Change registerInferfaceData{With} to take an explicit HscEnv

Josh Meredith gitlab at gitlab.haskell.org
Tue Jun 16 17:45:16 UTC 2020



Josh Meredith pushed to branch wip/coreField at Glasgow Haskell Compiler / GHC


Commits:
ad7448d3 by Josh Meredith at 2020-06-17T03:44:14+10:00
Change registerInferfaceData{With} to take an explicit HscEnv

- - - - -


1 changed file:

- compiler/GHC/Driver/Types.hs


Changes:

=====================================
compiler/GHC/Driver/Types.hs
=====================================
@@ -156,6 +156,7 @@ module GHC.Driver.Types (
         readField, readFieldWith, readIfaceField, readIfaceFieldWith,
         writeField, writeFieldWith, writeIfaceField, writeIfaceFieldWith,
         deleteField, deleteIfaceField,
+        registerInterfaceData, registerInterfaceDataWith,
     ) where
 
 #include "HsVersions.h"
@@ -3445,14 +3446,11 @@ deleteField name (ExtensibleFields fs) = ExtensibleFields $ Map.delete name fs
 deleteIfaceField :: FieldName -> ModIface -> ModIface
 deleteIfaceField name iface = iface { mi_ext_fields = deleteField name (mi_ext_fields iface) }
 
-registerInterfaceData :: (Binary a, HasHscEnv m, MonadIO m) => FieldName -> a -> m ()
-registerInterfaceData name x = registerInterfaceDataWith name (`put_` x)
-
-registerInterfaceDataWith :: (HasHscEnv m, MonadIO m) => FieldName -> (BinHandle -> IO ()) -> m ()
-registerInterfaceDataWith name write = do
-  env <- getHscEnv
-  let ext_fs_ref = hsc_extensible_fields env
-  liftIO $ do
-    ext_fs  <- readIORef ext_fs_ref
-    ext_fs' <- writeFieldWith name write ext_fs
-    writeIORef ext_fs_ref ext_fs'
+registerInterfaceData :: Binary a => FieldName -> HscEnv -> a -> IO ()
+registerInterfaceData name env x = registerInterfaceDataWith name env (`put_` x)
+
+registerInterfaceDataWith :: FieldName -> HscEnv -> (BinHandle -> IO ()) -> IO ()
+registerInterfaceDataWith name env write = do
+  ext_fs  <- readIORef (hsc_extensible_fields env)
+  ext_fs' <- writeFieldWith name write ext_fs
+  writeIORef (hsc_extensible_fields env) ext_fs'



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ad7448d3620984e33ce10330220a1acd9727da4c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ad7448d3620984e33ce10330220a1acd9727da4c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200616/6c3bd642/attachment-0001.html>


More information about the ghc-commits mailing list