module System.Texrunner
( runTex
, runTex'
, prettyPrintLog
) where
import Control.Applicative
import qualified Data.ByteString.Char8 as C8 hiding (concatMap)
import Data.ByteString.Lazy.Char8 as LC8 hiding (concatMap)
import Data.Maybe
import System.Directory
import System.Environment
import System.Exit
import System.FilePath
import System.IO
import System.IO.Temp
import System.Process
import System.Texrunner.Parse
runTex :: String
-> [String]
-> [FilePath]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex command args extras source =
withSystemTempDirectory "texrunner." $ \path ->
runTex' path command args extras source
runTex' :: FilePath
-> String
-> [String]
-> [FilePath]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex' path command args extras source = do
LC8.writeFile (path </> "texrunner.tex") source
environment <- extraTexInputs (path:extras) <$> getEnvironment
let p = (proc command ("texrunner.tex" : args))
{ cwd = Just path
, std_in = CreatePipe
, std_out = CreatePipe
, env = Just environment
}
(Just inH, Just outH, _, pHandle) <- createProcess p
hClose inH
a <- C8.hGetContents outH
hClose outH
exitC <- waitForProcess pHandle
pdfExists <- doesFileExist (path </> "texrunner.pdf")
pdfFile <- if pdfExists
then Just <$> LC8.readFile (path </> "texrunner.pdf")
else return Nothing
logExists <- doesFileExist (path </> "texrunner.log")
logFile <- if logExists
then Just <$> C8.readFile (path </> "texrunner.log")
else return Nothing
return (exitC, parseLog $ fromMaybe a logFile, pdfFile)
extraTexInputs :: [FilePath] -> [(String,String)] -> [(String,String)]
extraTexInputs [] = id
extraTexInputs inputss = alter f "TEXINPUTS"
where
f Nothing = Just inputs
f (Just x) = Just (inputs ++ [searchPathSeparator] ++ x)
inputs = concatMap (++ [searchPathSeparator]) inputss
alter :: Eq k => (Maybe a -> Maybe a) -> k -> [(k,a)] -> [(k,a)]
alter f k = go
where
go [] = maybeToList ((,) k <$> f Nothing)
go ((k',x):xs)
| k' == k = case f (Just x) of
Just x' -> (k',x') : xs
Nothing -> xs
| otherwise = (k',x) : go xs