module HashStore
( hashStore
, hashStoreWithContent
) where
import Crypto.Hash.BLAKE2.BLAKE2b (hash)
import Data.ByteString.Base16 (encode)
import Data.ByteString.Char8 (ByteString)
import System.Directory (createDirectoryIfMissing, doesFileExist)
import System.FilePath ((</>))
import qualified Data.ByteString.Char8 as BS
newtype Hash = Hash { unHash :: ByteString }
deriving (Eq)
hashContent :: ByteString -> Hash
hashContent = Hash . encode . hash 64 mempty
{-# INLINE hashContent #-}
hashFile :: ByteString -> FilePath -> FilePath
hashFile content file = BS.unpack (unHash $ hashContent content) ++ "-" ++ file
{-# INLINE hashFile #-}
hashStore :: FilePath
-> (ByteString -> IO ByteString)
-> (String, ByteString)
-> IO String
hashStore storePath action (name, actionInput) = do
createDirectoryIfMissing True storePath
let hashName = hashFile actionInput name
let storeName = storePath </> hashName
isUpToDate <- doesFileExist storeName
if isUpToDate then
pure hashName
else do
actionOutput <- action actionInput
BS.writeFile storeName actionOutput
pure hashName
hashStoreWithContent :: FilePath
-> (ByteString -> IO ByteString)
-> (String, ByteString)
-> IO (String, ByteString)
hashStoreWithContent storePath action (name, actionInput) = do
createDirectoryIfMissing True storePath
let hashName = hashFile actionInput name
let storeName = storePath </> hashName
isUpToDate <- doesFileExist storeName
if isUpToDate then do
fileContent <- BS.readFile storeName
pure (hashName, fileContent)
else do
newFileContent <- action actionInput
BS.writeFile storeName newFileContent
pure (hashName, newFileContent)