diff options
author | John MacFarlane <jgm@berkeley.edu> | 2015-09-26 17:06:56 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2015-09-26 17:06:56 -0700 |
commit | fdfc961284a71f634e8513d76f69f6d0add0b29b (patch) | |
tree | 99f1d2c2d1a16af0579182a3569d7455833b9ca3 /src | |
parent | 72bade01f54291cf1571c01cd989980df147d4e6 (diff) | |
parent | 7b0c1e0d37a4820b23d901965f059bba82cd48ae (diff) | |
download | pandoc-fdfc961284a71f634e8513d76f69f6d0add0b29b.tar.gz |
Merge pull request #2419 from mb21/bidi
Support bidirectional text output with XeLaTeX, ConTeXt and HTML
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 33 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 20 |
2 files changed, 40 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 5e2d7cfee..7d3830a60 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -83,13 +83,18 @@ pandocToConTeXt options (Pandoc meta blocks) = do $ metadata let context' = defField "context-lang" (maybe "" (fromBcp47 . splitBy (=='-')) $ getField "lang" context) - context + $ defField "context-dir" (toContextDir $ getField "dir" context) + $ context return $ if writerStandalone options then renderTemplate' (writerTemplate options) context' else main --- escape things as needed for ConTeXt +toContextDir :: Maybe String -> String +toContextDir (Just "rtl") = "r2l" +toContextDir (Just "ltr") = "l2r" +toContextDir _ = "" +-- | escape things as needed for ConTeXt escapeCharForConTeXt :: WriterOptions -> Char -> String escapeCharForConTeXt opts ch = let ligatures = writerTeXLigatures opts in @@ -151,13 +156,18 @@ blockToConTeXt (CodeBlock _ str) = -- blankline because \stoptyping can't have anything after it, inc. '}' blockToConTeXt (RawBlock "context" str) = return $ text str <> blankline blockToConTeXt (RawBlock _ _ ) = return empty -blockToConTeXt (Div (ident,_,_) bs) = do +blockToConTeXt (Div (ident,_,kvs) bs) = do contents <- blockListToConTeXt bs - if null ident - then return contents - else return $ - ("\\reference" <> brackets (text $ toLabel ident) <> braces empty <> - "%") $$ contents + let contents' = if null ident + then contents + else ("\\reference" <> brackets (text $ toLabel ident) <> + braces empty <> "%") $$ contents + let align dir = blankline <> "\\startalignment[" <> dir <> "]" + $$ contents' $$ "\\stopalignment" <> blankline + return $ case lookup "dir" kvs of + Just "rtl" -> align "righttoleft" + Just "ltr" -> align "lefttoright" + _ -> contents' blockToConTeXt (BulletList lst) = do contents <- mapM listItemToConTeXt lst return $ ("\\startitemize" <> if isTightList lst @@ -335,7 +345,12 @@ inlineToConTeXt (Note contents) = do then text "\\footnote{" <> nest 2 contents' <> char '}' else text "\\startbuffer " <> nest 2 contents' <> text "\\stopbuffer\\footnote{\\getbuffer}" -inlineToConTeXt (Span _ ils) = inlineListToConTeXt ils +inlineToConTeXt (Span (_,_,kvs) ils) = do + contents <- inlineListToConTeXt ils + return $ case lookup "dir" kvs of + Just "rtl" -> braces $ "\\righttoleft " <> contents + Just "ltr" -> braces $ "\\lefttoright " <> contents + _ -> contents -- | Craft the section header, inserting the secton reference, if supplied. sectionHeader :: Attr diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index adf0f7980..6effbcd01 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -187,6 +187,9 @@ pandocToLaTeX options (Pandoc meta blocks) = do $ defField "polyglossia-otherlangs" (maybe [] (map $ fst . toPolyglossia . splitBy (=='-')) $ getField "otherlangs" context) + $ defField "latex-dir-rtl" (case (getField "dir" context)::Maybe String of + Just "rtl" -> True + _ -> False) $ context return $ if writerStandalone options then renderTemplate' template context' @@ -323,14 +326,19 @@ isLineBreakOrSpace _ = False blockToLaTeX :: Block -- ^ Block to convert -> State WriterState Doc blockToLaTeX Null = return empty -blockToLaTeX (Div (identifier,classes,_) bs) = do +blockToLaTeX (Div (identifier,classes,kvs) bs) = do beamer <- writerBeamer `fmap` gets stOptions ref <- toLabel identifier let linkAnchor = if null identifier then empty else "\\hyperdef{}" <> braces (text ref) <> braces ("\\label" <> braces (text ref)) - contents <- blockListToLaTeX bs + contents' <- blockListToLaTeX bs + let align dir = inCmd "begin" dir $$ contents' $$ inCmd "end" dir + let contents = case lookup "dir" kvs of + Just "rtl" -> align "RTL" + Just "ltr" -> align "LTR" + _ -> contents' if beamer && "notes" `elem` classes -- speaker notes then return $ "\\note" <> braces contents else return (linkAnchor $$ contents) @@ -727,10 +735,12 @@ isQuoted _ = False -- | Convert inline element to LaTeX inlineToLaTeX :: Inline -- ^ Inline to convert -> State WriterState Doc -inlineToLaTeX (Span (id',classes,_) ils) = do +inlineToLaTeX (Span (id',classes,kvs) ils) = do let noEmph = "csl-no-emph" `elem` classes let noStrong = "csl-no-strong" `elem` classes let noSmallCaps = "csl-no-smallcaps" `elem` classes + let rtl = ("dir","rtl") `elem` kvs + let ltr = ("dir","ltr") `elem` kvs ref <- toLabel id' let linkAnchor = if null id' then empty @@ -740,7 +750,9 @@ inlineToLaTeX (Span (id',classes,_) ils) = do ((if noEmph then inCmd "textup" else id) . (if noStrong then inCmd "textnormal" else id) . (if noSmallCaps then inCmd "textnormal" else id) . - (if not (noEmph || noStrong || noSmallCaps) + (if rtl then inCmd "RL" else id) . + (if ltr then inCmd "LR" else id) . + (if not (noEmph || noStrong || noSmallCaps || rtl || ltr) then braces else id)) `fmap` inlineListToLaTeX ils inlineToLaTeX (Emph lst) = |