diff options
-rw-r--r-- | INSTALL | 5 | ||||
-rw-r--r-- | README | 14 | ||||
-rw-r--r-- | Setup.hs | 1 | ||||
-rw-r--r-- | pandoc.cabal | 19 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/UTF8.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 57 | ||||
-rw-r--r-- | tests/markdown-reader-more.native | 2 | ||||
-rw-r--r-- | tests/markdown-reader-more.txt | 4 |
11 files changed, 91 insertions, 47 deletions
@@ -116,9 +116,8 @@ assume that the pandoc source directory is your working directory. cabal install hsb2hs - - `http-conduit`: use the `http-conduit` library to fetch external - resources (default yes -- without this, pandoc cannot make SSL - connections) + - `https`: enable support for downloading resources over https + (using the `http-client` and `http-client-tls` libraries). 3. Build: @@ -1,6 +1,6 @@ % Pandoc User's Guide % John MacFarlane -% January 19, 2013 +% May 16, 2014 Synopsis ======== @@ -971,10 +971,8 @@ of the line containing the header text: {#identifier .class .class key=value key=value} -Although this syntax allows assignment of classes and key/value attributes, -only identifiers currently have any affect in the writers (and only in some -writers: HTML, LaTeX, ConTeXt, Textile, AsciiDoc). Thus, for example, -the following headers will all be assigned the identifier `foo`: +Thus, for example, the following headers will all be assigned the identifier +`foo`: # My header {#foo} @@ -985,6 +983,12 @@ the following headers will all be assigned the identifier `foo`: (This syntax is compatible with [PHP Markdown Extra].) +Note that although this syntax allows assignment of classes and key/value +attributes, writers generally don't use all of this information. Identifiers, +classes, and key/value attributes are used in HTML and HTML-based formats such +as EPUB and slidy. Identifiers are used for labels and link anchors in the +LaTeX, ConTeXt, Textile, and AsciiDoc writers. + Headers with the class `unnumbered` will not be numbered, even if `--number-sections` is specified. A single hyphen (`-`) in an attribute context is equivalent to `.unnumbered`, and preferable in non-English @@ -29,7 +29,6 @@ import Distribution.Verbosity ( Verbosity, silent ) import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest), toPathTemplate) import Distribution.Simple.Utils (installOrdinaryFiles, info) import Distribution.Simple.Test (test) -import Prelude hiding (catch) import System.Process ( rawSystem ) import System.FilePath ( (</>) ) import System.Directory ( findExecutable ) diff --git a/pandoc.cabal b/pandoc.cabal index 6f12ec375..a2138d6bf 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -196,8 +196,8 @@ Flag embed_data_files Description: Embed data files in binary for relocatable executable. Default: False -Flag http-conduit - Description: Enable downloading of resources over https. +Flag https + Description: Enable support for downloading of resources over https. Default: True Library @@ -214,7 +214,7 @@ Library directory >= 1 && < 1.3, bytestring >= 0.9 && < 0.11, text >= 0.11 && < 1.2, - zip-archive >= 0.1.3.3 && < 0.3, + zip-archive >= 0.2.3.2 && < 0.3, old-locale >= 1 && < 1.1, time >= 1.2 && < 1.5, HTTP >= 4000.0.5 && < 4000.3, @@ -227,7 +227,7 @@ Library tagsoup >= 0.13.1 && < 0.14, base64-bytestring >= 0.1 && < 1.1, zlib >= 0.5 && < 0.6, - highlighting-kate >= 0.5.8.1 && < 0.6, + highlighting-kate >= 0.5.8.2 && < 0.6, data-default >= 0.4 && < 0.6, temporary >= 1.1 && < 1.3, blaze-html >= 0.5 && < 0.8, @@ -239,10 +239,11 @@ Library 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.2, + if flag(https) + Build-Depends: http-client >= 0.3.2 && < 0.4, + http-client-tls >= 0.2 && < 0.3, http-types >= 0.8 && < 0.9 - cpp-options: -DHTTP_CONDUIT + cpp-options: -DHTTP_CLIENT if flag(embed_data_files) cpp-options: -DEMBED_DATA_FILES -- Build-Tools: hsb2hs -- not yet recognized by cabal @@ -328,7 +329,7 @@ Executable pandoc text >= 0.11 && < 1.2, bytestring >= 0.9 && < 0.11, extensible-exceptions >= 0.1 && < 0.2, - highlighting-kate >= 0.5.8.1 && < 0.6, + highlighting-kate >= 0.5.8.2 && < 0.6, aeson >= 0.7 && < 0.8, yaml >= 0.8.8.2 && < 0.9, containers >= 0.1 && < 0.6, @@ -371,7 +372,7 @@ Test-Suite test-pandoc directory >= 1 && < 1.3, filepath >= 1.1 && < 1.4, process >= 1 && < 1.3, - highlighting-kate >= 0.5.8.1 && < 0.6, + highlighting-kate >= 0.5.8.2 && < 0.6, Diff >= 0.2 && < 0.4, test-framework >= 0.3 && < 0.9, test-framework-hunit >= 0.2 && < 0.4, diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 4cd6591c0..8bc042e28 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -464,11 +464,13 @@ mathInlineWith :: String -> String -> Parser [Char] st String mathInlineWith op cl = try $ do string op notFollowedBy space - words' <- many1Till (count 1 (noneOf "\n\\") + words' <- many1Till (count 1 (noneOf " \t\n\\") <|> (char '\\' >> anyChar >>= \c -> return ['\\',c]) - <|> count 1 newline <* notFollowedBy' blankline - *> return " ") - (try $ string cl) + <|> do (blankline <* notFollowedBy' blankline) <|> + (oneOf " \t" <* skipMany (oneOf " \t")) + notFollowedBy (char '$') + return " " + ) (try $ string cl) notFollowedBy digit -- to prevent capture of $5 return $ concat words' diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 5129bc2e3..caa938ed6 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -618,12 +618,19 @@ codeBlockFenced = try $ do skipMany spaceChar attr <- option ([],[],[]) $ try (guardEnabled Ext_fenced_code_attributes >> attributes) - <|> ((\x -> ("",[x],[])) <$> identifier) + <|> ((\x -> ("",[toLanguageId x],[])) <$> many1 nonspaceChar) blankline contents <- manyTill anyLine (blockDelimiter (== c) (Just size)) blanklines return $ return $ B.codeBlockWith attr $ intercalate "\n" contents +-- correctly handle github language identifiers +toLanguageId :: String -> String +toLanguageId = map toLower . go + where go "c++" = "cpp" + go "objective-c" = "objectivec" + go x = x + codeBlockIndented :: MarkdownParser (F Blocks) codeBlockIndented = do contents <- many1 (indentedLine <|> diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 4f506b5a6..d8cbe46d9 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -118,11 +118,13 @@ import System.FilePath ( joinPath, splitDirectories ) #else import Paths_pandoc (getDataFileName) #endif -#ifdef HTTP_CONDUIT +#ifdef HTTP_CLIENT import Data.ByteString.Lazy (toChunks) -import Network.HTTP.Conduit (httpLbs, parseUrl, withManager, - responseBody, responseHeaders, addProxy, - Request(port,host)) +import Network.HTTP.Client (httpLbs, parseUrl, withManager, + responseBody, responseHeaders, + Request(port,host)) +import Network.HTTP.Client.Internal (addProxy) +import Network.HTTP.Client.TLS (tlsManagerSettings) import System.Environment (getEnv) import Network.HTTP.Types.Header ( hContentType) import Network (withSocketsDo) @@ -665,7 +667,7 @@ openURL u let mime = takeWhile (/=',') $ drop 5 u contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u in return $ Right (decodeLenient contents, Just mime) -#ifdef HTTP_CONDUIT +#ifdef HTTP_CLIENT | otherwise = withSocketsDo $ E.try $ do req <- parseUrl u (proxy :: Either E.SomeException String) <- E.try $ getEnv "http_proxy" @@ -674,7 +676,7 @@ openURL u Right pr -> case parseUrl pr of Just r -> addProxy (host r) (port r) req Nothing -> req - resp <- withManager $ httpLbs req' + resp <- withManager tlsManagerSettings $ httpLbs req' return (BS.concat $ toChunks $ responseBody resp, UTF8.toString `fmap` lookup hContentType (responseHeaders resp)) #else diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index 33c9ec1c5..cf25de85b 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -51,8 +51,7 @@ import System.IO hiding (readFile, writeFile, getContents, #if MIN_VERSION_base(4,6,0) import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn) #else -import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn, - catch) +import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn) #endif import qualified System.IO as IO import qualified Data.ByteString.Char8 as B diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 4d2a39846..b6687c330 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -59,11 +59,7 @@ import Text.Pandoc.Writers.Markdown ( writePlain ) import Data.Char ( toLower, isDigit, isAlphaNum ) import Network.URI ( unEscapeString ) import Text.Pandoc.MIME (getMimeType) -#if MIN_VERSION_base(4,6,0) -#else -import Prelude hiding (catch) -#endif -import Control.Exception (catch, SomeException) +import qualified Control.Exception as E import Text.Blaze.Html.Renderer.Utf8 (renderHtml) import Text.HTML.TagSoup @@ -76,7 +72,7 @@ data Chapter = Chapter (Maybe [Int]) [Block] data EPUBMetadata = EPUBMetadata{ epubIdentifier :: [Identifier] , epubTitle :: [Title] - , epubDate :: String + , epubDate :: [Date] , epubLanguage :: String , epubCreator :: [Creator] , epubContributor :: [Creator] @@ -97,6 +93,11 @@ data Stylesheet = StylesheetPath FilePath | StylesheetContents String deriving Show +data Date = Date{ + dateText :: String + , dateEvent :: Maybe String + } deriving Show + data Creator = Creator{ creatorText :: String , creatorRole :: Maybe String @@ -153,17 +154,19 @@ getEPUBMetadata opts meta = do then case lookup "lang" (writerVariables opts) of Just x -> return m{ epubLanguage = x } Nothing -> do - localeLang <- catch (liftM + localeLang <- E.catch (liftM (map (\c -> if c == '_' then '-' else c) . takeWhile (/='.')) $ getEnv "LANG") - (\e -> let _ = (e :: SomeException) in return "en-US") + (\e -> let _ = (e :: E.SomeException) in return "en-US") return m{ epubLanguage = localeLang } else return m let fixDate m = if null (epubDate m) then do currentTime <- getCurrentTime - return $ m{ epubDate = showDateTimeISO8601 currentTime } + return $ m{ epubDate = [ Date{ + dateText = showDateTimeISO8601 currentTime + , dateEvent = Nothing } ] } else return m let addAuthor m = if any (\c -> creatorRole c == Just "aut") $ epubCreator m @@ -187,8 +190,10 @@ addMetadataFromXML e@(Element (QName name _ (Just "dc")) attrs _ _) md , titleFileAs = getAttr "file-as" , titleType = getAttr "type" } : epubTitle md } - | name == "date" = md{ epubDate = fromMaybe "" $ normalizeDate' - $ strContent e } + | name == "date" = md{ epubDate = + Date{ dateText = fromMaybe "" $ normalizeDate' $ strContent e + , dateEvent = getAttr "event" + } : epubDate md } | name == "language" = md{ epubLanguage = strContent e } | name == "creator" = md{ epubCreator = Creator{ creatorText = strContent e @@ -253,6 +258,16 @@ getCreator s meta = getList s meta handleMetaValue , creatorRole = metaValueToString <$> M.lookup "role" m } handleMetaValue mv = Creator (metaValueToString mv) Nothing Nothing +getDate :: String -> Meta -> [Date] +getDate s meta = getList s meta handleMetaValue + where handleMetaValue (MetaMap m) = + Date{ dateText = maybe "" id $ + M.lookup "text" m >>= normalizeDate' . metaValueToString + , dateEvent = metaValueToString <$> M.lookup "event" m } + handleMetaValue mv = Date { dateText = maybe "" + id $ normalizeDate' $ metaValueToString mv + , dateEvent = Nothing } + simpleList :: String -> Meta -> [String] simpleList s meta = case lookupMeta s meta of @@ -282,8 +297,7 @@ metadataFromMeta opts meta = EPUBMetadata{ } where identifiers = getIdentifier meta titles = getTitle meta - date = fromMaybe "" $ - (metaValueToString <$> lookupMeta "date" meta) >>= normalizeDate' + date = getDate "date" meta language = maybe "" metaValueToString $ lookupMeta "language" meta `mplus` lookupMeta "lang" meta creators = getCreator "creator" meta @@ -641,7 +655,14 @@ metadataElement version md currentTime = identifierNodes = withIds "epub-id" toIdentifierNode $ epubIdentifier md titleNodes = withIds "epub-title" toTitleNode $ epubTitle md - dateNodes = dcTag' "date" $ epubDate md + dateNodes = if version == EPUB2 + then withIds "epub-date" toDateNode $ epubDate md + else -- epub3 allows only one dc:date + -- http://www.idpf.org/epub/30/spec/epub30-publications.html#sec-opf-dcdate + case epubDate md of + [] -> [] + (x:_) -> [dcNode "date" ! [("id","epub-date")] + $ dateText x] languageNodes = [dcTag "language" $ epubLanguage md] creatorNodes = withIds "epub-creator" (toCreatorNode "creator") $ epubCreator md @@ -675,7 +696,7 @@ metadataElement version md currentTime = (schemeToOnix `fmap` scheme) toCreatorNode s id' creator | version == EPUB2 = [dcNode s ! - ([("id",id')] ++ + (("id",id') : maybe [] (\x -> [("opf:file-as",x)]) (creatorFileAs creator) ++ maybe [] (\x -> [("opf:role",x)]) (creatorRole creator >>= toRelator)) $ creatorText creator] @@ -689,7 +710,7 @@ metadataElement version md currentTime = (creatorRole creator >>= toRelator) toTitleNode id' title | version == EPUB2 = [dcNode "title" ! - ([("id",id')] ++ + (("id",id') : maybe [] (\x -> [("opf:file-as",x)]) (titleFileAs title) ++ maybe [] (\x -> [("opf:title-type",x)]) (titleType title)) $ titleText title] @@ -701,6 +722,10 @@ metadataElement version md currentTime = maybe [] (\x -> [unode "meta" ! [("refines",'#':id'),("property","title-type")] $ x]) (titleType title) + toDateNode id' date = [dcNode "date" ! + (("id",id') : + maybe [] (\x -> [("opf:event",x)]) (dateEvent date)) $ + dateText date] schemeToOnix "ISBN-10" = "02" schemeToOnix "GTIN-13" = "03" schemeToOnix "UPC" = "04" diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native index 0d74c233d..b4713bc93 100644 --- a/tests/markdown-reader-more.native +++ b/tests/markdown-reader-more.native @@ -16,6 +16,8 @@ ,Header 3 ("my-header",[],[]) [Str "my",Space,Str "header"] ,Header 2 ("in-math",[],[]) [Str "$",Space,Str "in",Space,Str "math"] ,Para [Math InlineMath "\\$2 + \\$3"] +,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "math:"] +,Para [Str "$PATH",Space,Str "90",Space,Str "$PATH"] ,Header 2 ("commented-out-list-item",[],[]) [Str "Commented-out",Space,Str "list",Space,Str "item"] ,BulletList [[Plain [Str "one",Space,RawInline (Format "html") "<!--\n- two\n-->"]] diff --git a/tests/markdown-reader-more.txt b/tests/markdown-reader-more.txt index 739543bfd..4cd69c9d8 100644 --- a/tests/markdown-reader-more.txt +++ b/tests/markdown-reader-more.txt @@ -58,6 +58,10 @@ $\$2 + \$3$ +This should not be math: + +$PATH 90 $PATH + ## Commented-out list item - one |