{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TypeOperators #-}
module Pier.Core.Artifact
(
artifactRules
, SharedCache(..)
, HandleTemps(..)
, Artifact
, external
, (/>)
, replaceArtifactExtension
, readArtifact
, readArtifactB
, doesArtifactExist
, matchArtifactGlob
, unfreezeArtifacts
, callArtifact
, writeArtifact
, runCommand
, runCommandOutput
, runCommand_
, runCommandStdout
, Command
, message
, Output
, output
, input
, inputs
, inputList
, shadow
, groupFiles
, prog
, progA
, progTemp
, pathIn
, withCwd
, createDirectoryA
) where
import Control.Monad (forM_, when, unless)
import Control.Monad.IO.Class
import Data.Set (Set)
import Development.Shake
import Development.Shake.Classes
import Development.Shake.FilePath
import Distribution.Simple.Utils (matchDirFileGlob)
import GHC.Generics
import System.Directory as Directory
import System.Exit (ExitCode(..))
import System.Process.Internals (translate)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Encoding.Error as T hiding (replace)
import Pier.Core.Internal.Directory
import Pier.Core.Internal.HashableSet
import Pier.Core.Internal.Store
import Pier.Core.Persistent
data Command = Command
{ _commandProgs :: [Prog]
, commandInputs :: HashableSet Artifact
}
deriving (Typeable, Eq, Generic, Hashable, Binary, NFData)
data Call
= CallEnv String
| CallArtifact Artifact
| CallTemp FilePath
deriving (Typeable, Eq, Generic, Hashable, Binary, NFData)
data Prog
= ProgCall { _progCall :: Call
, _progArgs :: [String]
, progCwd :: FilePath
}
| Message String
| Shadow Artifact FilePath
deriving (Typeable, Eq, Generic, Hashable, Binary, NFData)
instance Monoid Command where
Command ps is `mappend` Command ps' is' = Command (ps ++ ps') (is <> is')
mempty = Command [] mempty
instance Semigroup Command where
(<>) = mappend
prog :: String -> [String] -> Command
prog p as = Command [ProgCall (CallEnv p) as "."] mempty
progA :: Artifact -> [String] -> Command
progA p as = Command [ProgCall (CallArtifact p) as "."]
$ HashableSet $ Set.singleton p
progTemp :: FilePath -> [String] -> Command
progTemp p as = Command [ProgCall (CallTemp p) as "."] mempty
message :: String -> Command
message s = Command [Message s] mempty
withCwd :: FilePath -> Command -> Command
withCwd path (Command ps as)
| isAbsolute path = error $ "withCwd: expected relative path, got " ++ show path
| otherwise = Command (map setPath ps) as
where
setPath m@Message{} = m
setPath p = p { progCwd = path }
input :: Artifact -> Command
input = inputs . Set.singleton
inputList :: [Artifact] -> Command
inputList = inputs . Set.fromList
inputs :: Set Artifact -> Command
inputs = Command [] . HashableSet
shadow :: Artifact -> FilePath -> Command
shadow a f
| isAbsolute f = error $ "shadowArtifact: need relative destination, found "
++ show f
| otherwise = Command [Shadow a f] mempty
data Output a = Output [FilePath] (Hash -> a)
instance Functor Output where
fmap f (Output g h) = Output g (f . h)
instance Applicative Output where
pure = Output [] . const
Output f g <*> Output f' g' = Output (f ++ f') (g <*> g')
output :: FilePath -> Output Artifact
output f
| ds `elem` [[], ["."]] = error $ "can't output empty path " ++ show f
| ".." `elem` ds = error $ "output: can't have \"..\" as a path component: "
++ show f
| normalise f == "." = error $ "Can't output empty path " ++ show f
| isAbsolute f = error $ "Can't output absolute path " ++ show f
| otherwise = Output [f] $ flip builtArtifact f
where
ds = splitDirectories f
externalArtifactDir :: FilePath
externalArtifactDir = artifactDir </> "external"
artifactRules :: Maybe SharedCache -> HandleTemps -> Rules ()
artifactRules cache ht = do
liftIO createExternalLink
commandRules cache ht
writeArtifactRules cache
storeRules
createExternalLink :: IO ()
createExternalLink = do
exists <- doesPathExist externalArtifactDir
unless exists $ do
createParentIfMissing externalArtifactDir
createDirectoryLink "../.." externalArtifactDir
data CommandQ = CommandQ
{ commandQCmd :: Command
, _commandQOutputs :: [FilePath]
}
deriving (Eq, Generic)
instance Show CommandQ where
show CommandQ { commandQCmd = Command progs _ }
= let msgs = List.intercalate "; " [m | Message m <- progs]
in "Command" ++
if null msgs
then ""
else ": " ++ msgs
instance Hashable CommandQ
instance Binary CommandQ
instance NFData CommandQ
type instance RuleResult CommandQ = Hash
commandHash :: CommandQ -> Action Hash
commandHash cmdQ = do
let externalFiles = [f | Artifact External f <- Set.toList
. unHashableSet
. commandInputs
$ commandQCmd cmdQ
, isRelative f
]
need externalFiles
userFileHashes <- liftIO $ mapM hashExternalFile externalFiles
makeHash ("commandHash", cmdQ, userFileHashes)
runCommand :: Output t -> Command -> Action t
runCommand (Output outs mk) c
= mk <$> askPersistent (CommandQ c outs)
runCommandOutput :: FilePath -> Command -> Action Artifact
runCommandOutput f = runCommand (output f)
runCommandStdout :: Command -> Action String
runCommandStdout c = do
out <- runCommandOutput stdoutOutput c
liftIO $ readFile $ pathIn out
runCommand_ :: Command -> Action ()
runCommand_ = runCommand (pure ())
commandRules :: Maybe SharedCache -> HandleTemps -> Rules ()
commandRules sharedCache ht = addPersistent $ \cmdQ@(CommandQ (Command progs inps) outs) -> do
putChatty $ showCommand cmdQ
h <- commandHash cmdQ
createArtifacts sharedCache h (progMessages progs) $ \resultDir ->
withPierTempDirectoryAction ht (hashString h) $ \tmpDir -> do
let tmpPathOut = (tmpDir </>)
liftIO $ collectInputs (unHashableSet inps) tmpDir
mapM_ (createParentIfMissing . tmpPathOut) outs
root <- liftIO getCurrentDirectory
stdoutStr <- B.concat <$> mapM (readProg (root </> tmpDir)) progs
let stdoutPath = tmpPathOut stdoutOutput
createParentIfMissing stdoutPath
liftIO $ B.writeFile stdoutPath stdoutStr
liftIO $ forM_ outs $ \f -> do
let src = tmpPathOut f
let dest = resultDir </> f
exist <- Directory.doesPathExist src
unless exist $
error $ "runCommand: missing output "
++ show f
++ " in temporary directory "
++ show tmpDir
createParentIfMissing dest
renamePath src dest
return h
putChatty :: String -> Action ()
putChatty s = do
v <- shakeVerbosity <$> getShakeOptions
when (v >= Chatty) $ putNormal s
progMessages :: [Prog] -> [String]
progMessages ps = [m | Message m <- ps]
collectInputs :: Set Artifact -> FilePath -> IO ()
collectInputs inps tmp = do
let inps' = dedupArtifacts inps
checkAllDistinctPaths inps'
liftIO $ mapM_ (linkArtifact tmp) inps'
readProg :: FilePath -> Prog -> Action B.ByteString
readProg _ (Message s) = do
putNormal s
return B.empty
readProg dir (ProgCall p as cwd) = readProgCall dir p as cwd
readProg dir (Shadow a0 f0) = do
liftIO $ linkShadow dir a0 f0
return B.empty
readProgCall :: FilePath -> Call -> [String] -> FilePath -> Action BC.ByteString
readProgCall dir p as cwd = do
let p' = case p of
CallEnv s -> s
CallArtifact f -> dir </> pathIn f
CallTemp f -> dir </> f
(ret, Stdout out, Stderr err)
<- quietly $ command
[ Cwd $ dir </> cwd
, Env defaultEnv
, EchoStderr False
]
p' (map (spliceTempDir dir) as)
let errStr = T.unpack . T.decodeUtf8With T.lenientDecode $ err
case ret of
ExitSuccess -> return out
ExitFailure ec -> do
v <- shakeVerbosity <$> getShakeOptions
fail $ if v < Loud
then errStr
else unlines
[ showProg (ProgCall p as cwd)
, "Working dir: " ++ translate (dir </> cwd)
, "Exit code: " ++ show ec
, "Stderr:"
, errStr
]
linkShadow :: FilePath -> Artifact -> FilePath -> IO ()
linkShadow dir a0 f0 = do
createParentIfMissing (dir </> f0)
loop a0 f0
where
loop a f = do
let aPath = pathIn a
isDir <- Directory.doesDirectoryExist aPath
if isDir
then do
Directory.createDirectoryIfMissing False (dir </> f)
cs <- getRegularContents aPath
mapM_ (\c -> loop (a /> c) (f </> c)) cs
else do
srcExists <- Directory.doesFileExist aPath
destExists <- Directory.doesPathExist (dir </> f)
let aPath' = case a of
Artifact External aa -> "external" </> aa
Artifact (Built h) aa -> hashString h </> aa
if
| not srcExists -> error $ "linkShadow: missing source "
++ show aPath
| destExists -> error $ "linkShadow: destination already exists: "
++ show f
| otherwise -> createFileLink
(relPathUp f </> "../../artifact" </> aPath')
(dir </> f)
relPathUp = joinPath . map (const "..") . splitDirectories . parentDirectory
showProg :: Prog -> String
showProg (Shadow a f) = unwords ["Shadow:", pathIn a, "=>", f]
showProg (Message m) = "Message: " ++ show m
showProg (ProgCall call args cwd) =
wrapCwd
. List.intercalate " \\\n "
$ showCall call : args
where
wrapCwd s = case cwd of
"." -> s
_ -> "(cd " ++ translate cwd ++ " &&\n " ++ s ++ ")"
showCall (CallArtifact a) = pathIn a
showCall (CallEnv f) = f
showCall (CallTemp f) = f
showCommand :: CommandQ -> String
showCommand (CommandQ (Command progs inps) outputs) = unlines $
map showOutput outputs
++ map showInput (Set.toList $ unHashableSet inps)
++ map showProg progs
where
showOutput a = "Output: " ++ a
showInput i = "Input: " ++ pathIn i
stdoutOutput :: FilePath
stdoutOutput = "_stdout"
defaultEnv :: [(String, String)]
defaultEnv =
[ ("PATH", "/usr/bin:/bin")
, ("LANG", "en_US.UTF-8")
]
spliceTempDir :: FilePath -> String -> String
spliceTempDir tmp = T.unpack . T.replace (T.pack "${TMPDIR}") (T.pack tmp) . T.pack
checkAllDistinctPaths :: Monad m => [Artifact] -> m ()
checkAllDistinctPaths as =
case Map.keys . Map.filter (> 1) . Map.fromListWith (+)
. map (\a -> (pathIn a, 1 :: Integer)) $ as of
[] -> return ()
fs -> error $ "Artifacts generated from more than one command: " ++ show fs
dedupArtifacts :: Set Artifact -> [Artifact]
dedupArtifacts = loop . Set.toAscList
where
loop (a@(Artifact (Built h) f) : Artifact (Built h') f' : fs)
| h == h', (f <//> "*") ?== f' = loop (a:fs)
loop (f:fs) = f : loop fs
loop [] = []
linkArtifact :: FilePath -> Artifact -> IO ()
linkArtifact _ (Artifact External f)
| isAbsolute f = return ()
linkArtifact dir a = do
curDir <- getCurrentDirectory
let realPath = curDir </> realPathIn a
let localPath = dir </> pathIn a
createParentIfMissing localPath
isFile <- Directory.doesFileExist realPath
if isFile
then createFileLink realPath localPath
else do
isDir <- Directory.doesDirectoryExist realPath
if isDir
then createDirectoryLink realPath localPath
else error $ "linkArtifact: source does not exist: " ++ show realPath
++ " for artifact " ++ show a
pathIn :: Artifact -> FilePath
pathIn (Artifact External f) = externalArtifactDir </> f
pathIn (Artifact (Built h) f) = hashDir h </> f
realPathIn :: Artifact -> FilePath
realPathIn (Artifact External f) = f
realPathIn (Artifact (Built h) f) = hashDir h </> f
replaceArtifactExtension :: Artifact -> String -> Artifact
replaceArtifactExtension (Artifact s f) ext
= Artifact s $ replaceExtension f ext
readArtifact :: Artifact -> Action String
readArtifact (Artifact External f) = readFile' f
readArtifact f = liftIO $ readFile $ pathIn f
readArtifactB :: Artifact -> Action B.ByteString
readArtifactB (Artifact External f) = need [f] >> liftIO (B.readFile f)
readArtifactB f = liftIO $ B.readFile $ pathIn f
data WriteArtifactQ = WriteArtifactQ
{ writePath :: FilePath
, writeContents :: String
}
deriving (Eq, Typeable, Generic, Hashable, Binary, NFData)
instance Show WriteArtifactQ where
show w = "Write " ++ writePath w
type instance RuleResult WriteArtifactQ = Artifact
writeArtifact :: FilePath -> String -> Action Artifact
writeArtifact path contents = askPersistent $ WriteArtifactQ path contents
writeArtifactRules :: Maybe SharedCache -> Rules ()
writeArtifactRules sharedCache = addPersistent
$ \WriteArtifactQ {writePath = path, writeContents = contents} -> do
h <- makeHash . T.encodeUtf8 . T.pack
$ "writeArtifact: " ++ contents
createArtifacts sharedCache h [] $ \tmpDir -> do
let out = tmpDir </> path
createParentIfMissing out
liftIO $ writeFile out contents
return $ builtArtifact h path
doesArtifactExist :: Artifact -> Action Bool
doesArtifactExist (Artifact External f) = Development.Shake.doesFileExist f
doesArtifactExist f = liftIO $ Directory.doesFileExist (pathIn f)
matchArtifactGlob :: Artifact -> FilePath -> Action [FilePath]
matchArtifactGlob (Artifact External f) g
= getDirectoryFiles f [g]
matchArtifactGlob a g
= liftIO $ matchDirFileGlob (pathIn a) g
callArtifact :: HandleTemps -> Set Artifact -> Artifact -> [String] -> IO ()
callArtifact ht inps bin args = withPierTempDirectory ht "exec" $ \tmp -> do
dir <- getCurrentDirectory
collectInputs (Set.insert bin inps) tmp
cmd_ [Cwd tmp]
(dir </> tmp </> pathIn bin) args
createDirectoryA :: FilePath -> Command
createDirectoryA f = prog "mkdir" ["-p", f]
groupFiles :: Artifact -> [(FilePath, FilePath)] -> Action Artifact
groupFiles dir files = let out = "group"
in runCommandOutput out
$ createDirectoryA out
<> foldMap (\(f, g) -> shadow (dir /> f) (out </> g))
files