[Git][ghc/ghc][master] add GHC.Utils.Binary.foldGet' and use for Iface

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Dec 24 00:10:26 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
aebef31c by doyougnu at 2022-12-23T19:10:09-05:00
add GHC.Utils.Binary.foldGet' and use for Iface

A minor optimization to remove lazy IO and a lazy accumulator

strictify foldGet'

IFace.Binary: use strict foldGet'

remove superfluous bang

- - - - -


2 changed files:

- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Utils/Binary.hs


Changes:

=====================================
compiler/GHC/Iface/Binary.hs
=====================================
@@ -292,7 +292,7 @@ getSymbolTable bh name_cache = do
     -- create an array of Names for the symbols and add them to the NameCache
     updateNameCache' name_cache $ \cache0 -> do
         mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int Name)
-        cache <- foldGet (fromIntegral sz) bh cache0 $ \i (uid, mod_name, occ) cache -> do
+        cache <- foldGet' (fromIntegral sz) bh cache0 $ \i (uid, mod_name, occ) cache -> do
           let mod = mkModule uid mod_name
           case lookupOrigNameCache cache mod occ of
             Just name -> do


=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -44,7 +44,7 @@ module GHC.Utils.Binary
    castBin,
    withBinBuffer,
 
-   foldGet,
+   foldGet, foldGet',
 
    writeBinMem,
    readBinMem,
@@ -332,6 +332,23 @@ foldGet n bh init_b f = go 0 init_b
           b' <- f i a b
           go (i+1) b'
 
+foldGet'
+  :: Binary a
+  => Word -- n elements
+  -> BinHandle
+  -> b -- initial accumulator
+  -> (Word -> a -> b -> IO b)
+  -> IO b
+{-# INLINE foldGet' #-}
+foldGet' n bh init_b f = go 0 init_b
+  where
+    go i !b
+      | i == n    = return b
+      | otherwise = do
+          !a  <- get bh
+          b'  <- f i a b
+          go (i+1) b'
+
 
 -- -----------------------------------------------------------------------------
 -- Low-level reading/writing of bytes



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aebef31cd8857749c7e25fe4b0d3ce4e12ae225a
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/20221223/8030bed3/attachment-0001.html>


More information about the ghc-commits mailing list