77{-# LANGUAGE DataKinds #-}
88{-# LANGUAGE TypeApplications #-}
99{-# LANGUAGE RecordWildCards #-}
10- {-# LANGUAGE FlexibleContexts #-}
1110module System.Nix.Store.Remote
12- {-
1311 (
1412 addToStore
1513 , addToStoreNar
@@ -36,35 +34,27 @@ module System.Nix.Store.Remote
3634 , syncWithGC
3735 , verifyStore
3836 )
39- -}
4037 where
4138
4239import Control.Monad
43- import Control.Monad.State
4440import Control.Monad.Except
4541import Control.Monad.IO.Class (liftIO )
46- import qualified Data.Binary as B
4742import qualified Data.Binary.Put as B
48- import Data.Maybe
49- import qualified Data.ByteString.Char8 as BSC
43+ import Data.ByteString (ByteString )
5044import qualified Data.ByteString.Lazy as BSL
5145import qualified Data.Map.Strict as M
52- import Data.Proxy (Proxy ( Proxy ) )
46+ import Data.Proxy (Proxy )
5347import Data.Text (Text )
54- import qualified Data.Text.Lazy as T
55- import qualified Data.Text.Lazy.Encoding as T
5648
5749import qualified System.Nix.Build as Build
58- import qualified Nix.Derivation as Drv
5950
60- -- import qualified System.Nix.GC as GC
6151import System.Nix.Hash (Digest , ValidAlgo )
6252import System.Nix.StorePath
6353import System.Nix.Hash
6454import System.Nix.Nar (localPackNar , putNar , narEffectsIO , Nar )
65- import System.Nix.Util
6655import System.Nix.ValidPath
6756
57+ import System.Nix.Store.Remote.Binary
6858import System.Nix.Store.Remote.Types
6959import System.Nix.Store.Remote.Protocol
7060import System.Nix.Store.Remote.Util
@@ -78,22 +68,22 @@ type SubstituteFlag = Bool
7868
7969addToStore
8070 :: forall a . (ValidAlgo a , NamedAlgo a )
81- => StorePathName -- BSL.ByteString
71+ => StorePathName
8272 -> FilePath
8373 -> Bool
8474 -> Proxy a
8575 -> (StorePath -> Bool )
8676 -> RepairFlag
8777 -> MonadStore StorePath
88- addToStore name pth recursive algoProxy pfilter repair = do
78+ addToStore name pth recursive _algoProxy pfilter repair = do
8979
9080 -- TODO: Is this lazy enough? We need `B.putLazyByteString bs` to stream `bs`
9181 bs :: BSL. ByteString <- liftIO $ B. runPut . putNar <$> localPackNar narEffectsIO pth
9282
9383 runOpArgs AddToStore $ do
9484 putText $ unStorePathName name
9585
96- putBool $ not $ algoName @ a `elem` [ " sha256" ] && recursive
86+ putBool $ not $ algoName @ a == " sha256" && recursive
9787 putBool recursive
9888
9989 putText $ algoName @ a
@@ -161,23 +151,22 @@ ensurePath :: StorePath -> MonadStore ()
161151ensurePath pn = do
162152 void $ simpleOpArgs EnsurePath $ putPath pn
163153
164- findRoots :: MonadStore (M. Map BSL. ByteString StorePath )
154+ findRoots :: MonadStore (M. Map ByteString StorePath )
165155findRoots = do
166156 runOp FindRoots
167157 sd <- getStoreDir
168- res <- getSocketIncremental (do
169- count <- getInt
170- res <- sequence $ replicate count ((,) <$> getByteStringLen <*> getPath sd)
171- return res
172- )
158+ res <- getSocketIncremental $ getMany $ (,) <$> getByteStringLen <*> getPath sd
173159
174160 r <- catRights res
175161 return $ M. fromList $ r
176162 where
177163 catRights :: [(a , Either String b )] -> MonadStore [(a , b )]
178164 catRights = mapM ex
165+
166+ ex :: (a , Either [Char ] b ) -> MonadStore (a , b )
179167 ex (x, Right y) = return (x, y)
180- ex (_x , Left e) = throwError $ " Unable to decode root: " ++ show e
168+ ex (_x , Left e) = throwError $ " Unable to decode root: " ++ e
169+
181170
182171isValidPathUncached :: StorePath -> MonadStore Bool
183172isValidPathUncached p = do
@@ -210,13 +199,13 @@ queryPathInfoUncached path = do
210199 unless valid $ error " Path is not valid"
211200
212201 deriver <- sockGetPathMay
213- narHash <- lBSToText <$> sockGetStr
202+ narHash <- bsToText <$> sockGetStr
214203 references <- sockGetPaths
215204 registrationTime <- sockGet getTime
216205 narSize <- sockGetInt
217206 ultimate <- sockGetBool
218- sigs <- map lBSToText <$> sockGetStrings
219- ca <- lBSToText <$> sockGetStr
207+ sigs <- map bsToText <$> sockGetStrings
208+ ca <- bsToText <$> sockGetStr
220209 return $ ValidPath {.. }
221210
222211queryReferrers :: StorePath -> MonadStore StorePathSet
0 commit comments