From dd7b83ac9111b63786c1042c4849d7cea79c668b Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Thu, 9 Sep 2021 18:32:37 -0700
Subject: [PATCH] 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.
---
 MANUAL.txt                            | 10 +++---
 data/templates/default.latex          | 14 +-------
 src/Text/Pandoc/Writers/LaTeX.hs      | 52 ++++-----------------------
 src/Text/Pandoc/Writers/LaTeX/Lang.hs | 51 +-------------------------
 src/Text/Pandoc/Writers/LaTeX/Util.hs | 12 +++----
 test/writers-lang-and-dir.latex       | 43 +++++++---------------
 6 files changed, 31 insertions(+), 151 deletions(-)

diff --git a/MANUAL.txt b/MANUAL.txt
index c2c46e05f..3551b2a32 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -142,11 +142,11 @@ When using LaTeX, the following packages need to be available
 contains images), [`hyperref`], [`xcolor`],
 [`ulem`], [`geometry`] (with the `geometry` variable set),
 [`setspace`] (with `linestretch`), and
-[`babel`] (with `lang`).  The use of `xelatex` or `lualatex` as
+[`babel`] (with `lang`).  If `CJKmainfont` is set, [`xeCJK`]
+is needed.  The use of `xelatex` or `lualatex` as
 the PDF engine requires [`fontspec`].  `lualatex` uses
-[`selnolig`]. `xelatex` uses [`polyglossia`] (with `lang`),
-[`xecjk`], and [`bidi`] (with the `dir` variable set). If the
-`mathspec` variable is set, `xelatex` will use [`mathspec`]
+[`selnolig`]. `xelatex` uses [`bidi`] (with the `dir` variable set).
+If the `mathspec` variable is set, `xelatex` will use [`mathspec`]
 instead of [`unicode-math`].  The [`upquote`] and [`microtype`]
 packages are used if available, and [`csquotes`] will be used
 for [typography] if the `csquotes` variable or metadata field is
@@ -197,7 +197,7 @@ footnotes in tables).
 [`weasyprint`]: https://weasyprint.org
 [`wkhtmltopdf`]: https://wkhtmltopdf.org
 [`xcolor`]: https://ctan.org/pkg/xcolor
-[`xecjk`]: https://ctan.org/pkg/xecjk
+[`xeCJK`]: https://ctan.org/pkg/xecjk
 [`xurl`]: https://ctan.org/pkg/xurl
 [`selnolig`]: https://ctan.org/pkg/selnolig
 
diff --git a/data/templates/default.latex b/data/templates/default.latex
index d6a6208a9..27a3fc877 100644
--- a/data/templates/default.latex
+++ b/data/templates/default.latex
@@ -374,22 +374,10 @@ $for(header-includes)$
 $header-includes$
 $endfor$
 $if(lang)$
