LaTeX template: define commands for zero width non-joiner character

Closes: #6639

The zero-width non-joiner character is used to avoid ligatures (e.g. in
German).
This commit is contained in:
Albert Krewinkel 2021-05-16 21:33:32 +02:00 committed by GitHub
parent 5a6399d9f6
commit d92622ba3c
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
4 changed files with 26 additions and 6 deletions

View file

@ -156,6 +156,25 @@ $if(CJKmainfont)$
\fi
$endif$
\fi
$if(zero-width-non-joiner)$
%% Support for zero-width non-joiner characters.
\makeatletter
\def\zerowidthnonjoiner{%
% Prevent ligatures and adjust kerning, but still support hyphenating.
\texorpdfstring{%
\textormath{\nobreak\discretionary{-}{}{\kern.03em}%
\ifvmode\else\nobreak\hskip\z@skip\fi}{}%
}{}%
}
\makeatother
\ifPDFTeX
\DeclareUnicodeCharacter{200C}{\zerowidthnonjoiner}
\else
\catcode`^^^^200c=\active
\protected\def ^^^^200c{\zerowidthnonjoiner}
\fi
%% End of ZWNJ support
$endif$
$if(beamer)$
$if(theme)$
\usetheme[$for(themeoptions)$$themeoptions$$sep$,$endfor$]{$theme$}

View file

@ -173,6 +173,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
defField "has-chapters" (stHasChapters st) $
defField "has-frontmatter" (documentClass `elem` frontmatterClasses) $
defField "listings" (writerListings options || stLHS st) $
defField "zero-width-non-joiner" (stZwnj st) $
defField "beamer" beamer $
(if stHighlighting st
then case writerHighlightStyle options of
@ -1048,5 +1049,3 @@ extractInline _ _ = []
-- Look up a key in an attribute and give a list of its values
lookKey :: Text -> Attr -> [Text]
lookKey key (_,_,kvs) = maybe [] T.words $ lookup key kvs

View file

@ -40,7 +40,7 @@ data WriterState =
, stCsquotes :: Bool -- ^ true if document uses csquotes
, stHighlighting :: Bool -- ^ true if document has highlighted code
, stIncremental :: Bool -- ^ true if beamer lists should be
-- displayed bit by bit
, stZwnj :: Bool -- ^ true if document has a ZWNJ character
, stInternalLinks :: [Text] -- ^ list of internal link targets
, stBeamer :: Bool -- ^ produce beamer
, stEmptyLine :: Bool -- ^ true if no content on line
@ -74,6 +74,7 @@ startingState options =
, stCsquotes = False
, stHighlighting = False
, stIncremental = writerIncremental options
, stZwnj = False
, stInternalLinks = []
, stBeamer = False
, stEmptyLine = True

View file

@ -22,6 +22,7 @@ module Text.Pandoc.Writers.LaTeX.Util (
where
import Control.Applicative ((<|>))
import Control.Monad (when)
import Text.Pandoc.Class (PandocMonad, toLang)
import Text.Pandoc.Options (WriterOptions(..), isEnabled)
import Text.Pandoc.Writers.LaTeX.Types (LW, WriterState(..))
@ -30,7 +31,7 @@ import Text.Pandoc.Highlighting (toListingsLanguage)
import Text.DocLayout
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize (showFl)
import Control.Monad.State.Strict (gets)
import Control.Monad.State.Strict (gets, modify)
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Extensions (Extension(Ext_smart))
@ -49,6 +50,8 @@ data StringContext = TextString
stringToLaTeX :: PandocMonad m => StringContext -> Text -> LW m Text
stringToLaTeX context zs = do
opts <- gets stOptions
when ('\x200c' `elemText` zs) $
modify (\s -> s { stZwnj = True })
return $ T.pack $
foldr (go opts context) mempty $ T.unpack $
if writerPreferAscii opts
@ -270,5 +273,3 @@ mbBraced :: Text -> Text
mbBraced x = if not (T.all isAlphaNum x)
then "{" <> x <> "}"
else x