From dd7b83ac9111b63786c1042c4849d7cea79c668b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 9 Sep 2021 18:32:37 -0700 Subject: Use babel, not polyglossia, with xelatex. Previously polyglossia worked better with xelatex, but that is no longer the case, so we simplify the code so that babel is used with all latex engines. This involves a change to the default LaTeX template. --- src/Text/Pandoc/Writers/LaTeX.hs | 52 +++++------------------------------ src/Text/Pandoc/Writers/LaTeX/Lang.hs | 51 +--------------------------------- src/Text/Pandoc/Writers/LaTeX/Util.hs | 12 ++++---- 3 files changed, 13 insertions(+), 102 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index c365aebf5..8c45c8db5 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -21,15 +21,13 @@ module Text.Pandoc.Writers.LaTeX ( ) where import Control.Monad.State.Strict import Data.Char (isDigit) -import Data.List (intersperse, nubBy, (\\)) +import Data.List (intersperse, (\\)) import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe, isNothing) -import qualified Data.Map as M import Data.Text (Text) import qualified Data.Text as T import Network.URI (unEscapeString) -import Text.DocTemplates (FromContext(lookupContext), renderTemplate, - Val(..), Context(..)) -import Text.Collate.Lang (Lang (..), renderLang) +import Text.DocTemplates (FromContext(lookupContext), renderTemplate) +import Text.Collate.Lang (renderLang) import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang) import Text.Pandoc.Definition import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight, @@ -46,7 +44,7 @@ import Text.Pandoc.Writers.LaTeX.Table (tableToLaTeX) import Text.Pandoc.Writers.LaTeX.Citation (citationsToNatbib, citationsToBiblatex) import Text.Pandoc.Writers.LaTeX.Types (LW, WriterState (..), startingState) -import Text.Pandoc.Writers.LaTeX.Lang (toPolyglossia, toBabel) +import Text.Pandoc.Writers.LaTeX.Lang (toBabel) import Text.Pandoc.Writers.LaTeX.Util (stringToLaTeX, StringContext(..), toLabel, inCmd, wrapDiv, hypertarget, labelFor, @@ -132,12 +130,6 @@ pandocToLaTeX options (Pandoc meta blocks) = do ,("tmargin","margin-top") ,("bmargin","margin-bottom") ] - let toPolyObj :: Lang -> Val Text - toPolyObj lang = MapVal $ Context $ - M.fromList [ ("name" , SimpleVal $ literal name) - , ("options" , SimpleVal $ literal opts) ] - where - (name, opts) = toPolyglossia lang mblang <- toLang $ case getLang options meta of Just l -> Just l Nothing | null docLangs -> Nothing @@ -216,36 +208,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do (literal $ toBabel l)) mblang $ defField "babel-otherlangs" (map (literal . toBabel) docLangs) - $ defField "babel-newcommands" (vcat $ - map (\(poly, babel) -> literal $ - -- \textspanish and \textgalician are already used by babel - -- save them as \oritext... and let babel use that - if poly `elem` ["spanish", "galician"] - then "\\let\\oritext" <> poly <> "\\text" <> poly <> "\n" <> - "\\AddBabelHook{" <> poly <> "}{beforeextras}" <> - "{\\renewcommand{\\text" <> poly <> "}{\\oritext" - <> poly <> "}}\n" <> - "\\AddBabelHook{" <> poly <> "}{afterextras}" <> - "{\\renewcommand{\\text" <> poly <> "}[2][]{\\foreignlanguage{" - <> poly <> "}{##2}}}" - else (if poly == "latin" -- see #4161 - then "\\providecommand{\\textlatin}{}\n\\renewcommand" - else "\\newcommand") <> "{\\text" <> poly <> - "}[2][]{\\foreignlanguage{" <> babel <> "}{#2}}\n" <> - "\\newenvironment{" <> poly <> - "}[2][]{\\begin{otherlanguage}{" <> - babel <> "}}{\\end{otherlanguage}}" - ) - -- eliminate duplicates that have same polyglossia name - $ nubBy (\a b -> fst a == fst b) - -- find polyglossia and babel names of languages used in the document - $ map (\l -> (fst $ toPolyglossia l, toBabel l)) docLangs - ) - $ maybe id (defField "polyglossia-lang" . toPolyObj) mblang - $ defField "polyglossia-otherlangs" - (ListVal (map toPolyObj docLangs :: [Val Text])) - $ - defField "latex-dir-rtl" + $ defField "latex-dir-rtl" ((render Nothing <$> getField "dir" context) == Just ("rtl" :: Text)) context return $ render colwidth $ @@ -771,9 +734,8 @@ inlineToLaTeX (Span (id',classes,kvs) ils) = do kvToCmd _ = Nothing langCmds = case lang of - Just lng -> let (l, o) = toPolyglossia lng - ops = if T.null o then "" else "[" <> o <> "]" - in ["text" <> l <> ops] + Just lng -> let l = toBabel lng + in ["foreignlanguage{" <> l <> "}"] Nothing -> [] let cmds = mapMaybe classToCmd classes ++ mapMaybe kvToCmd kvs ++ langCmds contents <- inlineListToLaTeX ils diff --git a/src/Text/Pandoc/Writers/LaTeX/Lang.hs b/src/Text/Pandoc/Writers/LaTeX/Lang.hs index 0ba68b74e..f6fa8d187 100644 --- a/src/Text/Pandoc/Writers/LaTeX/Lang.hs +++ b/src/Text/Pandoc/Writers/LaTeX/Lang.hs @@ -10,61 +10,12 @@ Portability : portable -} module Text.Pandoc.Writers.LaTeX.Lang - ( toPolyglossiaEnv, - toPolyglossia, - toBabel + ( toBabel ) where import Data.Text (Text) import Text.Collate.Lang (Lang(..)) --- In environments \Arabic instead of \arabic is used -toPolyglossiaEnv :: Lang -> (Text, Text) -toPolyglossiaEnv l = - case toPolyglossia l of - ("arabic", o) -> ("Arabic", o) - x -> x - --- Takes a list of the constituents of a BCP47 language code and --- converts it to a Polyglossia (language, options) tuple --- http://mirrors.ctan.org/macros/latex/contrib/polyglossia/polyglossia.pdf -toPolyglossia :: Lang -> (Text, Text) -toPolyglossia (Lang "ar" _ (Just "DZ") _ _ _) = ("arabic", "locale=algeria") -toPolyglossia (Lang "ar" _ (Just "IQ") _ _ _) = ("arabic", "locale=mashriq") -toPolyglossia (Lang "ar" _ (Just "JO") _ _ _) = ("arabic", "locale=mashriq") -toPolyglossia (Lang "ar" _ (Just "LB") _ _ _) = ("arabic", "locale=mashriq") -toPolyglossia (Lang "ar" _ (Just "LY") _ _ _) = ("arabic", "locale=libya") -toPolyglossia (Lang "ar" _ (Just "MA") _ _ _) = ("arabic", "locale=morocco") -toPolyglossia (Lang "ar" _ (Just "MR") _ _ _) = ("arabic", "locale=mauritania") -toPolyglossia (Lang "ar" _ (Just "PS") _ _ _) = ("arabic", "locale=mashriq") -toPolyglossia (Lang "ar" _ (Just "SY") _ _ _) = ("arabic", "locale=mashriq") -toPolyglossia (Lang "ar" _ (Just "TN") _ _ _) = ("arabic", "locale=tunisia") -toPolyglossia (Lang "de" _ _ vars _ _) - | "1901" `elem` vars = ("german", "spelling=old") -toPolyglossia (Lang "de" _ (Just "AT") vars _ _) - | "1901" `elem` vars = ("german", "variant=austrian, spelling=old") -toPolyglossia (Lang "de" _ (Just "AT") _ _ _) = ("german", "variant=austrian") -toPolyglossia (Lang "de" _ (Just "CH") vars _ _) - | "1901" `elem` vars = ("german", "variant=swiss, spelling=old") -toPolyglossia (Lang "de" _ (Just "CH") _ _ _) = ("german", "variant=swiss") -toPolyglossia (Lang "de" _ _ _ _ _) = ("german", "") -toPolyglossia (Lang "dsb" _ _ _ _ _) = ("lsorbian", "") -toPolyglossia (Lang "el" _ _ vars _ _) - | "polyton" `elem` vars = ("greek", "variant=poly") -toPolyglossia (Lang "en" _ (Just "AU") _ _ _) = ("english", "variant=australian") -toPolyglossia (Lang "en" _ (Just "CA") _ _ _) = ("english", "variant=canadian") -toPolyglossia (Lang "en" _ (Just "GB") _ _ _) = ("english", "variant=british") -toPolyglossia (Lang "en" _ (Just "NZ") _ _ _) = ("english", "variant=newzealand") -toPolyglossia (Lang "en" _ (Just "UK") _ _ _) = ("english", "variant=british") -toPolyglossia (Lang "en" _ (Just "US") _ _ _) = ("english", "variant=american") -toPolyglossia (Lang "grc" _ _ _ _ _) = ("greek", "variant=ancient") -toPolyglossia (Lang "hsb" _ _ _ _ _) = ("usorbian", "") -toPolyglossia (Lang "la" _ _ vars _ _) - | "x-classic" `elem` vars = ("latin", "variant=classic") -toPolyglossia (Lang "pt" _ (Just "BR") _ _ _) = ("portuguese", "variant=brazilian") -toPolyglossia (Lang "sl" _ _ _ _ _) = ("slovenian", "") -toPolyglossia x = (commonFromBcp47 x, "") - -- Takes a list of the constituents of a BCP47 language code and -- converts it to a Babel language string. -- http://mirrors.ctan.org/macros/latex/required/babel/base/babel.pdf diff --git a/src/Text/Pandoc/Writers/LaTeX/Util.hs b/src/Text/Pandoc/Writers/LaTeX/Util.hs index c34338121..d79326e0d 100644 --- a/src/Text/Pandoc/Writers/LaTeX/Util.hs +++ b/src/Text/Pandoc/Writers/LaTeX/Util.hs @@ -26,7 +26,7 @@ import Control.Monad (when) import Text.Pandoc.Class (PandocMonad, toLang) import Text.Pandoc.Options (WriterOptions(..), isEnabled) import Text.Pandoc.Writers.LaTeX.Types (LW, WriterState(..)) -import Text.Pandoc.Writers.LaTeX.Lang (toPolyglossiaEnv) +import Text.Pandoc.Writers.LaTeX.Lang (toBabel) import Text.Pandoc.Highlighting (toListingsLanguage) import Text.DocLayout import Text.Pandoc.Definition @@ -238,13 +238,11 @@ wrapDiv (_,classes,kvs) t = do Just "ltr" -> align "LTR" _ -> id wrapLang txt = case lang of - Just lng -> let (l, o) = toPolyglossiaEnv lng - ops = if T.null o - then "" - else brackets $ literal o - in inCmd "begin" (literal l) <> ops + Just lng -> let l = toBabel lng + in inCmd "begin" "otherlanguage" + <> (braces (literal l)) $$ blankline <> txt <> blankline - $$ inCmd "end" (literal l) + $$ inCmd "end" "otherlanguage" Nothing -> txt return $ wrapColumns . wrapColumn . wrapDir . wrapLang $ t -- cgit v1.2.3