-\ifXeTeX
-  % Load polyglossia as late as possible: uses bidi with RTL langages (e.g. Hebrew, Arabic)
-  \usepackage{polyglossia}
-  \setmainlanguage[$for(polyglossia-lang.options)$$polyglossia-lang.options$$sep$,$endfor$]{$polyglossia-lang.name$}
-$for(polyglossia-otherlangs)$
-  \setotherlanguage[$for(polyglossia-otherlangs.options)$$polyglossia-otherlangs.options$$sep$,$endfor$]{$polyglossia-otherlangs.name$}
-$endfor$
-\else
-  \usepackage[$for(babel-otherlangs)$$babel-otherlangs$,$endfor$main=$babel-lang$]{babel}
+\usepackage[$for(babel-otherlangs)$$babel-otherlangs$,$endfor$main=$babel-lang$]{babel}
 % get rid of language-specific shorthands (see #6817):
 \let\LanguageShortHands\languageshorthands
 \def\languageshorthands#1{}
-$if(babel-newcommands)$
-  $babel-newcommands$
-$endif$
-\fi
 $endif$
 \ifLuaTeX
   \usepackage{selnolig}  % disable illegal ligatures
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
 
diff --git a/test/writers-lang-and-dir.latex b/test/writers-lang-and-dir.latex
index d91f77325..e7e5aa876 100644
--- a/test/writers-lang-and-dir.latex
+++ b/test/writers-lang-and-dir.latex
@@ -45,30 +45,10 @@
 \providecommand{\tightlist}{%
   \setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
 \setcounter{secnumdepth}{-\maxdimen} % remove section numbering
-\ifXeTeX
-  % Load polyglossia as late as possible: uses bidi with RTL langages (e.g. Hebrew, Arabic)
-  \usepackage{polyglossia}
-  \setmainlanguage[]{english}
-  \setotherlanguage[]{german}
-  \setotherlanguage[variant=british]{english}
-  \setotherlanguage[variant=swiss]{german}
-  \setotherlanguage[]{spanish}
-  \setotherlanguage[]{french}
-\else
-  \usepackage[ngerman,british,nswissgerman,spanish,french,main=english]{babel}
+\usepackage[ngerman,british,nswissgerman,spanish,french,main=english]{babel}
 % get rid of language-specific shorthands (see #6817):
 \let\LanguageShortHands\languageshorthands
 \def\languageshorthands#1{}
-  \newcommand{\textgerman}[2][]{\foreignlanguage{ngerman}{#2}}
-  \newenvironment{german}[2][]{\begin{otherlanguage}{ngerman}}{\end{otherlanguage}}
-  \newcommand{\textenglish}[2][]{\foreignlanguage{british}{#2}}
-  \newenvironment{english}[2][]{\begin{otherlanguage}{british}}{\end{otherlanguage}}
-  \let\oritextspanish\textspanish
-  \AddBabelHook{spanish}{beforeextras}{\renewcommand{\textspanish}{\oritextspanish}}
-  \AddBabelHook{spanish}{afterextras}{\renewcommand{\textspanish}[2][]{\foreignlanguage{spanish}{##2}}}
-  \newcommand{\textfrench}[2][]{\foreignlanguage{french}{#2}}
-  \newenvironment{french}[2][]{\begin{otherlanguage}{french}}{\end{otherlanguage}}
-\fi
 \ifLuaTeX
   \usepackage{selnolig}  % disable illegal ligatures
 \fi
@@ -123,18 +103,19 @@ word-that-includesa\LR{ltrspan}right?
 
 Some text and
 
-\begin{german}
+\begin{otherlanguage}{ngerman}
 
 German div contents
 
-\end{german}
+\end{otherlanguage}
 
 and more text.
 
-Next paragraph with a \textenglish[variant=british]{British span} and a
-word-that-includesa\textgerman[variant=swiss]{Swiss German span}right?
+Next paragraph with a \foreignlanguage{british}{British span} and a
+word-that-includesa\foreignlanguage{nswissgerman}{Swiss German
+span}right?
 
-Some \textspanish{Spanish text}.
+Some \foreignlanguage{spanish}{Spanish text}.
 
 \hypertarget{combined}{%
 \section{Combined}\label{combined}}
@@ -142,17 +123,17 @@ Some \textspanish{Spanish text}.
 Some text and
 
 \begin{RTL}
-\begin{french}
+\begin{otherlanguage}{french}
 
 French rtl div contents
 
-\end{french}
+\end{otherlanguage}
 \end{RTL}
 
 and more text.
 
-Next paragraph with a \LR{\textenglish[variant=british]{British ltr
-span}} and a word-that-includesa\LR{\textgerman[variant=swiss]{Swiss
-German ltr span}}right?
+Next paragraph with a \LR{\foreignlanguage{british}{British ltr span}}
+and a word-that-includesa\LR{\foreignlanguage{nswissgerman}{Swiss German
+ltr span}}right?
 
 \end{document}