[Git][ghc/ghc][wip/fendor/ghc-iface-sharing] Shrink Bin buffer
Hannes Siebenhandl (@fendor)
gitlab at gitlab.haskell.org
Tue Apr 30 10:23:55 UTC 2024
Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing at Glasgow Haskell Compiler / GHC
Commits:
80821eac by Fendor at 2024-04-30T12:22:45+02:00
Shrink Bin buffer
- - - - -
1 changed file:
- compiler/GHC/Utils/Binary.hs
Changes:
=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -37,6 +37,7 @@ module GHC.Utils.Binary
castBin,
withBinBuffer,
freezeWriteHandle,
+ shrinkBinBuffer,
thawReadHandle,
foldGet, foldGet',
@@ -101,6 +102,7 @@ module GHC.Utils.Binary
BindingName(..),
simpleBindingNameWriter,
simpleBindingNameReader,
+ BinArray,
) where
import GHC.Prelude
@@ -125,7 +127,7 @@ import Foreign hiding (shiftL, shiftR, void)
import Data.Array
import Data.Array.IO
import Data.Array.Unsafe
-import Data.ByteString (ByteString)
+import Data.ByteString (ByteString, copy)
import Data.Coerce
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Unsafe as BS
@@ -344,6 +346,17 @@ freezeWriteHandle wbm = do
, rbm_arr_r = rbm_arr_r
}
+-- Copy the BinBuffer to a new BinBuffer which is exactly the right size.
+-- This performs a copy of the underlying buffer.
+-- The buffer may be truncated if the offset is not at the end of the written
+-- output.
+--
+-- UserData is also discarded during the copy
+-- You should just use this when translating a Put handle into a Get handle.
+shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle
+shrinkBinBuffer bh = withBinBuffer bh $ \bs -> do
+ unsafeUnpackBinBuffer (copy bs)
+
thawReadHandle :: ReadBinHandle -> IO WriteBinHandle
thawReadHandle rbm = do
wbm_off_r <- newFastMutInt =<< readFastMutInt (rbm_off_r rbm)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80821eac0039229c5d52e1deb3e8c627262c903a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80821eac0039229c5d52e1deb3e8c627262c903a
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/20240430/dcc26e12/attachment-0001.html>
More information about the ghc-commits
mailing list