diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 29df04d24..8533fe48c 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -449,7 +449,6 @@ convertWithOpts opts = do
           , writerEpubChapterLevel = optEpubChapterLevel opts
           , writerTOCDepth         = optTOCDepth opts
           , writerReferenceDoc     = optReferenceDoc opts
-          , writerPdfArgs          = optPdfEngineArgs opts
           , writerSyntaxMap        = syntaxMap
           }
 
@@ -512,14 +511,16 @@ convertWithOpts opts = do
       ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile
       TextWriter f -> case maybePdfProg of
         Just pdfProg -> do
-                res <- makePDF pdfProg f writerOptions doc
+                res <- makePDF pdfProg (optPdfEngineArgs opts) f
+                        writerOptions doc
                 case res of
                      Right pdf -> writeFnBinary outputFile pdf
                      Left err' -> liftIO $
                        E.throwIO $ PandocPDFError (UTF8.toStringLazy err')
         Nothing -> do
                 let htmlFormat = format `elem`
-                      ["html","html4","html5","s5","slidy","slideous","dzslides","revealjs"]
+                      ["html","html4","html5","s5","slidy",
+                       "slideous","dzslides","revealjs"]
                     handleEntities = if (htmlFormat ||
                                          format == "docbook4" ||
                                          format == "docbook5" ||
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 99c7afba7..d004abca4 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -221,7 +221,6 @@ data WriterOptions = WriterOptions
   , writerEpubChapterLevel  :: Int            -- ^ Header level for chapters (separate files)
   , writerTOCDepth          :: Int            -- ^ Number of levels to include in TOC
   , writerReferenceDoc      :: Maybe FilePath -- ^ Path to reference document if specified
-  , writerPdfArgs           :: [String]       -- ^ Flags to pass to pdf-engine
   , writerReferenceLocation :: ReferenceLocation    -- ^ Location of footnotes and references for writing markdown
   , writerSyntaxMap         :: SyntaxMap
   } deriving (Show, Data, Typeable, Generic)
@@ -256,7 +255,6 @@ instance Default WriterOptions where
                       , writerEpubChapterLevel = 1
                       , writerTOCDepth         = 3
                       , writerReferenceDoc     = Nothing
-                      , writerPdfArgs          = []
                       , writerReferenceLocation = EndOfDocument
                       , writerSyntaxMap        = defaultSyntaxMap
                       }
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index 797b5c138..f90a4454f 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -81,11 +81,12 @@ changePathSeparators = intercalate "/" . splitDirectories
 
 makePDF :: String              -- ^ pdf creator (pdflatex, lualatex, xelatex,
                                -- wkhtmltopdf, weasyprint, prince, context, pdfroff)
+        -> [String]            -- ^ arguments to pass to pdf creator
         -> (WriterOptions -> Pandoc -> PandocIO Text)  -- ^ writer
         -> WriterOptions       -- ^ options
         -> Pandoc              -- ^ document
         -> PandocIO (Either ByteString ByteString)
-makePDF "wkhtmltopdf" writer opts doc@(Pandoc meta _) = do
+makePDF "wkhtmltopdf" pdfargs writer opts doc@(Pandoc meta _) = do
   let mathArgs = case writerHTMLMathMethod opts of
                  -- with MathJax, wait til all math is rendered:
                       MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });",
@@ -93,8 +94,7 @@ makePDF "wkhtmltopdf" writer opts doc@(Pandoc meta _) = do
                       _ -> []
   meta' <- metaToJSON opts (return . stringify) (return . stringify) meta
   let toArgs (f, mbd) = maybe [] (\d -> ['-':'-':f, d]) mbd
-  let args   = writerPdfArgs opts ++ mathArgs ++
-               concatMap toArgs
+  let args   = pdfargs ++ mathArgs ++ concatMap toArgs
                  [("page-size", getField "papersize" meta')
                  ,("title", getField "title" meta')
                  ,("margin-bottom", fromMaybe (Just "1.2in")
@@ -109,23 +109,21 @@ makePDF "wkhtmltopdf" writer opts doc@(Pandoc meta _) = do
   source <- writer opts doc
   verbosity <- getVerbosity
   liftIO $ html2pdf verbosity "wkhtmltopdf" args source
-makePDF "weasyprint" writer opts doc = do
-  let args = writerPdfArgs opts
+makePDF "weasyprint" pdfargs writer opts doc = do
   source <- writer opts doc
   verbosity <- getVerbosity
-  liftIO $ html2pdf verbosity "weasyprint" args source
-makePDF "prince" writer opts doc = do
-  let args = writerPdfArgs opts
+  liftIO $ html2pdf verbosity "weasyprint" pdfargs source
+makePDF "prince" pdfargs writer opts doc = do
   source <- writer opts doc
   verbosity <- getVerbosity
-  liftIO $ html2pdf verbosity "prince" args source
-makePDF "pdfroff" writer opts doc = do
+  liftIO $ html2pdf verbosity "prince" pdfargs source
+makePDF "pdfroff" pdfargs writer opts doc = do
   source <- writer opts doc
   let args   = ["-ms", "-mpdfmark", "-e", "-t", "-k", "-KUTF-8", "-i",
-                "--no-toc-relocation"] ++ writerPdfArgs opts
+                "--no-toc-relocation"] ++ pdfargs
   verbosity <- getVerbosity
   liftIO $ ms2pdf verbosity args source
-makePDF program writer opts doc = do
+makePDF program pdfargs writer opts doc = do
   let withTemp = if takeBaseName program == "context"
                     then withTempDirectory "."
                     else withTempDir
@@ -136,11 +134,10 @@ makePDF program writer opts doc = do
                 putCommonState commonState
                 doc' <- handleImages tmpdir doc
                 writer opts doc'
-    let args = writerPdfArgs opts
     case takeBaseName program of
        "context" -> context2pdf verbosity tmpdir source
        prog | prog `elem` ["pdflatex", "lualatex", "xelatex"]
-           -> tex2pdf' verbosity args tmpdir program source
+           -> tex2pdf' verbosity pdfargs tmpdir program source
        _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program
 
 handleImages :: FilePath      -- ^ temp dir to store images