@@ -7,6 +7,7 @@ module System.Nix.Util where
77import Control.Monad
88import Data.Binary.Get
99import Data.Binary.Put
10+ import qualified Data.ByteString as BS
1011import qualified Data.ByteString.Lazy as LBS
1112
1213putInt :: Integral a => a -> Put
@@ -16,18 +17,17 @@ getInt :: Integral a => Get a
1617getInt = fromIntegral <$> getWord64le
1718
1819-- length prefixed string packing with padding to 8 bytes
19- putByteStringLen :: LBS . ByteString -> Put
20+ putByteStringLen :: BS . ByteString -> Put
2021putByteStringLen x = do
21- putInt $ fromIntegral $ len
22- putLazyByteString x
23- when (len `mod` 8 /= 0 ) $
24- pad $ fromIntegral $ 8 - (len `mod` 8 )
25- where len = LBS. length x
26- pad x = forM_ (take x $ cycle [0 ]) putWord8
22+ putInt $ len
23+ putByteString x
24+ pad $ 8 - (len `mod` 8 )
25+ where len = BS. length x
26+ pad x = replicateM_ x (putWord8 0 )
2727
28- putByteStrings :: Foldable t => t LBS . ByteString -> Put
28+ putByteStrings :: Foldable t => t BS . ByteString -> Put
2929putByteStrings xs = do
30- putInt $ fromIntegral $ length xs
30+ putInt $ length xs
3131 mapM_ putByteStringLen xs
3232
3333getByteStringLen :: Get LBS. ByteString
@@ -38,11 +38,10 @@ getByteStringLen = do
3838 pads <- unpad $ fromIntegral $ 8 - (len `mod` 8 )
3939 unless (all (== 0 ) pads) $ fail $ " No zeroes" ++ show (st, len, pads)
4040 return st
41- where unpad x = sequence $ replicate x getWord8
41+ where unpad x = replicateM x getWord8
4242
4343getByteStrings :: Get [LBS. ByteString ]
4444getByteStrings = do
4545 count <- getInt
4646 res <- sequence $ replicate count getByteStringLen
4747 return res
48-
0 commit comments