module Hakyll.Process
(
newExtension
, newExtOutFilePath
, execName
, execCompiler
, execCompilerWith
, unsafeExecCompiler
, 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
let outputReader = cOutToFileContents input out
unsafeExecCompiler name args outputReader
unsafeExecCompiler ::
ExecutableName
-> [String]
-> (B.ByteString -> IO B.ByteString)
-> Compiler (Item B.ByteString)
unsafeExecCompiler (ExecutableName exName) args outputReader =
do
results <- unsafeCompiler $ procResults
oldBody <- getResourceString
pure $ itemSetBody results oldBody
where
procResults = withProcessWait procConf waitOutput
procConf = setStdout byteStringOutput . proc exName $ args
waitOutput process = do
let stmProc = getStdout process
out <- atomically stmProc
checkExitCode process
outputReader out
cOutToFileContents :: FilePath -> CompilerOut -> B.ByteString -> IO B.ByteString
cOutToFileContents _ CStdOut out = pure out
cOutToFileContents _ (COutFile (SpecificPath f)) _ = B.readFile f
cOutToFileContents input (COutFile (RelativePath f)) _ = B.readFile (f input)
hargToArg :: FilePath -> ExecutableArg -> String
hargToArg _ (ProcArg s) = s
hargToArg f HakFilePath = f