aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README15
-rw-r--r--pandoc.cabal3
-rw-r--r--pandoc.hs12
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs9
4 files changed, 25 insertions, 14 deletions
diff --git a/README b/README
index 2b8b38b9e..df18fcfb1 100644
--- a/README
+++ b/README
@@ -1591,21 +1591,26 @@ CSS.
#### Extension: `implicit_header_references` ####
Pandoc behaves as if reference links have been defined for each header.
-So, instead of
+So, to link to a header
- [header identifiers](#header-identifiers-in-html)
+ # Header identifiers in HTML
you can simply write
- [header identifiers]
+ [Header identifiers in HTML]
or
- [header identifiers][]
+ [Header identifiers in HTML][]
or
- [the section on header identifiers][header identifiers]
+ [the section on header identifiers][header identifiers in
+ HTML]
+
+instead of giving the identifier explicitly:
+
+ [Header identifiers in HTML](#header-identifiers-in-html)
If there are multiple headers with identical text, the corresponding
reference will link to the first one only, and you will need to use explicit
diff --git a/pandoc.cabal b/pandoc.cabal
index d38754dcd..d1d623060 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -425,7 +425,8 @@ Executable pandoc
aeson >= 0.7.0.5 && < 0.12,
yaml >= 0.8.8.2 && < 0.9,
containers >= 0.1 && < 0.6,
- HTTP >= 4000.0.5 && < 4000.4
+ HTTP >= 4000.0.5 && < 4000.4,
+ process >= 1.0 && < 1.5
if flag(network-uri)
Build-Depends: network-uri >= 2.6 && < 2.7, network >= 2.6
else
diff --git a/pandoc.hs b/pandoc.hs
index e8a971de7..76803be43 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, TupleSections #-}
+{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables #-}
{-
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
@@ -52,6 +52,7 @@ import Data.Char ( toLower, toUpper )
import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort )
import System.Directory ( getAppUserDataDirectory, findExecutable,
doesFileExist, Permissions(..), getPermissions )
+import System.Process ( readProcessWithExitCode )
import System.IO ( stdout, stderr )
import System.IO.Error ( isDoesNotExistError )
import qualified Control.Exception as E
@@ -836,7 +837,7 @@ options =
, Option "" ["mathjax"]
(OptArg
(\arg opt -> do
- let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" arg
+ let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS_CHTML-full" arg
return opt { optHTMLMathMethod = MathJax url'})
"URL")
"" -- "Use MathJax for HTML math"
@@ -1401,8 +1402,11 @@ convertWithOpts opts args = do
_ | html5Output -> "wkhtmltopdf"
_ -> latexEngine
-- check for pdf creating program
- mbPdfProg <- findExecutable pdfprog
- when (isNothing mbPdfProg) $
+ (ec,_,_) <- E.catch
+ (readProcessWithExitCode pdfprog ["--version"] "")
+ (\(_ :: E.SomeException) ->
+ return (ExitFailure 1,"",""))
+ when (ec /= ExitSuccess) $
err 41 $ pdfprog ++ " not found. " ++
pdfprog ++ " is needed for pdf output."
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 283c8bc44..804e0febc 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -39,7 +39,8 @@ import Text.Pandoc.Templates
import Text.Printf ( printf )
import Network.URI ( isURI, unEscapeString )
import Data.Aeson (object, (.=), FromJSON)
-import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse, nub, nubBy )
+import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse,
+ nub, nubBy, foldl' )
import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit,
ord, isAlphaNum )
import Data.Maybe ( fromMaybe, isJust, catMaybes )
@@ -725,7 +726,7 @@ sectionHeader :: Bool -- True for unnumbered
-> State WriterState Doc
sectionHeader unnumbered ident level lst = do
txt <- inlineListToLaTeX lst
- plain <- stringToLaTeX TextString $ foldl (++) "" $ map stringify lst
+ plain <- stringToLaTeX TextString $ concatMap stringify lst
let noNote (Note _) = Str ""
noNote x = x
let lstNoNotes = walk noNote lst
@@ -1037,7 +1038,7 @@ citationsToNatbib (c:cs) | citationMode c == AuthorInText = do
citationsToNatbib cits = do
cits' <- mapM convertOne cits
- return $ text "\\citetext{" <> foldl combineTwo empty cits' <> text "}"
+ return $ text "\\citetext{" <> foldl' combineTwo empty cits' <> text "}"
where
combineTwo a b | isEmpty a = b
| otherwise = a <> text "; " <> b
@@ -1086,7 +1087,7 @@ citationsToBiblatex (one:[])
citationsToBiblatex (c:cs) = do
args <- mapM convertOne (c:cs)
- return $ text cmd <> foldl (<>) empty args
+ return $ text cmd <> foldl' (<>) empty args
where
cmd = case citationMode c of
AuthorInText -> "\\textcites"