22{-# LANGUAGE OverloadedStrings #-}
33{-# LANGUAGE TypeApplications #-}
44{-# LANGUAGE ScopedTypeVariables #-}
5+ {-# LANGUAGE AllowAmbiguousTypes #-}
6+ {-# LANGUAGE TypeFamilies #-}
57
68module System.Nix.ReadonlyStore where
79
@@ -13,7 +15,9 @@ import qualified Data.Text as T
1315import qualified Data.HashSet as HS
1416import Data.Text.Encoding
1517import System.Nix.Hash
18+ import System.Nix.Nar
1619import System.Nix.StorePath
20+ import Control.Monad.State.Strict
1721
1822
1923makeStorePath
@@ -70,3 +74,22 @@ makeFixedOutputPath fp recursive h =
7074computeStorePathForText
7175 :: FilePath -> StorePathName -> ByteString -> (StorePathSet -> StorePath )
7276computeStorePathForText fp nm = makeTextPath fp nm . hash
77+
78+ computeStorePathForPath :: forall a . (ValidAlgo a , NamedAlgo a )
79+ => StorePathName -- ^ Name part of the newly created `StorePath`
80+ -> FilePath -- ^ Local `FilePath` to add
81+ -> Bool -- ^ Add target directory recursively
82+ -> (FilePath -> Bool ) -- ^ Path filter function
83+ -> Bool -- ^ Only used by local store backend
84+ -> IO StorePath
85+ computeStorePathForPath name pth recursive _pathFilter _repair = do
86+ selectedHash <- if recursive then recursiveContentHash else flatContentHash
87+ pure $ makeFixedOutputPath " /nix/store" recursive selectedHash name
88+ where
89+ recursiveContentHash :: IO (Digest a )
90+ recursiveContentHash = finalize @ a <$> execStateT streamNarUpdate (initialize @ a )
91+ streamNarUpdate :: StateT (AlgoCtx a ) IO ()
92+ streamNarUpdate = streamNarIO (modify . flip (update @ a )) narEffectsIO pth
93+
94+ flatContentHash :: IO (Digest a )
95+ flatContentHash = hashLazy <$> narReadFile narEffectsIO pth
0 commit comments