{-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} module System.Nix.ReadonlyStore where import Data.ByteString (ByteString) import qualified Data.ByteString as BS import qualified Data.Text as T import qualified Data.HashSet as HS import Data.Text.Encoding import System.Nix.Hash import System.Nix.StorePath makeStorePath :: forall hashAlgo . (NamedAlgo hashAlgo) => FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath makeStorePath :: FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath makeStorePath FilePath fp ByteString ty Digest hashAlgo h StorePathName nm = Digest StorePathHashAlgo -> StorePathName -> FilePath -> StorePath StorePath Digest StorePathHashAlgo storeHash StorePathName nm FilePath fp where s :: ByteString s = ByteString -> [ByteString] -> ByteString BS.intercalate ByteString ":" [ ByteString ty , Text -> ByteString encodeUtf8 (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ NamedAlgo hashAlgo => Text forall (a :: HashAlgorithm). NamedAlgo a => Text algoName @hashAlgo , Text -> ByteString encodeUtf8 (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ BaseEncoding -> Digest hashAlgo -> Text forall (a :: HashAlgorithm). BaseEncoding -> Digest a -> Text encodeInBase BaseEncoding Base16 Digest hashAlgo h , Text -> ByteString encodeUtf8 (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ FilePath -> Text T.pack FilePath fp , Text -> ByteString encodeUtf8 (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ StorePathName -> Text unStorePathName StorePathName nm ] storeHash :: Digest StorePathHashAlgo storeHash = ByteString -> Digest StorePathHashAlgo forall (a :: HashAlgorithm). ValidAlgo a => ByteString -> Digest a hash ByteString s makeTextPath :: FilePath -> StorePathName -> Digest 'SHA256 -> StorePathSet -> StorePath makeTextPath :: FilePath -> StorePathName -> Digest 'SHA256 -> StorePathSet -> StorePath makeTextPath FilePath fp StorePathName nm Digest 'SHA256 h StorePathSet refs = FilePath -> ByteString -> Digest 'SHA256 -> StorePathName -> StorePath forall (hashAlgo :: HashAlgorithm). NamedAlgo hashAlgo => FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath makeStorePath FilePath fp ByteString ty Digest 'SHA256 h StorePathName nm where ty :: ByteString ty = ByteString -> [ByteString] -> ByteString BS.intercalate ByteString ":" (ByteString "text" ByteString -> [ByteString] -> [ByteString] forall a. a -> [a] -> [a] : (StorePath -> ByteString) -> [StorePath] -> [ByteString] forall a b. (a -> b) -> [a] -> [b] map StorePath -> ByteString storePathToRawFilePath (StorePathSet -> [StorePath] forall a. HashSet a -> [a] HS.toList StorePathSet refs)) makeFixedOutputPath :: forall hashAlgo . (ValidAlgo hashAlgo, NamedAlgo hashAlgo) => FilePath -> Bool -> Digest hashAlgo -> StorePathName -> StorePath makeFixedOutputPath :: FilePath -> Bool -> Digest hashAlgo -> StorePathName -> StorePath makeFixedOutputPath FilePath fp Bool recursive Digest hashAlgo h StorePathName nm = if Bool recursive Bool -> Bool -> Bool && (NamedAlgo hashAlgo => Text forall (a :: HashAlgorithm). NamedAlgo a => Text algoName @hashAlgo) Text -> Text -> Bool forall a. Eq a => a -> a -> Bool == Text "sha256" then FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath forall (hashAlgo :: HashAlgorithm). NamedAlgo hashAlgo => FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath makeStorePath FilePath fp ByteString "source" Digest hashAlgo h StorePathName nm else FilePath -> ByteString -> Digest 'SHA256 -> StorePathName -> StorePath forall (hashAlgo :: HashAlgorithm). NamedAlgo hashAlgo => FilePath -> ByteString -> Digest hashAlgo -> StorePathName -> StorePath makeStorePath FilePath fp ByteString "output:out" Digest 'SHA256 h' StorePathName nm where h' :: Digest 'SHA256 h' = ValidAlgo 'SHA256 => ByteString -> Digest 'SHA256 forall (a :: HashAlgorithm). ValidAlgo a => ByteString -> Digest a hash @'SHA256 (ByteString -> Digest 'SHA256) -> ByteString -> Digest 'SHA256 forall a b. (a -> b) -> a -> b $ ByteString "fixed:out:" ByteString -> ByteString -> ByteString forall a. Semigroup a => a -> a -> a <> Text -> ByteString encodeUtf8 (NamedAlgo hashAlgo => Text forall (a :: HashAlgorithm). NamedAlgo a => Text algoName @hashAlgo) ByteString -> ByteString -> ByteString forall a. Semigroup a => a -> a -> a <> (if Bool recursive then ByteString ":r:" else ByteString ":") ByteString -> ByteString -> ByteString forall a. Semigroup a => a -> a -> a <> Text -> ByteString encodeUtf8 (BaseEncoding -> Digest hashAlgo -> Text forall (a :: HashAlgorithm). BaseEncoding -> Digest a -> Text encodeInBase BaseEncoding Base16 Digest hashAlgo h) ByteString -> ByteString -> ByteString forall a. Semigroup a => a -> a -> a <> ByteString ":" computeStorePathForText :: FilePath -> StorePathName -> ByteString -> StorePathSet -> StorePath computeStorePathForText :: FilePath -> StorePathName -> ByteString -> StorePathSet -> StorePath computeStorePathForText FilePath fp StorePathName nm ByteString s StorePathSet refs = FilePath -> StorePathName -> Digest 'SHA256 -> StorePathSet -> StorePath makeTextPath FilePath fp StorePathName nm (ByteString -> Digest 'SHA256 forall (a :: HashAlgorithm). ValidAlgo a => ByteString -> Digest a hash ByteString s) StorePathSet refs