{-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} module NixHash (mkFileAttrs, replaceLeadingDot) where import BuilderDirs (BuilderDirs, currentDir) import Control.Monad.IO.Class (MonadIO (..)) import Control.Monad.Trans.Reader import Crypto.Hash (Digest, SHA256, hash) import qualified Data.ByteString as B import Data.Text (Text) import qualified Data.Text as T import Nix import Path (Abs, File, Path, Rel, toFilePath, ()) import Path.IO (withSystemTempFile) import System.IO import System.Nix.Hash (BaseEncoding (..), encodeDigestWith) import System.Nix.Nar (buildNarIO, narEffectsIO) -- | Build a set of @filename -> derivation@ attributes. mkFileAttrs :: [Path Rel File] -> ReaderT BuilderDirs IO [(Text, NExpr)] mkFileAttrs = traverse $ \f -> do h <- mkFileAttr f pure (T.pack (toFilePath f), h) -- | Hash the file, using Nix's NAR hash (the default to -- @builtins.path@ is NAR-style recursive hashing), and build a call -- to Nix's @builtins.path@ function. If @"file1"@ is a regular file, -- @mkHashEntry "file1"@ will generate: -- -- @ -- builtins.path { -- path = ./file1; -- sha256 = "<>"; -- } -- @ -- -- If @".file2"@ starts with a dot, that's an illegal Nix derivation -- name, so @mkHashEntry ".file2"@ will generate: -- -- @ -- builtins.path { -- path = ./.file2; -- name = "_file2"; -- sha256 = "<>" -- } -- @ mkFileAttr :: Path Rel File -> ReaderT BuilderDirs IO NExpr mkFileAttr f = do absF <- ( f) <$> currentDir h <- recursiveHash absF let bindings = [ "path" $= mkPath False (toFilePath absF) , "sha256" $= mkStr h ] ++ [ "name" $= mkStr (T.pack . replaceLeadingDot $ toFilePath f) | head (toFilePath f) == '.' ] pure $ "builtins" @. "path" @@ mkNonRecSet bindings -- | Serialise as per -- https://gist.github.com/jbeda/5c79d2b1434f0018d693 , which is an -- extract from Figure 5.2 of http://nixos.org/~eelco/pubs/phd-thesis.pdf , -- which is the Nix thesis. recursiveHash :: MonadIO m => Path Abs File -> m Text recursiveHash absF = liftIO . withSystemTempFile "nix-freeze-tree.nar" $ \_ h -> do buildNarIO narEffectsIO (toFilePath absF) h hSeek h AbsoluteSeek 0 contents <- B.hGetContents h pure $ encodeDigestWith NixBase32 (hash contents :: Digest SHA256) -- | A leading dot is illegal in Nix derivation names. Replace it with '_'. replaceLeadingDot :: FilePath -> FilePath replaceLeadingDot ('.':f) = '_':f replaceLeadingDot f = f