diff options
author | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 11:08:02 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 11:08:02 -0800 |
commit | 044bc44fc621e421b74367765022f108494b4e2e (patch) | |
tree | 015d9303d9876ce63a0f78cd522813e4a53640da /src/Text | |
parent | bbcc1501a5fa6b40ded88f6738d35ce7a8079313 (diff) | |
download | pandoc-044bc44fc621e421b74367765022f108494b4e2e.tar.gz |
Moved more into T.P.Readers.LaTeX.Lang.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 84 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Inline.hs | 65 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Lang.hs | 30 |
3 files changed, 97 insertions, 82 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index a27135fd2..4ec038b94 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -34,7 +34,7 @@ import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T import System.FilePath (addExtension, replaceExtension, takeExtension) -import Text.Pandoc.BCP47 (Lang (..), renderLang) +import Text.Pandoc.BCP47 (renderLang) import Text.Pandoc.Builder as B import Text.Pandoc.Class.PandocPure (PandocPure) import Text.Pandoc.Class.PandocMonad (PandocMonad (..), getResourcePath, @@ -58,11 +58,12 @@ import Text.Pandoc.Readers.LaTeX.Math (dollarsMath, inlineEnvironments, theoremEnvironment) import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments) import Text.Pandoc.Readers.LaTeX.Macro (macroDef) -import Text.Pandoc.Readers.LaTeX.Lang (polyglossiaLangToBCP47, +import Text.Pandoc.Readers.LaTeX.Lang (inlineLanguageCommands, babelLangToBCP47, setDefaultLanguage) import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands) import Text.Pandoc.Readers.LaTeX.Inline (acronymCommands, refCommands, nameCommands, charCommands, + biblatexInlineCommands, verbCommands, rawInlineOr, listingsLanguage) import Text.Pandoc.Shared @@ -350,8 +351,7 @@ unescapeURL = T.concat . go . T.splitOn "\\" inlineCommands :: PandocMonad m => M.Map Text (LP m Inlines) inlineCommands = M.unions - [ inlineLanguageCommands - , accentCommands tok + [ accentCommands tok , citationCommands inline , siunitxCommands tok , acronymCommands @@ -359,6 +359,8 @@ inlineCommands = M.unions , nameCommands , verbCommands , charCommands + , inlineLanguageCommands tok + , biblatexInlineCommands tok , rest ] where rest = M.fromList @@ -373,12 +375,6 @@ inlineCommands = M.unions , ("texttt", ttfamily) , ("sout", extractSpaces strikeout <$> tok) , ("alert", skipopts >> spanWith ("",["alert"],[]) <$> tok) -- beamer - , ("lq", return (str "‘")) - , ("rq", return (str "’")) - , ("textquoteleft", return (str "‘")) - , ("textquoteright", return (str "’")) - , ("textquotedblleft", return (str "“")) - , ("textquotedblright", return (str "”")) , ("textsuperscript", extractSpaces superscript <$> tok) , ("textsubscript", extractSpaces subscript <$> tok) , ("textbf", extractSpaces strong <$> tok) @@ -447,11 +443,6 @@ inlineCommands = M.unions , ("toggletrue", braced >>= setToggle True) , ("togglefalse", braced >>= setToggle False) , ("iftoggle", try $ ifToggle >> inline) - -- biblatex misc - , ("RN", romanNumeralUpper) - , ("Rn", romanNumeralLower) - -- babel - , ("foreignlanguage", foreignlanguage) -- include , ("input", rawInlineOr "input" $ include "input") -- soul package @@ -460,24 +451,6 @@ inlineCommands = M.unions , ("uline", underline <$> tok) -- plain tex stuff that should just be passed through as raw tex , ("ifdim", ifdim) - -- bibtex - , ("mkbibquote", spanWith nullAttr . doubleQuoted <$> tok) - , ("mkbibemph", spanWith nullAttr . emph <$> tok) - , ("mkbibitalic", spanWith nullAttr . emph <$> tok) - , ("mkbibbold", spanWith nullAttr . strong <$> tok) - , ("mkbibparens", - spanWith nullAttr . (\x -> str "(" <> x <> str ")") <$> tok) - , ("mkbibbrackets", - spanWith nullAttr . (\x -> str "[" <> x <> str "]") <$> tok) - , ("autocap", spanWith nullAttr <$> tok) - , ("textnormal", spanWith ("",["nodecor"],[]) <$> tok) - , ("bibstring", - (\x -> spanWith ("",[],[("bibstring",x)]) (str x)) . untokenize - <$> braced) - , ("adddot", pure (str ".")) - , ("adddotspace", pure (spanWith nullAttr (str "." <> space))) - , ("addabbrvspace", pure space) - , ("hyphen", pure (str "-")) ] lettrine :: PandocMonad m => LP m Inlines @@ -502,26 +475,6 @@ alterStr :: (Text -> Text) -> Inline -> Inline alterStr f (Str xs) = Str (f xs) alterStr _ x = x -foreignlanguage :: PandocMonad m => LP m Inlines -foreignlanguage = do - babelLang <- untokenize <$> braced - case babelLangToBCP47 babelLang of - Just lang -> spanWith ("", [], [("lang", renderLang lang)]) <$> tok - _ -> tok - -inlineLanguageCommands :: PandocMonad m => M.Map Text (LP m Inlines) -inlineLanguageCommands = M.fromList $ mk <$> M.toList polyglossiaLangToBCP47 - where - mk (polyglossia, bcp47Func) = - ("text" <> polyglossia, inlineLanguage bcp47Func) - -inlineLanguage :: PandocMonad m => (Text -> Lang) -> LP m Inlines -inlineLanguage bcp47Func = do - o <- option "" $ T.filter (\c -> c /= '[' && c /= ']') - <$> rawopt - let lang = renderLang $ bcp47Func o - extractSpaces (spanWith ("", [], [("lang", lang)])) <$> tok - hyperlink :: PandocMonad m => LP m Inlines hyperlink = try $ do src <- untokenize <$> braced @@ -542,31 +495,6 @@ hypertargetInline = try $ do ils <- grouped inline return $ spanWith (ref, [], []) ils -romanNumeralUpper :: (PandocMonad m) => LP m Inlines -romanNumeralUpper = - str . toRomanNumeral <$> romanNumeralArg - -romanNumeralLower :: (PandocMonad m) => LP m Inlines -romanNumeralLower = - str . T.toLower . toRomanNumeral <$> romanNumeralArg - -romanNumeralArg :: (PandocMonad m) => LP m Int -romanNumeralArg = spaces *> (parser <|> inBraces) - where - inBraces = do - symbol '{' - spaces - res <- parser - spaces - symbol '}' - return res - parser = do - s <- untokenize <$> many1 (satisfyTok isWordTok) - let (digits, rest) = T.span isDigit s - unless (T.null rest) $ - Prelude.fail "Non-digits in argument to \\Rn or \\RN" - safeRead digits - newToggle :: (Monoid a, PandocMonad m) => [Tok] -> LP m a newToggle name = do updateState $ \st -> diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs index 66014a77f..37c29188e 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs @@ -13,6 +13,7 @@ module Text.Pandoc.Readers.LaTeX.Inline , verbCommands , charCommands , nameCommands + , biblatexInlineCommands , refCommands , rawInlineOr , listingsLanguage @@ -23,15 +24,17 @@ import qualified Data.Map as M import Data.Text (Text) import qualified Data.Text as T import Text.Pandoc.Builder +import Text.Pandoc.Shared (toRomanNumeral, safeRead) import Text.Pandoc.Readers.LaTeX.Types (Tok (..), TokType (..)) -import Control.Applicative (optional) -import Control.Monad (guard, mzero, mplus) +import Control.Applicative (optional, (<|>)) +import Control.Monad (guard, mzero, mplus, unless) import Text.Pandoc.Class.PandocMonad (PandocMonad (..), translateTerm) import Text.Pandoc.Readers.LaTeX.Parsing import Text.Pandoc.Extensions (extensionEnabled, Extension(..)) import Text.Pandoc.Parsing (getOption, updateState, getState, notFollowedBy, manyTill, getInput, setInput, incSourceColumn, - option) + option, many1) +import Data.Char (isDigit) import Text.Pandoc.Highlighting (fromListingsLanguage,) import Data.Maybe (maybeToList) import Text.Pandoc.Options (ReaderOptions(..)) @@ -127,6 +130,31 @@ nlToSpace :: Char -> Char nlToSpace '\n' = ' ' nlToSpace x = x +romanNumeralUpper :: (PandocMonad m) => LP m Inlines +romanNumeralUpper = + str . toRomanNumeral <$> romanNumeralArg + +romanNumeralLower :: (PandocMonad m) => LP m Inlines +romanNumeralLower = + str . T.toLower . toRomanNumeral <$> romanNumeralArg + +romanNumeralArg :: (PandocMonad m) => LP m Int +romanNumeralArg = spaces *> (parser <|> inBraces) + where + inBraces = do + symbol '{' + spaces + res <- parser + spaces + symbol '}' + return res + parser = do + s <- untokenize <$> many1 (satisfyTok isWordTok) + let (digits, rest) = T.span isDigit s + unless (T.null rest) $ + Prelude.fail "Non-digits in argument to \\Rn or \\RN" + safeRead digits + verbCommands :: PandocMonad m => M.Map Text (LP m Inlines) @@ -157,6 +185,12 @@ charCommands = M.fromList , ("{", lit "{") , ("}", lit "}") , ("qed", lit "\a0\x25FB") + , ("lq", return (str "‘")) + , ("rq", return (str "’")) + , ("textquoteleft", return (str "‘")) + , ("textquoteright", return (str "’")) + , ("textquotedblleft", return (str "“")) + , ("textquotedblright", return (str "”")) , ("/", pure mempty) -- italic correction , ("\\", linebreak <$ (do inTableCell <- sInTableCell <$> getState guard $ not inTableCell @@ -185,6 +219,31 @@ charCommands = M.fromList , ("hyp", lit "-") ] +biblatexInlineCommands :: PandocMonad m + => LP m Inlines -> M.Map Text (LP m Inlines) +biblatexInlineCommands tok = M.fromList + -- biblatex misc + [ ("RN", romanNumeralUpper) + , ("Rn", romanNumeralLower) + , ("mkbibquote", spanWith nullAttr . doubleQuoted <$> tok) + , ("mkbibemph", spanWith nullAttr . emph <$> tok) + , ("mkbibitalic", spanWith nullAttr . emph <$> tok) + , ("mkbibbold", spanWith nullAttr . strong <$> tok) + , ("mkbibparens", + spanWith nullAttr . (\x -> str "(" <> x <> str ")") <$> tok) + , ("mkbibbrackets", + spanWith nullAttr . (\x -> str "[" <> x <> str "]") <$> tok) + , ("autocap", spanWith nullAttr <$> tok) + , ("textnormal", spanWith ("",["nodecor"],[]) <$> tok) + , ("bibstring", + (\x -> spanWith ("",[],[("bibstring",x)]) (str x)) . untokenize + <$> braced) + , ("adddot", pure (str ".")) + , ("adddotspace", pure (spanWith nullAttr (str "." <> space))) + , ("addabbrvspace", pure space) + , ("hyphen", pure (str "-")) + ] + nameCommands :: PandocMonad m => M.Map Text (LP m Inlines) nameCommands = M.fromList [ ("figurename", doTerm Translations.Figure) diff --git a/src/Text/Pandoc/Readers/LaTeX/Lang.hs b/src/Text/Pandoc/Readers/LaTeX/Lang.hs index adbeaa6d4..24acbdbe4 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Lang.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Lang.hs @@ -15,15 +15,43 @@ module Text.Pandoc.Readers.LaTeX.Lang ( setDefaultLanguage , polyglossiaLangToBCP47 , babelLangToBCP47 + , inlineLanguageCommands ) where import qualified Data.Map as M +import Data.Text (Text) import qualified Data.Text as T +import Text.Pandoc.Shared (extractSpaces) import Text.Pandoc.BCP47 (Lang(..), renderLang) import Text.Pandoc.Class (PandocMonad(..), setTranslations) import Text.Pandoc.Readers.LaTeX.Parsing import Text.Pandoc.Parsing (updateState, option) -import Text.Pandoc.Builder (Blocks, setMeta, str) +import Text.Pandoc.Builder (Blocks, Inlines, setMeta, str, spanWith) + +foreignlanguage :: PandocMonad m => LP m Inlines -> LP m Inlines +foreignlanguage tok = do + babelLang <- untokenize <$> braced + case babelLangToBCP47 babelLang of + Just lang -> spanWith ("", [], [("lang", renderLang lang)]) <$> tok + _ -> tok + +inlineLanguageCommands :: PandocMonad m + => LP m Inlines -> M.Map Text (LP m Inlines) +inlineLanguageCommands tok = + M.fromList $ + ("foreignlanguage", foreignlanguage tok) : + (mk <$> M.toList polyglossiaLangToBCP47) + where + mk (polyglossia, bcp47Func) = + ("text" <> polyglossia, inlineLanguage tok bcp47Func) + +inlineLanguage :: PandocMonad m + => LP m Inlines -> (Text -> Lang) -> LP m Inlines +inlineLanguage tok bcp47Func = do + o <- option "" $ T.filter (\c -> c /= '[' && c /= ']') + <$> rawopt + let lang = renderLang $ bcp47Func o + extractSpaces (spanWith ("", [], [("lang", lang)])) <$> tok setDefaultLanguage :: PandocMonad m => LP m Blocks setDefaultLanguage = do |