diff options
-rw-r--r-- | pandoc.cabal | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 17 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 27 | ||||
-rw-r--r-- | tests/writer.opml | 10 |
5 files changed, 44 insertions, 28 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index 8473447a3..e455c82a4 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -207,7 +207,7 @@ Library array >= 0.3 && < 0.6, parsec >= 3.1 && < 3.2, mtl >= 1.1 && < 2.2, - network >= 2 && < 2.5, + network >= 2 && < 2.6, filepath >= 1.1 && < 1.4, process >= 1 && < 1.3, directory >= 1 && < 1.3, @@ -222,7 +222,7 @@ Library random >= 1 && < 1.1, extensible-exceptions >= 0.1 && < 0.2, pandoc-types >= 1.12.3 && < 1.13, - aeson >= 0.6 && < 0.8, + aeson >= 0.7 && < 0.8, tagsoup >= 0.13.1 && < 0.14, base64-bytestring >= 0.1 && < 1.1, zlib >= 0.5 && < 0.6, @@ -233,12 +233,13 @@ Library blaze-markup >= 0.5.1 && < 0.7, attoparsec >= 0.10 && < 0.12, yaml >= 0.8.8.2 && < 0.9, + scientific >= 0.2 && < 0.3, vector >= 0.10 && < 0.11, hslua >= 0.3 && < 0.4, binary >= 0.5 && < 0.8 Build-Tools: alex, happy if flag(http-conduit) - Build-Depends: http-conduit >= 1.9 && < 2.1, + Build-Depends: http-conduit >= 1.9 && < 2.2, http-types >= 0.8 && < 0.9 cpp-options: -DHTTP_CONDUIT if flag(embed_data_files) @@ -322,12 +323,12 @@ Executable pandoc base >= 4.2 && <5, directory >= 1 && < 1.3, filepath >= 1.1 && < 1.4, - network >= 2 && < 2.5, + network >= 2 && < 2.6, text >= 0.11 && < 1.2, bytestring >= 0.9 && < 0.11, extensible-exceptions >= 0.1 && < 0.2, highlighting-kate >= 0.5.6 && < 0.6, - aeson >= 0.6 && < 0.8, + aeson >= 0.7 && < 0.8, yaml >= 0.8.8.2 && < 0.9, containers >= 0.1 && < 0.6, HTTP >= 4000.0.5 && < 4000.3 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 diff --git a/tests/writer.opml b/tests/writer.opml index 228cad247..34d161fb8 100644 --- a/tests/writer.opml +++ b/tests/writer.opml @@ -18,7 +18,7 @@ </outline> <outline text="Level 1"> <outline text="Level 2 with <em>emphasis</em>"> - <outline text="Level 3" _note="with no blank line"> + <outline text="Level 3" _note="with no blank line "> </outline> </outline> <outline text="Level 2" _note="with no blank line * * * * *"> @@ -55,18 +55,18 @@ <outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 \< 5. 6 \> 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: [ Right bracket: ] Left paren: ( Right paren: ) Greater-than: \> Hash: \# Period: . Bang: ! Plus: + Minus: - * * * * *"> </outline> <outline text="Links"> - <outline text="Explicit" _note="Just a [URL](/url/). [URL and title](/url/ "title"). [URL and title](/url/ "title preceded by two spaces"). [URL and title](/url/ "title preceded by a tab"). [URL and title](/url/ "title with "quotes" in it") [URL and title](/url/ "title with single quotes") [with\_underscore](/url/with_underscore) [Email link](mailto:nobody@nowhere.net) [Empty]()."> + <outline text="Explicit" _note="Just a [URL](/url/). [URL and title](/url/ "title"). [URL and title](/url/ "title preceded by two spaces"). [URL and title](/url/ "title preceded by a tab"). [URL and title](/url/ "title with "quotes" in it") [URL and title](/url/ "title with single quotes") [with\_underscore](/url/with_underscore) [Email link](mailto:nobody@nowhere.net) [Empty](). "> </outline> - <outline text="Reference" _note="Foo [bar](/url/). Foo [bar](/url/). Foo [bar](/url/). With [embedded [brackets]](/url/). [b](/url/) by itself should be a link. Indented [once](/url). Indented [twice](/url). Indented [thrice](/url). This should [not][] be a link. [not]: /url Foo [bar](/url/ "Title with "quotes" inside"). Foo [biz](/url/ "Title with "quote" inside")."> + <outline text="Reference" _note="Foo [bar](/url/). Foo [bar](/url/). Foo [bar](/url/). With [embedded [brackets]](/url/). [b](/url/) by itself should be a link. Indented [once](/url). Indented [twice](/url). Indented [thrice](/url). This should [not][] be a link. [not]: /url Foo [bar](/url/ "Title with "quotes" inside"). Foo [biz](/url/ "Title with "quote" inside"). "> </outline> - <outline text="With ampersands" _note="Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). Here’s a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). Here’s an [inline link](/script?foo=1&bar=2). Here’s an [inline link in pointy braces](/script?foo=1&bar=2)."> + <outline text="With ampersands" _note="Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). Here’s a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). Here’s an [inline link](/script?foo=1&bar=2). Here’s an [inline link in pointy braces](/script?foo=1&bar=2). "> </outline> <outline text="Autolinks" _note="With an ampersand: <http://example.com/?foo=1&bar=2> - In a list? - <http://example.com/> - It should. An e-mail address: <nobody@nowhere.net> > Blockquoted: <http://example.com/> Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> * * * * *"> </outline> </outline> <outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902): ![lalune](lalune.jpg "Voyage dans la Lune") Here is a movie ![movie](movie.jpg) icon. * * * * *"> </outline> -<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be a footnote reference, because it contains a space.[\^my note] Here is an inline note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [^2]: Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as [bracketed text]. [^4]: In quote. [^5]: In list."> +<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be a footnote reference, because it contains a space.[\^my note] Here is an inline note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [^2]: Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as [bracketed text]. [^4]: In quote. [^5]: In list. "> </outline> </body> </opml> |