aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs19
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs18
2 files changed, 34 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 31c8d9095..27c018e73 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -420,6 +420,8 @@ inlineCommands = M.unions
, ("uline", underline <$> tok)
-- plain tex stuff that should just be passed through as raw tex
, ("ifdim", ifdim)
+ -- stackengine
+ , ("addstackgap", skipopts *> tok)
]
lettrine :: PandocMonad m => LP m Inlines
@@ -833,6 +835,7 @@ blockCommands = M.fromList
<|> (grouped block >>= addMeta "title")))
, ("subtitle", mempty <$ (skipopts *> tok >>= addMeta "subtitle"))
, ("author", mempty <$ (skipopts *> authors))
+ , ("tableofcontents", mempty <$ (addMeta "tableOfContents" True))
-- -- in letter class, temp. store address & sig as title, author
, ("address", mempty <$ (skipopts *> tok >>= addMeta "address"))
, ("signature", mempty <$ (skipopts *> authors))
@@ -929,11 +932,15 @@ environments = M.union (tableEnvironments blocks inline) $
, ("abstract", mempty <$ (env "abstract" blocks >>= addMeta "abstract"))
, ("sloppypar", env "sloppypar" blocks)
, ("letter", env "letter" letterContents)
+ , ("multicols", env "multicols" multicols)
, ("minipage", env "minipage" $
skipopts *> spaces *> optional braced *> spaces *> blocks)
, ("figure", env "figure" $ skipopts *> figure)
, ("subfigure", env "subfigure" $ skipopts *> tok *> figure)
, ("center", divWith ("", ["center"], []) <$> env "center" blocks)
+ , ("flushright", divWith ("", ["flushright"], []) <$> env "flushright" blocks)
+ , ("flushleft", divWith ("", ["flushleft"], []) <$> env "flushleft" blocks)
+ , ("landscape", env "landscape" blocks)
, ("quote", blockQuote <$> env "quote" blocks)
, ("quotation", blockQuote <$> env "quotation" blocks)
, ("verse", blockQuote <$> env "verse" blocks)
@@ -1083,6 +1090,18 @@ letterContents = do
_ -> mempty
return $ addr <> bs -- sig added by \closing
+multicols :: PandocMonad m => LP m Blocks
+multicols = do
+ spaces
+ n <- fromMaybe 1 . safeRead . untokenize <$> braced
+ spaces
+ bs <- blocks
+ return $ divWith ("", ["columns"], []) $ cols n bs
+ where
+ cols :: Int -> Blocks -> Blocks
+ cols n = foldr1 (.) (replicate n $ divWith ("", ["column"], []))
+
+
figure :: PandocMonad m => LP m Blocks
figure = try $ do
resetCaption
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 7eb8dfe12..6f91d1965 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -28,6 +28,7 @@ module Text.Pandoc.Writers.HTML (
writeRevealJs,
tagWithAttributes
) where
+import Control.Monad.Identity (runIdentity)
import Control.Monad.State.Strict
import Data.Char (ord)
import Data.List (intercalate, intersperse, partition, delete, (\\), foldl')
@@ -51,7 +52,7 @@ import Text.Pandoc.ImageSize
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Slides
-import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.Templates (Template, compileTemplate, renderTemplate)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
import Text.Pandoc.Writers.Shared
@@ -203,10 +204,13 @@ writeHtmlString' :: PandocMonad m
=> WriterState -> WriterOptions -> Pandoc -> m Text
writeHtmlString' st opts d = do
(body, context) <- evalStateT (pandocToHtml opts d) st
+ let defaultTemplate = fmap (const tocTemplate) (getField "table-of-contents" context :: Maybe Text)
+ let template = msum [ writerTemplate opts
+ , defaultTemplate ]
(if writerPreferAscii opts
then toEntities
else id) <$>
- case writerTemplate opts of
+ case template of
Nothing -> return $ renderHtml' body
Just tpl -> do
-- warn if empty lang
@@ -239,6 +243,13 @@ writeHtml' st opts d =
(body, _) <- evalStateT (pandocToHtml opts d) st
return body
+wantTOC :: Meta -> Maybe Bool
+wantTOC = fmap (== MetaBool True) . lookupMeta "tableOfContents"
+
+tocTemplate :: Template Text
+tocTemplate = either error id . runIdentity . compileTemplate "" $
+ "<div class=\"toc\"><h1></h1>$table-of-contents$</div>$body$"
+
-- result is (title, authors, date, toc, body, new variables)
pandocToHtml :: PandocMonad m
=> WriterOptions
@@ -262,7 +273,8 @@ pandocToHtml opts (Pandoc meta blocks) = do
if slideVariant == NoSlides
then blocks
else prepSlides slideLevel blocks
- toc <- if writerTableOfContents opts && slideVariant /= S5Slides
+ let withTOC = fromMaybe (writerTableOfContents opts) (wantTOC meta)
+ toc <- if withTOC && slideVariant /= S5Slides
then fmap renderHtml' <$> tableOfContents opts sects
else return Nothing
blocks' <- blockListToHtml opts sects