{-# 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 Data.Binary.Put (runPut) import Data.Bool (bool) import qualified Data.ByteString.Lazy as BL import Data.Text (Text) import qualified Data.Text as T import Nix import Path (Abs, File, Path, Rel, (), toFilePath) import qualified System.Directory as D import System.Nix.Hash (HashAlgorithm(..), encodeBase32, hashLazy) import System.Nix.Nar ( FileSystemObject(..) , IsExecutable(..) , Nar(..) , putNar ) -- | 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 = do b <- liftIO . BL.readFile $ toFilePath absF executable <- bool NonExecutable Executable . D.executable <$> liftIO (D.getPermissions $ toFilePath absF) let nar = runPut . putNar . Nar $ Regular executable (BL.length b) b pure . encodeBase32 $ hashLazy @'SHA256 nar -- | A leading dot is illegal in Nix derivation names. Replace it with '_'. replaceLeadingDot :: FilePath -> FilePath replaceLeadingDot ('.':f) = '_':f replaceLeadingDot f = f