Skip to content

Commit

Permalink
computeStorePathForPath: force SHA256 as it's the only valid choice
Browse files Browse the repository at this point in the history
  • Loading branch information
layus authored and sorki committed Mar 24, 2021
1 parent b85f7c8 commit db71ece
Showing 1 changed file with 13 additions and 17 deletions.
30 changes: 13 additions & 17 deletions hnix-store-core/src/System/Nix/ReadonlyStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeFamilies #-}

module System.Nix.ReadonlyStore where

Expand Down Expand Up @@ -50,9 +48,7 @@ makeTextPath fp nm h refs = makeStorePath fp ty h nm

makeFixedOutputPath
:: forall hashAlgo
. ( ValidAlgo hashAlgo
, NamedAlgo hashAlgo
)
. NamedAlgo hashAlgo
=> FilePath
-> Bool
-> Digest hashAlgo
Expand All @@ -75,21 +71,21 @@ computeStorePathForText
:: FilePath -> StorePathName -> ByteString -> (StorePathSet -> StorePath)
computeStorePathForText fp nm = makeTextPath fp nm . hash

computeStorePathForPath :: forall a. (ValidAlgo a, NamedAlgo a)
=> StorePathName -- ^ Name part of the newly created `StorePath`
-> FilePath -- ^ Local `FilePath` to add
-> Bool -- ^ Add target directory recursively
-> (FilePath -> Bool) -- ^ Path filter function
-> Bool -- ^ Only used by local store backend
-> IO StorePath
computeStorePathForPath
:: StorePathName -- ^ Name part of the newly created `StorePath`
-> FilePath -- ^ Local `FilePath` to add
-> Bool -- ^ Add target directory recursively
-> (FilePath -> Bool) -- ^ Path filter function
-> Bool -- ^ Only used by local store backend
-> IO StorePath
computeStorePathForPath name pth recursive _pathFilter _repair = do
selectedHash <- if recursive then recursiveContentHash else flatContentHash
pure $ makeFixedOutputPath "/nix/store" recursive selectedHash name
where
recursiveContentHash :: IO (Digest a)
recursiveContentHash = finalize @a <$> execStateT streamNarUpdate (initialize @a)
streamNarUpdate :: StateT (AlgoCtx a) IO ()
streamNarUpdate = streamNarIO (modify . flip (update @a)) narEffectsIO pth
recursiveContentHash :: IO (Digest 'SHA256)
recursiveContentHash = finalize <$> execStateT streamNarUpdate (initialize @'SHA256)
streamNarUpdate :: StateT (AlgoCtx 'SHA256) IO ()
streamNarUpdate = streamNarIO (modify . flip (update @'SHA256)) narEffectsIO pth

flatContentHash :: IO (Digest a)
flatContentHash :: IO (Digest 'SHA256)
flatContentHash = hashLazy <$> narReadFile narEffectsIO pth

0 comments on commit db71ece

Please sign in to comment.