module Hakyll.Process
(
newExtension
, newExtOutFilePath
, execName
, execCompiler
, execCompilerWith
, CompilerOut(..)
, ExecutableArg(..)
, ExecutableArgs
, ExecutableName
, OutFilePath(..)
) where
import qualified Data.ByteString.Lazy.Char8 as B
import GHC.Conc (atomically)
import Hakyll.Core.Item
import Hakyll.Core.Compiler
import System.Process.Typed
data CompilerOut =
CStdOut
| COutFile OutFilePath
data ExecutableArg =
HakFilePath
| ProcArg String deriving (Read, Show)
data OutFilePath =
SpecificPath FilePath
| RelativePath (FilePath -> FilePath)
newtype ExecutableName = ExecutableName String deriving (Read, Show)
type ExecutableArgs = [ExecutableArg]
newExtension :: String -> FilePath -> FilePath
newExtension ext f = (reverse . dropWhile (/= '.') . reverse $ f) <> ext
newExtOutFilePath :: String -> CompilerOut
newExtOutFilePath ext = COutFile $ RelativePath (newExtension ext)
execName :: String -> ExecutableName
execName = ExecutableName
execCompiler :: ExecutableName -> CompilerOut -> Compiler (Item B.ByteString)
execCompiler name out = execCompilerWith name [] out
execCompilerWith :: ExecutableName -> ExecutableArgs -> CompilerOut -> Compiler (Item B.ByteString)
execCompilerWith name exArgs out = do
input <- getResourceFilePath
let args = fmap (hargToArg input) exArgs
results <- unsafeCompiler $ runExecutable name args out input
oldBody <- getResourceString
pure $ itemSetBody results oldBody
runExecutable :: ExecutableName -> [String] -> CompilerOut -> FilePath -> IO B.ByteString
runExecutable (ExecutableName exName) args compilerOut inputFile = withProcessWait procConf waitOutput where
procConf = setStdout byteStringOutput . proc exName $ args
waitOutput process = do
let stmProc = getStdout process
out <- atomically stmProc
checkExitCode process
case compilerOut of
CStdOut -> pure out
COutFile (SpecificPath f) -> B.readFile f
COutFile (RelativePath f) -> B.readFile (f inputFile)
hargToArg :: FilePath -> ExecutableArg -> String
hargToArg _ (ProcArg s) = s
hargToArg f HakFilePath = f