PDF: On Windows, create temdir in working directory.
Reason: the path to the system temp directory may contain tildes, which causes problems in LaTeX when the username is more than eight characters. Closes #777.
This commit is contained in:
parent
fdd5f26d14
commit
26fefa040a
2 changed files with 12 additions and 2 deletions
|
@ -358,6 +358,8 @@ Executable pandoc
|
||||||
Ghc-Prof-Options: -auto-all -caf-all -rtsopts
|
Ghc-Prof-Options: -auto-all -caf-all -rtsopts
|
||||||
else
|
else
|
||||||
Ghc-Prof-Options: -auto-all -caf-all
|
Ghc-Prof-Options: -auto-all -caf-all
|
||||||
|
if os(windows)
|
||||||
|
Cpp-options: -D_WINDOWS
|
||||||
Default-Language: Haskell98
|
Default-Language: Haskell98
|
||||||
Default-Extensions: CPP
|
Default-Extensions: CPP
|
||||||
Other-Extensions: PatternGuards, OverloadedStrings,
|
Other-Extensions: PatternGuards, OverloadedStrings,
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings, CPP #-}
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>
|
Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>
|
||||||
|
|
||||||
|
@ -45,10 +45,18 @@ import Text.Pandoc.UTF8 as UTF8
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless)
|
||||||
import Data.List (isInfixOf)
|
import Data.List (isInfixOf)
|
||||||
|
|
||||||
|
withTempDir :: String -> (FilePath -> IO a) -> IO a
|
||||||
|
withTempDir =
|
||||||
|
#ifdef _WINDOWS
|
||||||
|
withTempDirectory "."
|
||||||
|
#else
|
||||||
|
withSystemTempDirectory
|
||||||
|
#endif
|
||||||
|
|
||||||
tex2pdf :: String -- ^ tex program (pdflatex, lualatex, xelatex)
|
tex2pdf :: String -- ^ tex program (pdflatex, lualatex, xelatex)
|
||||||
-> String -- ^ latex source
|
-> String -- ^ latex source
|
||||||
-> IO (Either ByteString ByteString)
|
-> IO (Either ByteString ByteString)
|
||||||
tex2pdf program source = withSystemTempDirectory "tex2pdf" $ \tmpdir ->
|
tex2pdf program source = withTempDir "tex2pdf." $ \tmpdir ->
|
||||||
tex2pdf' tmpdir program source
|
tex2pdf' tmpdir program source
|
||||||
|
|
||||||
tex2pdf' :: FilePath -- ^ temp directory for output
|
tex2pdf' :: FilePath -- ^ temp directory for output
|
||||||
|
|
Loading…
Reference in a new issue