aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-02-28 09:49:34 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2021-02-28 09:49:34 -0800
commit564c39beef36bf008fa5d2c840560ef064152e7d (patch)
treeff0d9100520a961ef3487fe033174a44b0930072
parent5e571d963587866957a26d382aeab9935311fb9d (diff)
downloadpandoc-564c39beef36bf008fa5d2c840560ef064152e7d.tar.gz
Move setDefaultLanguage to T.P.Readers.LaTeX.Lang.
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs16
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Lang.hs22
2 files changed, 22 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 3935c92ef..2155379db 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -44,7 +44,7 @@ import Text.Pandoc.Builder
import Text.Pandoc.Class.PandocPure (PandocPure)
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), getResourcePath,
readFileFromDirs, report, setResourcePath,
- setTranslations, translateTerm)
+ translateTerm)
import Text.Pandoc.Error (PandocError (PandocParseError, PandocParsecError))
import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl)
@@ -59,7 +59,7 @@ import Text.Pandoc.Readers.LaTeX.Accent (accentCommands)
import Text.Pandoc.Readers.LaTeX.Citation (citationCommands, cites)
import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments)
import Text.Pandoc.Readers.LaTeX.Lang (polyglossiaLangToBCP47,
- babelLangToBCP47)
+ babelLangToBCP47, setDefaultLanguage)
import Text.Pandoc.Readers.LaTeX.SIunitx
import Text.Pandoc.Shared
import qualified Text.Pandoc.Translations as Translations
@@ -1856,15 +1856,3 @@ block = do
blocks :: PandocMonad m => LP m Blocks
blocks = mconcat <$> many block
-setDefaultLanguage :: PandocMonad m => LP m Blocks
-setDefaultLanguage = do
- o <- option "" $ T.filter (\c -> c /= '[' && c /= ']')
- <$> rawopt
- polylang <- untokenize <$> braced
- case M.lookup polylang polyglossiaLangToBCP47 of
- Nothing -> return mempty -- TODO mzero? warning?
- Just langFunc -> do
- let l = langFunc o
- setTranslations l
- updateState $ setMeta "lang" $ str (renderLang l)
- return mempty
diff --git a/src/Text/Pandoc/Readers/LaTeX/Lang.hs b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
index 5f634818e..adbeaa6d4 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Lang.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
@@ -12,13 +12,31 @@ Functions for parsing polyglossia and babel language specifiers to
BCP47 'Lang'.
-}
module Text.Pandoc.Readers.LaTeX.Lang
- ( polyglossiaLangToBCP47
+ ( setDefaultLanguage
+ , polyglossiaLangToBCP47
, babelLangToBCP47
)
where
import qualified Data.Map as M
import qualified Data.Text as T
-import Text.Pandoc.BCP47 (Lang(..))
+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)
+
+setDefaultLanguage :: PandocMonad m => LP m Blocks
+setDefaultLanguage = do
+ o <- option "" $ T.filter (\c -> c /= '[' && c /= ']')
+ <$> rawopt
+ polylang <- untokenize <$> braced
+ case M.lookup polylang polyglossiaLangToBCP47 of
+ Nothing -> return mempty -- TODO mzero? warning?
+ Just langFunc -> do
+ let l = langFunc o
+ setTranslations l
+ updateState $ setMeta "lang" $ str (renderLang l)
+ return mempty
polyglossiaLangToBCP47 :: M.Map T.Text (T.Text -> Lang)
polyglossiaLangToBCP47 = M.fromList