Skip to content

Commit 59fca95

Browse files
committed
add packZipWith for backward compatibility with GHC 8.10.7
1 parent 135e7fe commit 59fca95

File tree

2 files changed

+28
-2
lines changed

2 files changed

+28
-2
lines changed

src/Simplex/Messaging/Agent/Store/SQLite.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ import qualified Simplex.Messaging.Agent.Store.SQLite.DB as DB
7070
import Simplex.Messaging.Agent.Store.SQLite.Util
7171
import Simplex.Messaging.Agent.Store.Shared (Migration (..), MigrationConfig (..), MigrationError (..))
7272
import qualified Simplex.Messaging.Crypto as C
73-
import Simplex.Messaging.Util (ifM, safeDecodeUtf8)
73+
import Simplex.Messaging.Util (ifM, packZipWith, safeDecodeUtf8)
7474
import System.Directory (copyFile, createDirectoryIfMissing, doesFileExist)
7575
import System.FilePath (takeDirectory, takeFileName, (</>))
7676

@@ -146,7 +146,8 @@ sqliteXorMd5Combine = mkSQLiteFunc $ \cxt args -> do
146146
SQLite3.funcResultBlob cxt $ xorMd5Combine idsHash rId
147147

148148
xorMd5Combine :: ByteString -> ByteString -> ByteString
149-
xorMd5Combine idsHash rId = B.packZipWith xor idsHash $ C.md5Hash rId
149+
xorMd5Combine idsHash rId = packZipWith xor idsHash $ C.md5Hash rId
150+
{-# INLINE xorMd5Combine #-}
150151

151152
closeDBStore :: DBStore -> IO ()
152153
closeDBStore st@DBStore {dbClosed} =

src/Simplex/Messaging/Util.hs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE BangPatterns #-}
12
{-# LANGUAGE MonadComprehensions #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# LANGUAGE ScopedTypeVariables #-}
@@ -15,6 +16,7 @@ import qualified Data.Aeson as J
1516
import Data.Bifunctor (first, second)
1617
import Data.ByteString.Char8 (ByteString)
1718
import qualified Data.ByteString.Char8 as B
19+
import Data.ByteString.Internal (toForeignPtr, unsafeCreate, unsafeWithForeignPtr)
1820
import qualified Data.ByteString.Lazy.Char8 as LB
1921
import Data.IORef
2022
import Data.Int (Int64)
@@ -29,6 +31,8 @@ import qualified Data.Text as T
2931
import Data.Text.Encoding (decodeUtf8With, encodeUtf8)
3032
import Data.Time (NominalDiffTime)
3133
import Data.Tuple (swap)
34+
import Data.Word (Word8)
35+
import Foreign.Storable (peekByteOff, pokeByteOff)
3236
import GHC.Conc (labelThread, myThreadId, threadDelay)
3337
import UnliftIO hiding (atomicModifyIORef')
3438
import qualified UnliftIO.Exception as UE
@@ -156,6 +160,27 @@ mapAccumLM_NonEmpty
156160
mapAccumLM_NonEmpty f s (x :| xs) =
157161
[(s2, x' :| xs') | (s1, x') <- f s x, (s2, xs') <- mapAccumLM_List f s1 xs]
158162

163+
-- | Optimized from bytestring package for GHC 8.10.7 compatibility
164+
packZipWith :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
165+
packZipWith f s1 s2 =
166+
unsafeCreate len $ \r ->
167+
unsafeWithForeignPtr fp1 $ \p1 ->
168+
unsafeWithForeignPtr fp2 $ \p2 -> zipWith_ p1 p2 r
169+
where
170+
zipWith_ p1 p2 r = go 0
171+
where
172+
go :: Int -> IO ()
173+
go !n
174+
| n >= len = pure ()
175+
| otherwise = do
176+
x <- peekByteOff p1 (off1 + n)
177+
y <- peekByteOff p2 (off2 + n)
178+
pokeByteOff r n (f x y)
179+
go (n + 1)
180+
(fp1, off1, l1) = toForeignPtr s1
181+
(fp2, off2, l2) = toForeignPtr s2
182+
len = min l1 l2
183+
159184
tryWriteTBQueue :: TBQueue a -> a -> STM Bool
160185
tryWriteTBQueue q a = do
161186
full <- isFullTBQueue q

0 commit comments

Comments
 (0)