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/Writers/EPUB.hs17
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs27
3 files changed, 33 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 053385d20..d3ca8d26f 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Readers.Markdown ( readMarkdown,
import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
import qualified Data.Map as M
+import Data.Scientific (coefficient, base10Exponent)
import Data.Ord ( comparing )
import Data.Char ( isAlphaNum, toLower )
import Data.Maybe
@@ -285,7 +286,11 @@ toMetaValue opts x =
yamlToMeta :: ReaderOptions -> Yaml.Value -> MetaValue
yamlToMeta opts (Yaml.String t) = toMetaValue opts t
-yamlToMeta _ (Yaml.Number n) = MetaString $ show n
+yamlToMeta _ (Yaml.Number n)
+ -- avoid decimal points for numbers that don't need them:
+ | base10Exponent n >= 0 = MetaString $ show
+ $ coefficient n * (10 ^ base10Exponent n)
+ | otherwise = MetaString $ show n
yamlToMeta _ (Yaml.Bool b) = MetaBool b
yamlToMeta opts (Yaml.Array xs) = B.toMetaValue $ map (yamlToMeta opts)
$ V.toList xs
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index dae45b90f..9f10554a9 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -35,7 +35,7 @@ import Data.Maybe ( fromMaybe )
import Data.List ( isInfixOf, intercalate )
import System.Environment ( getEnv )
import Text.Printf (printf)
-import System.FilePath ( (</>), takeBaseName, takeExtension, takeFileName )
+import System.FilePath ( (</>), takeExtension, takeFileName )
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as B8
import qualified Text.Pandoc.UTF8 as UTF8
@@ -56,7 +56,7 @@ import Text.XML.Light hiding (ppTopElement)
import Text.Pandoc.UUID
import Text.Pandoc.Writers.HTML
import Text.Pandoc.Writers.Markdown ( writePlain )
-import Data.Char ( toLower, isDigit )
+import Data.Char ( toLower, isDigit, isAlphaNum )
import Network.URI ( unEscapeString )
import Text.Pandoc.MIME (getMimeType)
#if MIN_VERSION_base(4,6,0)
@@ -132,6 +132,11 @@ removeNote :: Inline -> Inline
removeNote (Note _) = Str ""
removeNote x = x
+toId :: FilePath -> String
+toId = map (\x -> if isAlphaNum x || x == '-' || x == '_'
+ then x
+ else '_') . takeFileName
+
getEPUBMetadata :: WriterOptions -> Meta -> IO EPUBMetadata
getEPUBMetadata opts meta = do
let md = metadataFromMeta opts meta
@@ -427,7 +432,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
-- contents.opf
let chapterNode ent = unode "item" !
- ([("id", takeBaseName $ eRelativePath ent),
+ ([("id", toId $ eRelativePath ent),
("href", eRelativePath ent),
("media-type", "application/xhtml+xml")]
++ case props ent of
@@ -435,14 +440,14 @@ writeEPUB opts doc@(Pandoc meta _) = do
xs -> [("properties", unwords xs)])
$ ()
let chapterRefNode ent = unode "itemref" !
- [("idref", takeBaseName $ eRelativePath ent)] $ ()
+ [("idref", takeFileName $ eRelativePath ent)] $ ()
let pictureNode ent = unode "item" !
- [("id", takeBaseName $ eRelativePath ent),
+ [("id", toId $ eRelativePath ent),
("href", eRelativePath ent),
("media-type", fromMaybe "application/octet-stream"
$ mediaTypeOf $ eRelativePath ent)] $ ()
let fontNode ent = unode "item" !
- [("id", takeBaseName $ eRelativePath ent),
+ [("id", toId $ eRelativePath ent),
("href", eRelativePath ent),
("media-type", fromMaybe "" $ getMimeType $ eRelativePath ent)] $ ()
let plainTitle = case docTitle meta of
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index e8f976da1..95082add6 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -316,20 +316,25 @@ blockToMarkdown opts (Div attrs ils) = do
contents <> blankline <> "</div>" <> blankline
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
- return $ contents <> cr
+ -- escape if para starts with ordered list marker
+ st <- get
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ let rendered = render colwidth contents
+ let escapeDelimiter (x:xs) | x `elem` ".()" = '\\':x:xs
+ | otherwise = x : escapeDelimiter xs
+ escapeDelimiter [] = []
+ let contents' = if isEnabled Ext_all_symbols_escapable opts &&
+ not (stPlain st) && beginsWithOrderedListMarker rendered
+ then text $ escapeDelimiter rendered
+ else contents
+ return $ contents' <> cr
-- title beginning with fig: indicates figure
blockToMarkdown opts (Para [Image alt (src,'f':'i':'g':':':tit)]) =
blockToMarkdown opts (Para [Image alt (src,tit)])
-blockToMarkdown opts (Para inlines) = do
- contents <- inlineListToMarkdown opts inlines
- -- escape if para starts with ordered list marker
- st <- get
- let esc = if isEnabled Ext_all_symbols_escapable opts &&
- not (stPlain st) &&
- beginsWithOrderedListMarker (render Nothing contents)
- then text "\x200B" -- zero-width space, a hack
- else empty
- return $ esc <> contents <> blankline
+blockToMarkdown opts (Para inlines) =
+ (<> blankline) `fmap` blockToMarkdown opts (Plain inlines)
blockToMarkdown opts (RawBlock f str)
| f == "html" = do
st <- get