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 :: String
-> [String]
-> [String]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex String
command [String]
args [String]
extras ByteString
source =
String
-> (String -> IO (ExitCode, TexLog, Maybe ByteString))
-> IO (ExitCode, TexLog, Maybe ByteString)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> m a) -> m a
withSystemTempDirectory String
"texrunner." ((String -> IO (ExitCode, TexLog, Maybe ByteString))
-> IO (ExitCode, TexLog, Maybe ByteString))
-> (String -> IO (ExitCode, TexLog, Maybe ByteString))
-> IO (ExitCode, TexLog, Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \String
path ->
String
-> String
-> [String]
-> [String]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex' String
path String
command [String]
args [String]
extras ByteString
source
runTex' :: FilePath
-> String
-> [String]
-> [FilePath]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex' :: String
-> String
-> [String]
-> [String]
-> ByteString
-> IO (ExitCode, TexLog, Maybe ByteString)
runTex' String
path String
command [String]
args [String]
extras ByteString
source = do
String -> ByteString -> IO ()
LC8.writeFile (String
path String -> String -> String
</> String
"texrunner.tex") ByteString
source
[(String, String)]
environment <- [String] -> [(String, String)] -> [(String, String)]
extraTexInputs (String
pathString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
extras) ([(String, String)] -> [(String, String)])
-> IO [(String, String)] -> IO [(String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(String, String)]
getEnvironment
let p :: CreateProcess
p = (String -> [String] -> CreateProcess
proc String
command (String
"texrunner.tex" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
args))
{ cwd = Just path
, std_in = CreatePipe
, std_out = CreatePipe
, env = Just environment
}
(Just Handle
inH, Just Handle
outH, Maybe Handle
_, ProcessHandle
pHandle) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p
Handle -> IO ()
hClose Handle
inH
ByteString
a <- Handle -> IO ByteString
C8.hGetContents Handle
outH
Handle -> IO ()
hClose Handle
outH
ExitCode
exitC <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pHandle
Bool
pdfExists <- String -> IO Bool
doesFileExist (String
path String -> String -> String
</> String
"texrunner.pdf")
Maybe ByteString
pdfFile <- if Bool
pdfExists
then ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
LC8.readFile (String
path String -> String -> String
</> String
"texrunner.pdf")
else Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
Bool
logExists <- String -> IO Bool
doesFileExist (String
path String -> String -> String
</> String
"texrunner.log")
Maybe ByteString
logFile <- if Bool
logExists
then ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
C8.readFile (String
path String -> String -> String
</> String
"texrunner.log")
else Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
(ExitCode, TexLog, Maybe ByteString)
-> IO (ExitCode, TexLog, Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
exitC, ByteString -> TexLog
parseLog (ByteString -> TexLog) -> ByteString -> TexLog
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
a Maybe ByteString
logFile, Maybe ByteString
pdfFile)
extraTexInputs :: [FilePath] -> [(String,String)] -> [(String,String)]
[] = [(String, String)] -> [(String, String)]
forall a. a -> a
id
extraTexInputs [String]
inputss = (Maybe String -> Maybe String)
-> String -> [(String, String)] -> [(String, String)]
forall k a.
Eq k =>
(Maybe a -> Maybe a) -> k -> [(k, a)] -> [(k, a)]
alter Maybe String -> Maybe String
f String
"TEXINPUTS"
where
f :: Maybe String -> Maybe String
f Maybe String
Nothing = String -> Maybe String
forall a. a -> Maybe a
Just String
inputs
f (Just String
x) = String -> Maybe String
forall a. a -> Maybe a
Just (String
inputs String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Char
searchPathSeparator] String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x)
inputs :: String
inputs = (String -> String) -> [String] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Char
searchPathSeparator]) [String]
inputss
alter :: Eq k => (Maybe a -> Maybe a) -> k -> [(k,a)] -> [(k,a)]
alter :: forall k a.
Eq k =>
(Maybe a -> Maybe a) -> k -> [(k, a)] -> [(k, a)]
alter Maybe a -> Maybe a
f k
k = [(k, a)] -> [(k, a)]
go
where
go :: [(k, a)] -> [(k, a)]
go [] = Maybe (k, a) -> [(k, a)]
forall a. Maybe a -> [a]
maybeToList ((,) k
k (a -> (k, a)) -> Maybe a -> Maybe (k, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing)
go ((k
k',a
x):[(k, a)]
xs)
| k
k' k -> k -> Bool
forall a. Eq a => a -> a -> Bool
== k
k = case Maybe a -> Maybe a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
x) of
Just a
x' -> (k
k',a
x') (k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
: [(k, a)]
xs
Maybe a
Nothing -> [(k, a)]
xs
| Bool
otherwise = (k
k',a
x) (k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
: [(k, a)] -> [(k, a)]
go [(k, a)]
xs