PDF: Removed TeXError type, just return a bytestring.
This commit is contained in:
parent
50e16e6855
commit
c9c78344b1
2 changed files with 8 additions and 18 deletions
|
@ -46,19 +46,20 @@ import Text.Pandoc.UTF8 as UTF8
|
||||||
|
|
||||||
tex2pdf :: TeXProgram
|
tex2pdf :: TeXProgram
|
||||||
-> String -- ^ latex source
|
-> String -- ^ latex source
|
||||||
-> IO (Either TeXError ByteString)
|
-> IO (Either ByteString ByteString)
|
||||||
tex2pdf program source = withSystemTempDirectory "tex2pdf" $ \tmpdir ->
|
tex2pdf program source = withSystemTempDirectory "tex2pdf" $ \tmpdir ->
|
||||||
tex2pdf' tmpdir program source
|
tex2pdf' tmpdir program source
|
||||||
|
|
||||||
tex2pdf' :: FilePath -- ^ temp directory for output
|
tex2pdf' :: FilePath -- ^ temp directory for output
|
||||||
-> TeXProgram
|
-> TeXProgram
|
||||||
-> String -- ^ tex source
|
-> String -- ^ tex source
|
||||||
-> IO (Either TeXError ByteString)
|
-> IO (Either ByteString ByteString)
|
||||||
tex2pdf' tmpDir program source = do
|
tex2pdf' tmpDir program source = do
|
||||||
(exit, log', mbPdf) <- runTeXProgram program 3 tmpDir source
|
(exit, log', mbPdf) <- runTeXProgram program 3 tmpDir source
|
||||||
case (exit, mbPdf) of
|
case (exit, mbPdf) of
|
||||||
(ExitFailure ec, _) -> return $ Left $ extractTeXError ec log'
|
(ExitFailure _, _) -> return $ Left $ extractMsg log'
|
||||||
(ExitSuccess, Nothing) -> error "tex2pdf: ExitSuccess but no PDF created!"
|
(ExitSuccess, Nothing) -> return $ Left
|
||||||
|
"tex2pdf: ExitSuccess but no PDF created!"
|
||||||
(ExitSuccess, Just pdf) -> return $ Right pdf
|
(ExitSuccess, Just pdf) -> return $ Right pdf
|
||||||
|
|
||||||
data TeXProgram = PDFLaTeX
|
data TeXProgram = PDFLaTeX
|
||||||
|
@ -69,18 +70,8 @@ data TeXProgram = PDFLaTeX
|
||||||
| PDFTeX
|
| PDFTeX
|
||||||
deriving (Show, Read)
|
deriving (Show, Read)
|
||||||
|
|
||||||
data TeXError = TeXError { exitCode :: Int
|
|
||||||
, message :: ByteString
|
|
||||||
, fullLog :: ByteString
|
|
||||||
} deriving (Show, Read)
|
|
||||||
|
|
||||||
-- parsing output
|
-- parsing output
|
||||||
|
|
||||||
extractTeXError :: Int -> ByteString -> TeXError
|
|
||||||
extractTeXError ec log' = TeXError { exitCode = ec
|
|
||||||
, message = extractMsg log'
|
|
||||||
, fullLog = log' }
|
|
||||||
|
|
||||||
extractMsg :: ByteString -> ByteString
|
extractMsg :: ByteString -> ByteString
|
||||||
extractMsg log' = do
|
extractMsg log' = do
|
||||||
let msg' = dropWhile (not . ("!" `BC.isPrefixOf`)) $ BC.lines log'
|
let msg' = dropWhile (not . ("!" `BC.isPrefixOf`)) $ BC.lines log'
|
||||||
|
@ -134,8 +125,7 @@ runTeXProgram program runsLeft tmpDir source = do
|
||||||
-- 'readProcessWithExitCode' from 'System.Process'.)
|
-- 'readProcessWithExitCode' from 'System.Process'.)
|
||||||
readCommand :: FilePath -- ^ command to run
|
readCommand :: FilePath -- ^ command to run
|
||||||
-> [String] -- ^ any arguments
|
-> [String] -- ^ any arguments
|
||||||
-> IO (ExitCode,ByteString,ByteString) -- ^ exitcode, stdout, stderr
|
-> IO (ExitCode,ByteString,ByteString) -- ^ exit, stdout, stderr
|
||||||
|
|
||||||
readCommand cmd args = do
|
readCommand cmd args = do
|
||||||
(Just inh, Just outh, Just errh, pid) <-
|
(Just inh, Just outh, Just errh, pid) <-
|
||||||
createProcess (proc cmd args){ std_in = CreatePipe,
|
createProcess (proc cmd args){ std_in = CreatePipe,
|
||||||
|
@ -156,5 +146,4 @@ readCommand cmd args = do
|
||||||
hClose outh
|
hClose outh
|
||||||
-- wait on the process
|
-- wait on the process
|
||||||
ex <- waitForProcess pid
|
ex <- waitForProcess pid
|
||||||
return (ex, out, err)
|
return (ex, out, err)
|
||||||
|
|
|
@ -30,6 +30,7 @@ writers.
|
||||||
-}
|
-}
|
||||||
module Main where
|
module Main where
|
||||||
import Text.Pandoc
|
import Text.Pandoc
|
||||||
|
import Text.Pandoc.PDF (tex2pdf)
|
||||||
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
|
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
|
||||||
headerShift, findDataFile, normalize )
|
headerShift, findDataFile, normalize )
|
||||||
import Text.Pandoc.SelfContained ( makeSelfContained )
|
import Text.Pandoc.SelfContained ( makeSelfContained )
|
||||||
|
|
Loading…
Add table
Reference in a new issue