Skip to content

Commit

Permalink
cachix: improve nar hash mismatch error
Browse files Browse the repository at this point in the history
  • Loading branch information
sandydoo committed Jun 18, 2024
1 parent 921ce5f commit 7913ce3
Showing 1 changed file with 15 additions and 3 deletions.
18 changes: 15 additions & 3 deletions cachix/src/Cachix/Client/Push.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE Rank2Types #-}

{- This is a standalone module so it shouldn't depend on any CLI state like Env -}
Expand Down Expand Up @@ -66,6 +67,7 @@ import qualified Data.Conduit.Lzma as Lzma (compress)
import qualified Data.Conduit.Zstd as Zstd (compress)
import Data.IORef
import qualified Data.Set as Set
import Data.String.Here (iTrim)
import qualified Data.Text as T
import Hercules.CNix (StorePath)
import qualified Hercules.CNix.Std.Set as Std.Set
Expand Down Expand Up @@ -442,11 +444,21 @@ newNarInfoCreate pushParams storePath pathInfo UploadNarDetails {..} = do
storeDir <- Store.storeDir store
storePathText <- liftIO $ toS <$> Store.storePathToPath store storePath

-- TODO: show expected vs actual NAR hash
when (undNarHash /= piNarHash pathInfo) $
throwM $
NarHashMismatch $
toS storePathText <> ": Nar hash mismatch between nix-store --dump and nix db. You can repair db metadata by running as root: $ nix-store --verify --repair --check-contents"
NarHashMismatch
[iTrim|
${storePathText}: the computed NAR hash doesn't match the hash returned by the Nix store.

Expected: ${undNarHash}
Got: ${piNarHash pathInfo}

1. Try repairing the Nix store:

sudo nix-store --verify --repair --check-contents

2. If the issue persists, report it to https://github.com/cachix/cachix/issues
|]

let deriver =
fromMaybe "unknown-deriver" $
Expand Down

0 comments on commit 7913ce3

Please sign in to comment.