{-# LANGUAGE DeriveAnyClass #-}
module Pier.Core.Internal.Store
(
HandleTemps(..),
withPierTempDirectory,
withPierTempDirectoryAction,
pierDir,
artifactDir,
Hash,
hashString,
hashDir,
makeHash,
createArtifacts,
unfreezeArtifacts,
SharedCache(..),
hashExternalFile,
Artifact(..),
Source(..),
builtArtifact,
external,
(/>),
storeRules,
) where
import Control.Monad (forM_, when, void)
import Control.Monad.IO.Class
import Crypto.Hash.SHA256 (hashlazy, hash)
import Data.ByteString.Base64 (encode)
import Development.Shake
import Development.Shake.Classes hiding (hash)
import Development.Shake.FilePath
import GHC.Generics
import System.Directory as Directory
import System.IO.Temp
import qualified Data.Binary as Binary
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Data.List as List
import Pier.Core.Internal.Directory
pierDir :: FilePath
pierDir = "_pier"
data HandleTemps = RemoveTemps | KeepTemps
withPierTempDirectoryAction
:: HandleTemps -> String -> (FilePath -> Action a) -> Action a
withPierTempDirectoryAction KeepTemps template f =
createPierTempDirectory template >>= f
withPierTempDirectoryAction RemoveTemps template f = do
tmp <- createPierTempDirectory template
f tmp `actionFinally` removeDirectoryRecursive tmp
withPierTempDirectory
:: HandleTemps -> String -> (FilePath -> IO a) -> IO a
withPierTempDirectory KeepTemps template f =
createPierTempDirectory template >>= f
withPierTempDirectory RemoveTemps template f = do
createDirectoryIfMissing True pierTempDirectory
withTempDirectory pierTempDirectory template f
pierTempDirectory :: String
pierTempDirectory = pierDir </> "tmp"
createPierTempDirectory :: MonadIO m => String -> m FilePath
createPierTempDirectory template = liftIO $ do
createDirectoryIfMissing True pierTempDirectory
createTempDirectory pierTempDirectory template
newtype Hash = Hash B.ByteString
deriving (Show, Eq, Ord, Binary, NFData, Hashable, Generic)
makeHash :: Binary a => a -> Action Hash
makeHash x = do
version <- askOracle GetArtifactVersion
return . Hash . fixChars . dropPadding . encode . hashlazy . Binary.encode
. tagVersion version
$ x
where
fixChars = BC.map $ \case
'/' -> '_'
c -> c
dropPadding c
| BC.last c == '=' = BC.init c
| otherwise = c
tagVersion = (,)
hashExternalFile :: FilePath -> IO B.ByteString
hashExternalFile = fmap hash . B.readFile
newtype ArtifactVersion = ArtifactVersion Int
deriving (Show,Typeable,Eq,Hashable,Binary,NFData,Generic)
data GetArtifactVersion = GetArtifactVersion
deriving (Show,Typeable,Eq,Hashable,Binary,NFData,Generic)
type instance RuleResult GetArtifactVersion = ArtifactVersion
artifactVersionRule :: Rules ()
artifactVersionRule = void $ addOracle $ \GetArtifactVersion
-> return $ ArtifactVersion 1
hashDir :: Hash -> FilePath
hashDir h = artifactDir </> hashString h
hashString :: Hash -> String
hashString (Hash h) = BC.unpack h
storeRules :: Rules ()
storeRules = artifactVersionRule
newtype SharedCache = SharedCache FilePath
globalHashDir :: SharedCache -> Hash -> FilePath
globalHashDir (SharedCache f) h = f </> hashString h
createArtifacts ::
Maybe SharedCache
-> Hash
-> [String]
-> (FilePath -> Action ())
-> Action ()
createArtifacts maybeSharedCache h messages act = do
let destDir = hashDir h
exists <- liftIO $ Directory.doesDirectoryExist destDir
if exists
then mapM_ cacheMessage messages
else do
tempDir <- createPierTempDirectory $ hashString h ++ "-result"
case maybeSharedCache of
Nothing -> act tempDir
Just cache -> do
getFromSharedCache <- liftIO $ copyFromCache cache h tempDir
if getFromSharedCache
then mapM_ sharedCacheMessage messages
else do
act tempDir
liftIO $ copyToCache cache h tempDir
liftIO $ finish tempDir destDir
where
cacheMessage m = putNormal $ "(from cache: " ++ m ++ ")"
sharedCacheMessage m = putNormal $ "(from shared cache: " ++ m ++ ")"
finish tempDir destDir = do
let freeze RegularFile = freezePath
freeze DirectoryEnd = freezePath
freeze _ = const $ return ()
getRegularContents tempDir
>>= mapM_ (forFileRecursive_ freeze . (tempDir </>))
createParentIfMissing destDir
Directory.renameDirectory tempDir destDir
freezePath destDir
copyFromCache :: SharedCache -> Hash -> FilePath -> IO Bool
copyFromCache cache h tempDir = do
let globalDir = globalHashDir cache h
globalExists <- liftIO $ Directory.doesDirectoryExist globalDir
if globalExists
then copyDirectory globalDir tempDir >> return True
else return False
copyToCache :: SharedCache -> Hash -> FilePath -> IO ()
copyToCache cache h src = do
tempDir <- createPierTempDirectory $ hashString h ++ "-cache"
copyDirectory src tempDir
let dest = globalHashDir cache h
createParentIfMissing dest
Directory.renameDirectory tempDir dest
artifactDir :: FilePath
artifactDir = pierDir </> "artifact"
freezePath :: FilePath -> IO ()
freezePath f =
getPermissions f >>= setPermissions f . setOwnerWritable False
unfreezeArtifacts :: IO ()
unfreezeArtifacts = forM_ [artifactDir, pierTempDirectory] $ \dir -> do
exists <- Directory.doesDirectoryExist dir
when exists $ forFileRecursive_ unfreeze dir
where
unfreeze DirectoryStart f =
getPermissions f >>= setPermissions f . setOwnerWritable True
unfreeze _ _ = return ()
data Artifact = Artifact Source FilePath
deriving (Eq, Ord, Generic, Hashable, Binary, NFData)
instance Show Artifact where
show (Artifact External f) = "external:" ++ show f
show (Artifact (Built h) f) = hashString h ++ ":" ++ show f
data Source = Built Hash | External
deriving (Show, Eq, Ord, Generic, Hashable, Binary, NFData)
builtArtifact :: Hash -> FilePath -> Artifact
builtArtifact h = Artifact (Built h) . normaliseMore
external :: FilePath -> Artifact
external f
| null f' = error "external: empty input"
| artifactDir `List.isPrefixOf` f' = error $ "external: forbidden prefix: " ++ show f'
| otherwise = Artifact External f'
where
f' = normaliseMore f
normaliseMore :: FilePath -> FilePath
normaliseMore = dropTrailingPathSeparator . normalise
(/>) :: Artifact -> FilePath -> Artifact
Artifact source f /> g = Artifact source $ normaliseMore $ f </> g
infixr 5 />