Skip to content

Commit 7bd82c9

Browse files
committed
WIP addToStore protocol implementation
1 parent 6f1626a commit 7bd82c9

File tree

2 files changed

+53
-27
lines changed
  • hnix-store-core/src/System/Nix/Internal
  • hnix-store-remote/src/System/Nix/Store

2 files changed

+53
-27
lines changed

hnix-store-core/src/System/Nix/Internal/Hash.hs

Lines changed: 17 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -47,21 +47,6 @@ data HashAlgorithm' n
4747

4848
type HashAlgorithm = HashAlgorithm' Nat
4949

50-
class AlgoVal (a :: HashAlgorithm) where
51-
algoVal :: HashAlgorithm' Integer
52-
53-
instance AlgoVal MD5 where
54-
algoVal = MD5
55-
56-
instance AlgoVal SHA1 where
57-
algoVal = SHA1
58-
59-
instance AlgoVal SHA256 where
60-
algoVal = SHA256
61-
62-
instance forall a n.(AlgoVal a, KnownNat n) => AlgoVal (Truncated n a) where
63-
algoVal = Truncated (natVal (Proxy @n)) (algoVal @a)
64-
6550
-- | Types with kind @HashAlgorithm@ may be a @HasDigest@ instance
6651
-- if they are able to hash bytestrings via the init/update/finalize
6752
-- API of cryptonite
@@ -185,3 +170,20 @@ truncateDigest (Digest c) = Digest $ BS.pack $ map truncOutputByte [0.. n-1]
185170

186171
digits32 :: V.Vector Char
187172
digits32 = V.fromList "0123456789abcdfghijklmnpqrsvwxyz"
173+
174+
175+
-- | Convert type-level @HashAlgorithm@ into the value level
176+
class AlgoVal (a :: HashAlgorithm) where
177+
algoVal :: HashAlgorithm' Integer
178+
179+
instance AlgoVal MD5 where
180+
algoVal = MD5
181+
182+
instance AlgoVal SHA1 where
183+
algoVal = SHA1
184+
185+
instance AlgoVal SHA256 where
186+
algoVal = SHA256
187+
188+
instance forall a n.(AlgoVal a, KnownNat n) => AlgoVal (Truncated n a) where
189+
algoVal = Truncated (natVal (Proxy @n)) (algoVal @a)

hnix-store-remote/src/System/Nix/Store/Remote.hs

Lines changed: 36 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -35,19 +35,24 @@ module System.Nix.Store.Remote (
3535
, queryMissing
3636
) where
3737

38+
import Control.Monad
39+
import Control.Monad.IO.Class (liftIO)
40+
import qualified Data.Binary as B
41+
import qualified Data.Binary.Put as B
3842
import Data.Maybe
3943
import qualified Data.ByteString.Lazy as LBS
4044
import qualified Data.Map.Strict as M
4145
import Data.Proxy (Proxy(Proxy))
46+
import qualified Data.Text.Lazy as T
47+
import qualified Data.Text.Lazy.Encoding as T
4248

43-
import Control.Monad
44-
45-
import qualified System.Nix.Build as Build
46-
import qualified System.Nix.Derivation as Drv
47-
import qualified System.Nix.GC as GC
48-
import System.Nix.Hash (Digest, HashAlgorithm)
49+
import qualified System.Nix.Build as Build
50+
import qualified System.Nix.Derivation as Drv
51+
import qualified System.Nix.GC as GC
52+
import System.Nix.Hash (Digest, HashAlgorithm)
4953
import System.Nix.Path
5054
import System.Nix.Hash
55+
import System.Nix.Nar (localPackNar, putNar)
5156
import System.Nix.Util
5257

5358
import System.Nix.Store.Remote.Types
@@ -183,23 +188,42 @@ addToStoreNar = undefined -- XXX
183188
-- instance forall n a.BaseHashAlgorithm a => BaseHashAlgorithm (Truncated n a) where
184189
-- baseHashAlgorithm = baseHashAlgorithm @a
185190

191+
printHashType :: HashAlgorithm' Integer -> T.Text
192+
printHashType MD5 = "MD5"
193+
printHashType SHA1 = "SHA1"
194+
printHashType SHA256 = "SHA256"
195+
printHashType (Truncated _ a) = printHashType a
196+
186197
type PathFilter = Path -> Bool
187198
addToStore
188-
:: forall a. AlgoVal a
199+
:: forall a. (HasDigest a, AlgoVal a)
189200
=> LBS.ByteString
190-
-> Path
201+
-> FilePath
191202
-> Bool
192203
-> Proxy a
193204
-> PathFilter
194205
-> RepairFlag
195206
-> MonadStore Path
196207
addToStore name pth recursive algoProxy pfilter repair = do
208+
-- Get length first
209+
len <- liftIO $ LBS.length . B.runPut . putNar <$> localPackNar undefined pth
210+
-- Fetch full NAR bytestring separately. We are trying to
211+
-- avoid forcing the full string in memory
212+
bs :: LBS.ByteString <- liftIO $ B.runPut . putNar <$> localPackNar undefined pth
197213
runOpArgs AddToStore $ do
198214
putByteStringLen name
199-
putByteStringLen $ if algoVal @a == SHA256 && recursive then 0 else 1
200-
putByteStringLen $ if recursive then 0 else 1
201-
putByteStringLen name
202-
fmap (fromMaybe "TODO: Error") sockGetPath
215+
-- TODO: really send the string 0 or 1? Or is this Word8's 0 and 1?
216+
putByteStringLen $ if algoVal @a `elem` [SHA256, Truncated 20 SHA256]
217+
&& recursive
218+
then "0"
219+
else "1"
220+
-- TODO: really send the string 0 or 1? Or is this Word8's 0 and 1?
221+
putByteStringLen $ if recursive then "0" else "1"
222+
putByteStringLen (T.encodeUtf8 . printHashType $ algoVal @a)
223+
224+
putInt len
225+
B.putLazyByteString bs
226+
fmap (fromMaybe $ error "TODO: Error") sockGetPath
203227

204228

205229
addTextToStore :: LBS.ByteString -> LBS.ByteString -> PathSet -> RepairFlag -> MonadStore (Maybe Path)

0 commit comments

Comments
 (0)