aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs7
-rw-r--r--src/Text/Pandoc/Shared.hs2
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs32
3 files changed, 31 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 6b7f1a8fb..02a787670 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -927,6 +927,12 @@ para = try $ do
<|> (guardDisabled Ext_blank_before_header >> () <$ lookAhead header)
<|> (guardEnabled Ext_lists_without_preceding_blankline >>
() <$ lookAhead listStart)
+ <|> do guardEnabled Ext_native_divs
+ inHtmlBlock <- stateInHtmlBlock <$> getState
+ case inHtmlBlock of
+ Just "div" -> () <$
+ lookAhead (htmlTag (~== TagClose "div"))
+ _ -> mzero
return $ do
result' <- result
case B.toList result' of
@@ -1611,6 +1617,7 @@ endline = try $ do
guardEnabled Ext_blank_before_header <|> notFollowedBy (char '#') -- atx header
guardDisabled Ext_backtick_code_blocks <|>
notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
+ notFollowedByHtmlCloser
(eof >> return mempty)
<|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
<|> (guardEnabled Ext_ignore_line_breaks >> return mempty)
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 54d252d43..2d7c08718 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -126,6 +126,7 @@ import Text.Pandoc.Compat.Monoid
import Data.ByteString.Base64 (decodeLenient)
import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr)
import qualified Data.Text as T (toUpper, pack, unpack)
+import Data.ByteString.Lazy (toChunks)
#ifdef EMBED_DATA_FILES
import Text.Pandoc.Data (dataFiles)
@@ -133,7 +134,6 @@ import Text.Pandoc.Data (dataFiles)
import Paths_pandoc (getDataFileName)
#endif
#ifdef HTTP_CLIENT
-import Data.ByteString.Lazy (toChunks)
import Network.HTTP.Client (httpLbs, parseUrl, withManager,
responseBody, responseHeaders,
Request(port,host))
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index ffd5bf101..e4f2d1335 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -406,7 +406,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
$ case blocks of
(Header 1 _ _ : _) -> blocks
_ -> Header 1 ("",["unnumbered"],[])
- (docTitle meta) : blocks
+ (docTitle' meta) : blocks
let chapterHeaderLevel = writerEpubChapterLevel opts
-- internal reference IDs change when we chunk the file,
@@ -484,7 +484,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
[("id", toId $ eRelativePath ent),
("href", eRelativePath ent),
("media-type", fromMaybe "" $ getMimeType $ eRelativePath ent)] $ ()
- let plainTitle = case docTitle meta of
+ let plainTitle = case docTitle' meta of
[] -> case epubTitle metadata of
[] -> "UNTITLED"
(x:_) -> titleText x
@@ -524,9 +524,10 @@ writeEPUB opts doc@(Pandoc meta _) = do
Just _ -> [ unode "itemref" !
[("idref", "cover_xhtml"),("linear","no")] $ () ]
++ ((unode "itemref" ! [("idref", "title_page_xhtml")
- ,("linear", if null (docTitle meta)
- then "no"
- else "yes")] $ ()) :
+ ,("linear",
+ case lookupMeta "title" meta of
+ Just _ -> "yes"
+ Nothing -> "no")] $ ()) :
(unode "itemref" ! [("idref", "nav")
,("linear", if writerTableOfContents opts
then "yes"
@@ -578,7 +579,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
] ++ subs
let tpNode = unode "navPoint" ! [("id", "navPoint-0")] $
- [ unode "navLabel" $ unode "text" (stringify $ docTitle meta)
+ [ unode "navLabel" $ unode "text" (stringify $ docTitle' meta)
, unode "content" ! [("src","title_page.xhtml")] $ () ]
let tocData = UTF8.fromStringLazy $ ppTopElement $
@@ -597,7 +598,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
Nothing -> []
Just img -> [unode "meta" ! [("name","cover"),
("content", toId img)] $ ()]
- , unode "docTitle" $ unode "text" $ plainTitle
+ , unode "docTitle'" $ unode "text" $ plainTitle
, unode "navMap" $
tpNode : evalState (mapM (navPointNode navMapFormatter) secs) 1
]
@@ -731,8 +732,8 @@ metadataElement version md currentTime =
toTitleNode id' title
| version == EPUB2 = [dcNode "title" !
(("id",id') :
- maybe [] (\x -> [("opf:file-as",x)]) (titleFileAs title) ++
- maybe [] (\x -> [("opf:title-type",x)]) (titleType title)) $
+ -- note: EPUB2 doesn't accept opf:title-type
+ maybe [] (\x -> [("opf:file-as",x)]) (titleFileAs title)) $
titleText title]
| otherwise = [dcNode "title" ! [("id",id')] $ titleText title]
++
@@ -1192,3 +1193,16 @@ relatorMap =
,("writer of added text", "wat")
]
+docTitle' :: Meta -> [Inline]
+docTitle' meta = fromMaybe [] $ go <$> lookupMeta "title" meta
+ where go (MetaString s) = [Str s]
+ go (MetaInlines xs) = xs
+ go (MetaBlocks [Para xs]) = xs
+ go (MetaBlocks [Plain xs]) = xs
+ go (MetaMap m) =
+ case M.lookup "type" m of
+ Just x | stringify x == "main" ->
+ maybe [] go $ M.lookup "text" m
+ _ -> []
+ go (MetaList xs) = concatMap go xs
+ go _ = []