aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs16
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs5
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs4
3 files changed, 10 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index 8073f9ad2..b6b271488 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -13,8 +13,7 @@ import Text.Pandoc.Definition hiding (Attr)
import Text.Pandoc.Walk (walk, query)
import Text.Pandoc.Generic(bottomUp)
import Text.Pandoc.Readers.HTML (readHtml)
-import Text.Pandoc.Options ( ReaderOptions(..), readerExtensions, Extension(..)
- , readerTrace)
+import Text.Pandoc.Options ( ReaderOptions(..), readerTrace)
import Text.Pandoc.Shared (escapeURI, collapseFilePath)
import Text.Pandoc.MediaBag (MediaBag, insertMedia)
import Text.Pandoc.Compat.Except (MonadError, throwError, runExcept, Except)
@@ -32,7 +31,6 @@ import Data.Monoid (mempty, (<>))
import Data.List (isPrefixOf, isInfixOf)
import Data.Maybe (mapMaybe, fromMaybe)
import qualified Data.Map as M (Map, lookup, fromList, elems)
-import qualified Data.Set as S (insert)
import Control.DeepSeq.Generics (deepseq, NFData)
import Debug.Trace (trace)
@@ -51,7 +49,7 @@ runEPUB = either error id . runExcept
-- are of the form "filename#id"
--
archiveToEPUB :: (MonadError String m) => ReaderOptions -> Archive -> m (Pandoc, MediaBag)
-archiveToEPUB (setEPUBOptions -> os) archive = do
+archiveToEPUB os archive = do
-- root is path to folder with manifest file in
(root, content) <- getManifest archive
meta <- parseMeta content
@@ -67,6 +65,7 @@ archiveToEPUB (setEPUBOptions -> os) archive = do
let mediaBag = fetchImages (M.elems items) archive ast
return $ (ast, mediaBag)
where
+ os' = os {readerParseRaw = True}
parseSpineElem :: MonadError String m => FilePath -> (FilePath, MIME) -> m Pandoc
parseSpineElem (normalise -> r) (normalise -> path, mime) = do
when (readerTrace os) (traceM path)
@@ -77,20 +76,13 @@ archiveToEPUB (setEPUBOptions -> os) archive = do
mimeToReader "application/xhtml+xml" (normalise -> path) = do
fname <- findEntryByPathE path archive
return $ fixInternalReferences path .
- readHtml os .
+ readHtml os' .
UTF8.toStringLazy $
fromEntry fname
mimeToReader s path
| s `elem` imageMimes = return $ imageToPandoc path
| otherwise = return $ mempty
-setEPUBOptions :: ReaderOptions -> ReaderOptions
-setEPUBOptions os = os''
- where
- rs = readerExtensions os
- os' = os {readerExtensions = foldr S.insert rs [Ext_epub_html_exts]}
- os'' = os' {readerParseRaw = True}
-
-- paths should be absolute when this function is called
-- renameImages should do this
fetchImages :: [(FilePath, MIME)]
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 3d988cd80..1789b865f 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -45,7 +45,8 @@ import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
import Text.Pandoc.Shared ( extractSpaces, renderTags'
, escapeURI, safeRead )
import Text.Pandoc.Options (ReaderOptions(readerParseRaw, readerTrace)
- , Extension (Ext_epub_html_exts))
+ , Extension (Ext_epub_html_exts,
+ Ext_native_divs, Ext_native_spans))
import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Walk
import Data.Maybe ( fromMaybe, isJust)
@@ -296,6 +297,7 @@ pRawTag = do
pDiv :: TagParser Blocks
pDiv = try $ do
+ guardEnabled Ext_native_divs
TagOpen _ attr <- lookAhead $ pSatisfy $ tagOpen (=="div") (const True)
contents <- pInTags "div" block
return $ B.divWith (mkAttr attr) contents
@@ -560,6 +562,7 @@ pCode = try $ do
pSpan :: TagParser Inlines
pSpan = try $ do
+ guardEnabled Ext_native_spans
TagOpen _ attr <- lookAhead $ pSatisfy $ tagOpen (=="span") (const True)
contents <- pInTags "span" inline
return $ B.spanWith (mkAttr attr) contents
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 04b3fa684..861f81b23 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1764,7 +1764,7 @@ inBrackets parser = do
spanHtml :: MarkdownParser (F Inlines)
spanHtml = try $ do
- guardEnabled Ext_markdown_in_html_blocks
+ guardEnabled Ext_native_spans
(TagOpen _ attrs, _) <- htmlTag (~== TagOpen "span" [])
contents <- mconcat <$> manyTill inline (htmlTag (~== TagClose "span"))
let ident = fromMaybe "" $ lookup "id" attrs
@@ -1779,7 +1779,7 @@ spanHtml = try $ do
divHtml :: MarkdownParser (F Blocks)
divHtml = try $ do
- guardEnabled Ext_markdown_in_html_blocks
+ guardEnabled Ext_native_divs
(TagOpen _ attrs, rawtag) <- htmlTag (~== TagOpen "div" [])
-- we set stateInHtmlBlock so that closing tags that can be either block or
-- inline will not be parsed as inline tags