PDF: Use / as path separators in latex input only
Fixes compile error on Windows for 5040f3e
Reverted back to canonical file separators </> in all places except for
arguments to the LaTeX builder and in TEXINPUTS
See #1151.
Note: Temporary directories still fail to be removed in Windows due to
call of ByteString.Lazy.readFile creating process ownership of the
compiled pdf file.
This commit is contained in:
parent
5040f3ede0
commit
1aed9208f8
1 changed files with 15 additions and 12 deletions
|
@ -56,11 +56,11 @@ import Data.List (intercalate)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
withTempDir :: String -> (FilePath -> IO a) -> IO a
|
withTempDir :: String -> (FilePath -> IO a) -> IO a
|
||||||
withTempDir f =
|
withTempDir =
|
||||||
#ifdef _WINDOWS
|
#ifdef _WINDOWS
|
||||||
withTempDirectory "." (f . changePathSeparators)
|
withTempDirectory "."
|
||||||
#else
|
#else
|
||||||
withSystemTempDirectory f
|
withSystemTempDirectory
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
#ifdef _WINDOWS
|
#ifdef _WINDOWS
|
||||||
|
@ -99,8 +99,7 @@ handleImage' baseURL tmpdir (Image ils (src,tit)) = do
|
||||||
let ext = fromMaybe (takeExtension src) $
|
let ext = fromMaybe (takeExtension src) $
|
||||||
extensionFromMimeType mime
|
extensionFromMimeType mime
|
||||||
let basename = UTF8.toString $ B64.encode $ UTF8.fromString src
|
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
|
BS.writeFile fname contents
|
||||||
return $ Image ils (fname,tit)
|
return $ Image ils (fname,tit)
|
||||||
_ -> do
|
_ -> do
|
||||||
|
@ -152,18 +151,22 @@ extractMsg log' = do
|
||||||
runTeXProgram :: String -> Int -> FilePath -> String
|
runTeXProgram :: String -> Int -> FilePath -> String
|
||||||
-> IO (ExitCode, ByteString, Maybe ByteString)
|
-> IO (ExitCode, ByteString, Maybe ByteString)
|
||||||
runTeXProgram program runsLeft tmpDir source = do
|
runTeXProgram program runsLeft tmpDir source = do
|
||||||
let file = tmpDir ++ "/input.tex"
|
let file = tmpDir </> "input.tex"
|
||||||
exists <- doesFileExist file
|
exists <- doesFileExist file
|
||||||
unless exists $ UTF8.writeFile file source
|
unless exists $ UTF8.writeFile file source
|
||||||
let programArgs = ["-halt-on-error", "-interaction", "nonstopmode",
|
|
||||||
"-output-directory", tmpDir, file]
|
|
||||||
env' <- getEnvironment
|
|
||||||
#ifdef _WINDOWS
|
#ifdef _WINDOWS
|
||||||
let sep = ";"
|
-- note: we want / even on Windows, for TexLive
|
||||||
|
let tmpDir' = changePathSeparators tmpDir
|
||||||
|
let file' = changePathSeparators file
|
||||||
#else
|
#else
|
||||||
let sep = ":"
|
let tmpDir' = tmpDir
|
||||||
|
let file' = file
|
||||||
#endif
|
#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'
|
$ lookup "TEXINPUTS" env'
|
||||||
let env'' = ("TEXINPUTS", texinputs) :
|
let env'' = ("TEXINPUTS", texinputs) :
|
||||||
[(k,v) | (k,v) <- env', k /= "TEXINPUTS"]
|
[(k,v) | (k,v) <- env', k /= "TEXINPUTS"]
|
||||||
|
|
Loading…
Add table
Reference in a new issue