@@ -39,7 +39,7 @@ import Text.Pandoc.Templates
39
39
import Text.Printf ( printf )
40
40
import Network.URI ( isURI , unEscapeString )
41
41
import Data.Aeson (object , (.=) )
42
- import Data.List ( (\\) , isInfixOf , stripPrefix , intercalate , intersperse )
42
+ import Data.List ( (\\) , isInfixOf , stripPrefix , intercalate , intersperse , nub , nubBy )
43
43
import Data.Char ( toLower , isPunctuation , isAscii , isLetter , isDigit , ord )
44
44
import Data.Maybe ( fromMaybe )
45
45
import qualified Data.Text as T
@@ -145,6 +145,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
145
145
st <- get
146
146
titleMeta <- stringToLaTeX TextString $ stringify $ docTitle meta
147
147
authorsMeta <- mapM (stringToLaTeX TextString . stringify) $ docAuthors meta
148
+ let docLangs = nub $ query (extract " lang" ) blocks
148
149
let context = defField " toc" (writerTableOfContents options) $
149
150
defField " toc-depth" (show (writerTOCDepth options -
150
151
if stBook st
@@ -179,18 +180,48 @@ pandocToLaTeX options (Pandoc meta blocks) = do
179
180
Biblatex -> defField " biblio-title" biblioTitle .
180
181
defField " biblatex" True
181
182
_ -> id ) $
183
+ -- set lang to something so polyglossia/babel is included
184
+ defField " lang" (if null docLangs then " " :: String else " en" ) $
185
+ defField " otherlangs" docLangs $
186
+ defField " dir" (if (null $ query (extract " dir" ) blocks)
187
+ then " " :: String
188
+ else " ltr" ) $
182
189
metadata
183
190
let toPolyObj lang = object [ " name" .= T. pack name
184
191
, " options" .= T. pack opts ]
185
192
where
186
193
(name, opts) = toPolyglossia lang
187
194
let lang = maybe [] (splitBy (== ' -' )) $ getField " lang" context
195
+ otherlangs = maybe [] (map $ splitBy (== ' -' )) $ getField " otherlangs" context
188
196
let context' =
189
197
defField " babel-lang" (toBabel lang)
198
+ $ defField " babel-otherlangs" (map toBabel otherlangs)
199
+ $ defField " babel-newcommands" (concatMap (\ (poly, babel) ->
200
+ -- \textspanish and \textgalician are already used by babel
201
+ -- save them as \oritext... and let babel use that
202
+ if poly `elem` [" spanish" , " galician" ]
203
+ then " \\ let\\ oritext" ++ poly ++ " \\ text" ++ poly ++ " \n " ++
204
+ " \\ AddBabelHook{" ++ poly ++ " }{beforeextras}" ++
205
+ " {\\ renewcommand{\\ text" ++ poly ++ " }{\\ oritext"
206
+ ++ poly ++ " }}\n " ++
207
+ " \\ AddBabelHook{" ++ poly ++ " }{afterextras}\n " ++
208
+ " {\\ renewcommand{\\ text" ++ poly ++ " }[2][]{\\ foreignlanguage{"
209
+ ++ poly ++ " }{##2}}}\n "
210
+ else " \\ newcommand{\\ text" ++ poly ++ " }[2][]{\\ foreignlanguage{"
211
+ ++ babel ++ " }{#2}}\n " ++
212
+ " \\ newenvironment{" ++ poly ++ " }[1]{\\ begin{otherlanguage}{"
213
+ ++ babel ++ " }}{\\ end{otherlanguage}}\n "
214
+ )
215
+ -- eliminate duplicates that have same polyglossia name
216
+ $ nubBy (\ a b -> fst a == fst b)
217
+ -- find polyglossia and babel names of languages used in the document
218
+ $ map (\ l ->
219
+ let lng = splitBy (== ' -' ) l
220
+ in (fst $ toPolyglossia lng, toBabel lng)
221
+ )
222
+ docLangs )
190
223
$ defField " polyglossia-lang" (toPolyObj lang)
191
- $ defField " polyglossia-otherlangs"
192
- (maybe [] (map $ toPolyObj . splitBy (== ' -' )) $
193
- getField " otherlangs" context)
224
+ $ defField " polyglossia-otherlangs" (map toPolyObj otherlangs)
194
225
$ defField " latex-dir-rtl" (case (getField " dir" context):: Maybe String of
195
226
Just " rtl" -> True
196
227
_ -> False )
@@ -337,15 +368,24 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do
337
368
then empty
338
369
else " \\ hyperdef{}" <> braces (text ref) <>
339
370
braces (" \\ label" <> braces (text ref))
340
- contents' <- blockListToLaTeX bs
341
- let align dir = inCmd " begin" dir $$ contents' $$ inCmd " end" dir
342
- let contents = case lookup " dir" kvs of
343
- Just " rtl" -> align " RTL"
344
- Just " ltr" -> align " LTR"
345
- _ -> contents'
346
- if beamer && " notes" `elem` classes -- speaker notes
347
- then return $ " \\ note" <> braces contents
348
- else return (linkAnchor $$ contents)
371
+ let align dir txt = inCmd " begin" dir $$ txt $$ inCmd " end" dir
372
+ let wrapDir = case lookup " dir" kvs of
373
+ Just " rtl" -> align " RTL"
374
+ Just " ltr" -> align " LTR"
375
+ _ -> id
376
+ wrapLang txt = case lookup " lang" kvs of
377
+ Just lng -> let (l, o) = toPolyglossiaEnv lng
378
+ ops = if null o
379
+ then " "
380
+ else brackets $ text o
381
+ in inCmd " begin" (text l) <> ops
382
+ $$ blankline <> txt <> blankline
383
+ $$ inCmd " end" (text l)
384
+ Nothing -> txt
385
+ wrapNotes txt = if beamer && " notes" `elem` classes
386
+ then " \\ note" <> braces txt -- speaker notes
387
+ else linkAnchor $$ txt
388
+ fmap (wrapDir . wrapLang . wrapNotes) $ blockListToLaTeX bs
349
389
blockToLaTeX (Plain lst) =
350
390
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
351
391
-- title beginning with fig: indicates that the image is a figure
@@ -756,9 +796,12 @@ inlineToLaTeX (Span (id',classes,kvs) ils) = do
756
796
(if noSmallCaps then inCmd " textnormal" else id ) .
757
797
(if rtl then inCmd " RL" else id ) .
758
798
(if ltr then inCmd " LR" else id ) .
759
- (if not (noEmph || noStrong || noSmallCaps || rtl || ltr)
760
- then braces
761
- else id )) `fmap` inlineListToLaTeX ils
799
+ (case lookup " lang" kvs of
800
+ Just lng -> let (l, o) = toPolyglossiaEnv lng
801
+ ops = if null o then " " else brackets (text o)
802
+ in \ c -> char ' \\ ' <> " text" <> text l <> ops <> braces c
803
+ Nothing -> id )
804
+ ) `fmap` inlineListToLaTeX ils
762
805
inlineToLaTeX (Emph lst) =
763
806
inlineListToLaTeX lst >>= return . inCmd " emph"
764
807
inlineToLaTeX (Strong lst) =
@@ -999,6 +1042,30 @@ getListingsLanguage :: [String] -> Maybe String
999
1042
getListingsLanguage [] = Nothing
1000
1043
getListingsLanguage (x: xs) = toListingsLanguage x <|> getListingsLanguage xs
1001
1044
1045
+ -- Extract a key from divs and spans
1046
+ extract :: String -> Block -> [String ]
1047
+ extract key (Div attr _) = lookKey key attr
1048
+ extract key (Plain ils) = concatMap (extractInline key) ils
1049
+ extract key (Para ils) = concatMap (extractInline key) ils
1050
+ extract key (Header _ _ ils) = concatMap (extractInline key) ils
1051
+ extract _ _ = []
1052
+
1053
+ -- Extract a key from spans
1054
+ extractInline :: String -> Inline -> [String ]
1055
+ extractInline key (Span attr _) = lookKey key attr
1056
+ extractInline _ _ = []
1057
+
1058
+ -- Look up a key in an attribute and give a list of its values
1059
+ lookKey :: String -> Attr -> [String ]
1060
+ lookKey key (_,_,kvs) = maybe [] words $ lookup key kvs
1061
+
1062
+ -- In environments \Arabic instead of \arabic is used
1063
+ toPolyglossiaEnv :: String -> (String , String )
1064
+ toPolyglossiaEnv l =
1065
+ case toPolyglossia $ (splitBy (== ' -' )) l of
1066
+ (" arabic" , o) -> (" Arabic" , o)
1067
+ x -> x
1068
+
1002
1069
-- Takes a list of the constituents of a BCP 47 language code and
1003
1070
-- converts it to a Polyglossia (language, options) tuple
1004
1071
-- http://mirrors.concertpass.com/tex-archive/macros/latex/contrib/polyglossia/polyglossia.pdf
0 commit comments