aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/PDF.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/PDF.hs')
-rw-r--r--src/Text/Pandoc/PDF.hs27
1 files changed, 15 insertions, 12 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index 4dfa1d827..a5f1597bd 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -56,11 +56,11 @@ import Data.List (intercalate)
#endif
withTempDir :: String -> (FilePath -> IO a) -> IO a
-withTempDir f =
+withTempDir =
#ifdef _WINDOWS
- withTempDirectory "." (f . changePathSeparators)
+ withTempDirectory "."
#else
- withSystemTempDirectory f
+ withSystemTempDirectory
#endif
#ifdef _WINDOWS
@@ -99,8 +99,7 @@ handleImage' baseURL tmpdir (Image ils (src,tit)) = do
let ext = fromMaybe (takeExtension src) $
extensionFromMimeType mime
let basename = UTF8.toString $ B64.encode $ UTF8.fromString src
- -- note: we want / even on Windows, for TexLive:
- let fname = tmpdir ++ "/" ++ basename <.> ext
+ let fname = tmpdir </> basename <.> ext
BS.writeFile fname contents
return $ Image ils (fname,tit)
_ -> do
@@ -152,18 +151,22 @@ extractMsg log' = do
runTeXProgram :: String -> Int -> FilePath -> String
-> IO (ExitCode, ByteString, Maybe ByteString)
runTeXProgram program runsLeft tmpDir source = do
- let file = tmpDir ++ "/input.tex"
+ let file = tmpDir </> "input.tex"
exists <- doesFileExist file
unless exists $ UTF8.writeFile file source
- let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
- "-output-directory", tmpDir, file]
- env' <- getEnvironment
#ifdef _WINDOWS
- let sep = ";"
+ -- note: we want / even on Windows, for TexLive
+ let tmpDir' = changePathSeparators tmpDir
+ let file' = changePathSeparators file
#else
- let sep = ":"
+ let tmpDir' = tmpDir
+ let file' = file
#endif
- let texinputs = maybe (tmpDir ++ sep) ((tmpDir ++ sep) ++)
+ let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
+ "-output-directory", tmpDir', file']
+ env' <- getEnvironment
+ let sep = searchPathSeparator:[]
+ let texinputs = maybe (tmpDir' ++ sep) ((tmpDir' ++ sep) ++)
$ lookup "TEXINPUTS" env'
let env'' = ("TEXINPUTS", texinputs) :
[(k,v) | (k,v) <- env', k /= "TEXINPUTS"]