From cd2551c16c1da0404b8de182f17160aebb69219d Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 2 May 2017 16:00:04 +0200 Subject: Added PandocResourceNotFound error. Use this instead of PandocIOError when a resource is not found in path. This improves the error message in this case, see #3629. --- src/Text/Pandoc/Class.hs | 12 ++++-------- src/Text/Pandoc/Error.hs | 3 +++ src/Text/Pandoc/Writers/Docx.hs | 11 ++++------- src/Text/Pandoc/Writers/ICML.hs | 6 +----- src/Text/Pandoc/Writers/ODT.hs | 6 +----- src/Text/Pandoc/Writers/RTF.hs | 5 +---- 6 files changed, 14 insertions(+), 29 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 1afa64c10..ad9901125 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -330,8 +330,7 @@ downloadOrRead sourceURL s = do convertSlash x = x withPaths :: PandocMonad m => [FilePath] -> (FilePath -> m a) -> FilePath -> m a -withPaths [] _ fp = throwError $ PandocIOError fp - (userError "file not found in resource path") +withPaths [] _ fp = throwError $ PandocResourceNotFound fp withPaths (p:ps) action fp = catchError (action (p fp)) (\_ -> withPaths ps action fp) @@ -433,20 +432,17 @@ instance PandocMonad PandocPure where modifyPureState $ \st -> st { stUniqStore = us } return u _ -> M.fail "uniq store ran out of elements" - openURL u = throwError $ PandocIOError u $ - userError "Cannot open URL in PandocPure" + openURL u = throwError $ PandocResourceNotFound u readFileLazy fp = do fps <- getsPureState stFiles case infoFileContents <$> getFileInfo fp fps of Just bs -> return (BL.fromStrict bs) - Nothing -> throwError $ PandocIOError fp - (userError "File not found in PureState") + Nothing -> throwError $ PandocResourceNotFound fp readFileStrict fp = do fps <- getsPureState stFiles case infoFileContents <$> getFileInfo fp fps of Just bs -> return bs - Nothing -> throwError $ PandocIOError fp - (userError "File not found in PureState") + Nothing -> throwError $ PandocResourceNotFound fp readDataFile Nothing "reference.docx" = do (B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceDocx readDataFile Nothing "reference.odt" = do diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 135cb3945..a6db5e047 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -58,6 +58,7 @@ data PandocError = PandocIOError String IOError | PandocPDFError String | PandocFilterError String String | PandocCouldNotFindDataFileError String + | PandocResourceNotFound String | PandocAppError String deriving (Show, Typeable, Generic) @@ -94,6 +95,8 @@ handleError (Left e) = filtername ++ ":\n" ++ msg PandocCouldNotFindDataFileError fn -> err 97 $ "Could not find data file " ++ fn + PandocResourceNotFound fn -> err 99 $ + "File " ++ fn ++ " not found in resource path" PandocAppError s -> err 1 s err :: Int -> String -> IO a diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index fddec91cc..620f9060e 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -55,7 +55,6 @@ import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Compat.Time import Text.Pandoc.Definition -import Text.Pandoc.Error import Text.Pandoc.Generic import Text.Pandoc.Highlighting (highlight) import Text.Pandoc.ImageSize @@ -1303,12 +1302,10 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do M.insert src (ident, imgpath, mbMimeType, imgElt, img) $ stImages st } return [imgElt]) - (\e -> do case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') - -- emit alt text - inlinesToOpenXML opts alt) + (\e -> do + report $ CouldNotFetchResource src (show e) + -- emit alt text + inlinesToOpenXML opts alt) br :: Element br = breakElement "textWrapping" diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index cd3cac5a7..4d9998665 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -25,7 +25,6 @@ import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition -import Text.Pandoc.Error (PandocError (..)) import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options @@ -550,10 +549,7 @@ imageICML opts style attr (src, _) = do report $ CouldNotDetermineImageSize src msg return def) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return def) let (ow, oh) = sizeInPoints imgS (imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 395ef0a96..6c6f38dbe 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -39,7 +39,6 @@ import System.FilePath (takeDirectory, takeExtension, (<.>)) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition -import Text.Pandoc.Error (PandocError (..)) import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) @@ -178,10 +177,7 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError modify $ \st -> st{ stEntries = entry : entries } return $ Image newattr lab (newsrc, t)) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return $ Emph lab) transformPicMath _ (Math t math) = do diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 67f0fc2e0..7aa2280dd 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -92,10 +92,7 @@ rtfEmbedImage opts x@(Image attr _ (src,_)) = catchError report $ CouldNotDetermineMimeType src return x) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return x) rtfEmbedImage _ x = return x -- cgit v1.2.3 From e02cfcdeaccf588399579283998a7fb93a5c08f6 Mon Sep 17 00:00:00 2001 From: Mauro Bieg Date: Wed, 3 May 2017 12:13:25 +0200 Subject: Markdown Writer: put space before reference link definitions Fixes #3630 (#3631). Previously the attributes in link reference definitions did not have a space preceding. --- src/Text/Pandoc/Writers/Markdown.hs | 2 +- test/command/3630.md | 8 ++++++++ 2 files changed, 9 insertions(+), 1 deletion(-) create mode 100644 test/command/3630.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 8e3ac3665..655fd8780 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -241,7 +241,7 @@ keyToMarkdown opts (label', (src, tit), attr) = do else space <> "\"" <> text tit <> "\"" return $ nest 2 $ hang 2 ("[" <> label' <> "]:" <> space) (text src <> tit') - <> linkAttributes opts attr + <+> linkAttributes opts attr -- | Return markdown representation of notes. notesToMarkdown :: PandocMonad m => WriterOptions -> [[Block]] -> MD m Doc diff --git a/test/command/3630.md b/test/command/3630.md new file mode 100644 index 000000000..db3a17dda --- /dev/null +++ b/test/command/3630.md @@ -0,0 +1,8 @@ +``` +% pandoc -f markdown -t markdown --reference-links +![foo](bar.png){#myId} +^D +![foo] + + [foo]: bar.png {#myId} +``` -- cgit v1.2.3 From 6e55e6837a38b83d0ed4329ab366c699d6c2551f Mon Sep 17 00:00:00 2001 From: schrieveslaach Date: Wed, 3 May 2017 12:16:48 +0200 Subject: LaTeX reader: Add support for tabularx environment (#3632) --- src/Text/Pandoc/Readers/LaTeX.hs | 7 ++- test/command/tabularx.md | 110 +++++++++++++++++++++++++++++++++++++++ 2 files changed, 116 insertions(+), 1 deletion(-) create mode 100644 test/command/tabularx.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index a54238206..b88b6eae4 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1156,6 +1156,7 @@ environments = M.fromList , ("table", env "table" $ resetCaption *> skipopts *> blocks >>= addTableCaption) , ("tabular*", env "tabular" $ simpTable True) + , ("tabularx", env "tabularx" $ simpTable True) , ("tabular", env "tabular" $ simpTable False) , ("quote", blockQuote <$> env "quote" blocks) , ("quotation", blockQuote <$> env "quotation" blocks) @@ -1414,7 +1415,11 @@ parseAligns = try $ do let lAlign = AlignLeft <$ char 'l' let rAlign = AlignRight <$ char 'r' let parAlign = AlignLeft <$ (char 'p' >> braced) - let alignChar = cAlign <|> lAlign <|> rAlign <|> parAlign + -- algins from tabularx + let xAlign = AlignLeft <$ char 'X' + let mAlign = AlignLeft <$ (char 'm' >> braced) + let bAlign = AlignLeft <$ (char 'b' >> braced) + let alignChar = cAlign <|> lAlign <|> rAlign <|> parAlign <|> xAlign <|> mAlign <|> bAlign let alignPrefix = char '>' >> braced let alignSuffix = char '<' >> braced let alignSpec = do diff --git a/test/command/tabularx.md b/test/command/tabularx.md new file mode 100644 index 000000000..1d295c978 --- /dev/null +++ b/test/command/tabularx.md @@ -0,0 +1,110 @@ +``` +% pandoc -f latex -t native +\begin{tabularx}{\linewidth}{|c|c|c|} +\hline + Column Heading 1 + & Column Heading 2 + & Column Heading 3 \\ +\hline + Cell 1.1 + & Cell 1.2 + & Cell 1.3 \\ +\hline + Cell 2.1 + & Cell 2.2 + & Cell 2.3 \\ +\hline + Cell 3.1 + & Cell 3.2 + & Cell 3.3 \\ +\hline +\end{tabularx} +^D +[Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] + [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] + [[[Plain [Str "Cell",Space,Str "1.1"]] + ,[Plain [Str "Cell",Space,Str "1.2"]] + ,[Plain [Str "Cell",Space,Str "1.3"]]] + ,[[Plain [Str "Cell",Space,Str "2.1"]] + ,[Plain [Str "Cell",Space,Str "2.2"]] + ,[Plain [Str "Cell",Space,Str "2.3"]]] + ,[[Plain [Str "Cell",Space,Str "3.1"]] + ,[Plain [Str "Cell",Space,Str "3.2"]] + ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +``` + +``` +% pandoc -f latex -t native +\begin{tabularx}{\linewidth}{|X|c|p{0.25\linewidth}|} +\hline + Column Heading 1 + & Column Heading 2 + & Column Heading 3 \\ +\hline + Cell 1.1 + & Cell 1.2 + & Cell 1.3 \\ +\hline + Cell 2.1 + & Cell 2.2 + & Cell 2.3 \\ +\hline + Cell 3.1 + & Cell 3.2 + & Cell 3.3 \\ +\hline +\end{tabularx} +^D +[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0] + [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] + [[[Plain [Str "Cell",Space,Str "1.1"]] + ,[Plain [Str "Cell",Space,Str "1.2"]] + ,[Plain [Str "Cell",Space,Str "1.3"]]] + ,[[Plain [Str "Cell",Space,Str "2.1"]] + ,[Plain [Str "Cell",Space,Str "2.2"]] + ,[Plain [Str "Cell",Space,Str "2.3"]]] + ,[[Plain [Str "Cell",Space,Str "3.1"]] + ,[Plain [Str "Cell",Space,Str "3.2"]] + ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +``` + +``` +% pandoc -f latex -t native +\begin{tabularx}{\linewidth}{|b{0.25\linewidth}|c|m{0.25\linewidth}|} +\hline + Column Heading 1 + & Column Heading 2 + & Column Heading 3 \\ +\hline + Cell 1.1 + & Cell 1.2 + & Cell 1.3 \\ +\hline + Cell 2.1 + & Cell 2.2 + & Cell 2.3 \\ +\hline + Cell 3.1 + & Cell 3.2 + & Cell 3.3 \\ +\hline +\end{tabularx} +^D +[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0] + [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] + [[[Plain [Str "Cell",Space,Str "1.1"]] + ,[Plain [Str "Cell",Space,Str "1.2"]] + ,[Plain [Str "Cell",Space,Str "1.3"]]] + ,[[Plain [Str "Cell",Space,Str "2.1"]] + ,[Plain [Str "Cell",Space,Str "2.2"]] + ,[Plain [Str "Cell",Space,Str "2.3"]]] + ,[[Plain [Str "Cell",Space,Str "3.1"]] + ,[Plain [Str "Cell",Space,Str "3.2"]] + ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +``` -- cgit v1.2.3 From 79855ef934175c9a8890653375e05735d8b05a8d Mon Sep 17 00:00:00 2001 From: David A Roberts Date: Wed, 3 May 2017 20:19:45 +1000 Subject: Markdown writer: better escaping for links (#3628) Previously the Markdown writer would sometimes create links where there were none in the source. This is now avoided by selectively escaping bracket characters when they occur in a place where a link might be created. Closes #3619. --- src/Text/Pandoc/Writers/Markdown.hs | 11 ++++++++++- test/command/3619.md | 28 ++++++++++++++++++++++++++++ 2 files changed, 38 insertions(+), 1 deletion(-) create mode 100644 test/command/3619.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 655fd8780..7c0874278 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -821,7 +821,8 @@ inlineListToMarkdown opts lst = do where go [] = return empty go (i:is) = case i of (Link _ _ _) -> case is of - -- If a link is followed by another link or '[' we don't shortcut + -- If a link is followed by another link, or '[', '(' or ':' + -- then we don't shortcut (Link _ _ _):_ -> unshortcutable Space:(Link _ _ _):_ -> unshortcutable Space:(Str('[':_)):_ -> unshortcutable @@ -831,9 +832,17 @@ inlineListToMarkdown opts lst = do SoftBreak:(Str('[':_)):_ -> unshortcutable SoftBreak:(RawInline _ ('[':_)):_ -> unshortcutable SoftBreak:(Cite _ _):_ -> unshortcutable + LineBreak:(Link _ _ _):_ -> unshortcutable + LineBreak:(Str('[':_)):_ -> unshortcutable + LineBreak:(RawInline _ ('[':_)):_ -> unshortcutable + LineBreak:(Cite _ _):_ -> unshortcutable (Cite _ _):_ -> unshortcutable Str ('[':_):_ -> unshortcutable + Str ('(':_):_ -> unshortcutable + Str (':':_):_ -> unshortcutable (RawInline _ ('[':_)):_ -> unshortcutable + (RawInline _ ('(':_)):_ -> unshortcutable + (RawInline _ (':':_)):_ -> unshortcutable (RawInline _ (' ':'[':_)):_ -> unshortcutable _ -> shortcutable _ -> shortcutable diff --git a/test/command/3619.md b/test/command/3619.md new file mode 100644 index 000000000..62962c43b --- /dev/null +++ b/test/command/3619.md @@ -0,0 +1,28 @@ +``` +% pandoc -f html -t markdown --reference-links +bar: baz +^D +[bar][]: baz + + [bar]: foo +``` + +``` +% pandoc -f html -t markdown --reference-links +bar(baz) +^D +[bar][](baz) + + [bar]: foo +``` + +``` +% pandoc -f html -t markdown_strict --reference-links +foo
bar +^D +[foo][] +[bar] + + [foo]: a + [bar]: b +``` -- cgit v1.2.3 From df23d96c8991b215ead8ceb11607c5bebfb1f6db Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 2 May 2017 23:41:45 +0200 Subject: Generalize tableWith, gridTableWith The parsing functions `tableWith` and `gridTableWith` are generalized to work with more parsers. The parser state only has to be an instance of the `HasOptions` class instead of requiring a concrete type. Block parsers are required to return blocks wrapped into a monad, as this makes it possible to use parsers returning results wrapped in `Future`s. --- src/Text/Pandoc/Parsing.hs | 49 ++++++++++++++++++++++-------------------- src/Text/Pandoc/Readers/RST.hs | 12 ++++++++--- 2 files changed, 35 insertions(+), 26 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index a6d3cd46a..e0c0e36d6 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -762,21 +762,22 @@ lineBlockLines = try $ do -- | Parse a table using 'headerParser', 'rowParser', -- 'lineParser', and 'footerParser'. -tableWith :: Stream s m Char - => ParserT s ParserState m ([Blocks], [Alignment], [Int]) - -> ([Int] -> ParserT s ParserState m [Blocks]) - -> ParserT s ParserState m sep - -> ParserT s ParserState m end - -> ParserT s ParserState m Blocks +tableWith :: (Stream s m Char, HasReaderOptions st, + Functor mf, Applicative mf, Monad mf) + => ParserT s st m (mf [Blocks], [Alignment], [Int]) + -> ([Int] -> ParserT s st m (mf [Blocks])) + -> ParserT s st m sep + -> ParserT s st m end + -> ParserT s st m (mf Blocks) tableWith headerParser rowParser lineParser footerParser = try $ do (heads, aligns, indices) <- headerParser - lines' <- rowParser indices `sepEndBy1` lineParser + lines' <- sequence <$> rowParser indices `sepEndBy1` lineParser footerParser numColumns <- getOption readerColumns let widths = if (indices == []) then replicate (length aligns) 0.0 else widthsFromIndices numColumns indices - return $ B.table mempty (zip aligns widths) heads lines' + return $ B.table mempty (zip aligns widths) <$> heads <*> lines' -- Calculate relative widths of table columns, based on indices widthsFromIndices :: Int -- Number of columns on terminal @@ -809,10 +810,11 @@ widthsFromIndices numColumns' indices = -- (which may be grid), then the rows, -- which may be grid, separated by blank lines, and -- ending with a footer (dashed line followed by blank line). -gridTableWith :: Stream [Char] m Char - => ParserT [Char] ParserState m Blocks -- ^ Block list parser - -> Bool -- ^ Headerless table - -> ParserT [Char] ParserState m Blocks +gridTableWith :: (Stream [Char] m Char, HasReaderOptions st, + Functor mf, Applicative mf, Monad mf) + => ParserT [Char] st m (mf Blocks) -- ^ Block list parser + -> Bool -- ^ Headerless table + -> ParserT [Char] st m (mf Blocks) gridTableWith blocks headless = tableWith (gridTableHeader headless blocks) (gridTableRow blocks) (gridTableSep '-') gridTableFooter @@ -835,14 +837,14 @@ removeFinalBar = reverse . dropWhile (`elem` " \t") . dropWhile (=='|') . reverse -- | Separator between rows of grid table. -gridTableSep :: Stream s m Char => Char -> ParserT s ParserState m Char +gridTableSep :: Stream s m Char => Char -> ParserT s st m Char gridTableSep ch = try $ gridDashedLines ch >> return '\n' -- | Parse header for a grid table. -gridTableHeader :: Stream [Char] m Char +gridTableHeader :: (Stream [Char] m Char, Functor mf, Applicative mf, Monad mf) => Bool -- ^ Headerless table - -> ParserT [Char] ParserState m Blocks - -> ParserT [Char] ParserState m ([Blocks], [Alignment], [Int]) + -> ParserT [Char] st m (mf Blocks) + -> ParserT [Char] st m (mf [Blocks], [Alignment], [Int]) gridTableHeader headless blocks = try $ do optional blanklines dashes <- gridDashedLines '-' @@ -862,25 +864,26 @@ gridTableHeader headless blocks = try $ do then replicate (length dashes) "" else map (intercalate " ") $ transpose $ map (gridTableSplitLine indices) rawContent - heads <- mapM (parseFromString blocks) $ map trim rawHeads + heads <- fmap sequence . mapM (parseFromString blocks) $ map trim rawHeads return (heads, aligns, indices) -gridTableRawLine :: Stream s m Char => [Int] -> ParserT s ParserState m [String] +gridTableRawLine :: Stream s m Char => [Int] -> ParserT s st m [String] gridTableRawLine indices = do char '|' line <- many1Till anyChar newline return (gridTableSplitLine indices line) -- | Parse row of grid table. -gridTableRow :: Stream [Char] m Char - => ParserT [Char] ParserState m Blocks +gridTableRow :: (Stream [Char] m Char, Functor mf, Applicative mf, Monad mf) + => ParserT [Char] st m (mf Blocks) -> [Int] - -> ParserT [Char] ParserState m [Blocks] + -> ParserT [Char] st m (mf [Blocks]) gridTableRow blocks indices = do colLines <- many1 (gridTableRawLine indices) let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $ transpose colLines - mapM (liftM compactifyCell . parseFromString blocks) cols + cells <- sequence <$> mapM (parseFromString blocks) cols + return $ fmap (map compactifyCell) cells removeOneLeadingSpace :: [String] -> [String] removeOneLeadingSpace xs = @@ -894,7 +897,7 @@ compactifyCell :: Blocks -> Blocks compactifyCell bs = head $ compactify [bs] -- | Parse footer for a grid table. -gridTableFooter :: Stream s m Char => ParserT s ParserState m [Char] +gridTableFooter :: Stream s m Char => ParserT s st m [Char] gridTableFooter = blanklines --- diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 7564998ff..628351f36 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -32,6 +32,7 @@ Conversion from reStructuredText to 'Pandoc' document. -} module Text.Pandoc.Readers.RST ( readRST ) where import Control.Monad (guard, liftM, mzero, when) +import Control.Monad.Identity (Identity(..)) import Control.Monad.Except (throwError) import Data.Char (isHexDigit, isSpace, toLower, toUpper) import Data.List (deleteFirstsBy, findIndex, intercalate, isInfixOf, isSuffixOf, @@ -1119,8 +1120,12 @@ simpleTable :: PandocMonad m => Bool -- ^ Headerless table -> RSTParser m Blocks simpleTable headless = do - tbl <- tableWith (simpleTableHeader headless) simpleTableRow - sep simpleTableFooter + let wrapIdFst (a, b, c) = (Identity a, b, c) + wrapId = fmap Identity + tbl <- runIdentity <$> tableWith + (wrapIdFst <$> simpleTableHeader headless) + (wrapId <$> simpleTableRow) + sep simpleTableFooter -- Simple tables get 0s for relative column widths (i.e., use default) case B.toList tbl of [Table c a _w h l] -> return $ B.singleton $ @@ -1134,7 +1139,8 @@ simpleTable headless = do gridTable :: PandocMonad m => Bool -- ^ Headerless table -> RSTParser m Blocks -gridTable headerless = gridTableWith parseBlocks headerless +gridTable headerless = runIdentity <$> + gridTableWith (Identity <$> parseBlocks) headerless table :: PandocMonad m => RSTParser m Blocks table = gridTable False <|> simpleTable False <|> -- cgit v1.2.3 From 57cba3f1d5aa682df4ca8aafc3bc1d2ed4ead911 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Wed, 3 May 2017 22:43:34 +0200 Subject: Org reader: support table.el tables Closes #3314 --- src/Text/Pandoc/Readers/Org/BlockStarts.hs | 5 +++++ src/Text/Pandoc/Readers/Org/Blocks.hs | 20 +++++++++++------- src/Text/Pandoc/Readers/Org/Parsing.hs | 1 + test/command/3314.md | 34 ++++++++++++++++++++++++++++++ 4 files changed, 52 insertions(+), 8 deletions(-) create mode 100644 test/command/3314.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index cc2e82d5b..f05725f16 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -61,6 +61,10 @@ headerStart = try $ tableStart :: Monad m => OrgParser m Char tableStart = try $ skipSpaces *> char '|' +gridTableStart :: Monad m => OrgParser m () +gridTableStart = try $ skipSpaces <* char '+' <* char '-' + + latexEnvStart :: Monad m => OrgParser m String latexEnvStart = try $ do skipSpaces *> string "\\begin{" @@ -126,6 +130,7 @@ endOfBlock = lookAhead . try $ do , hline , metaLineStart , commentLineStart + , gridTableStart , void noteMarker , void tableStart , void drawerStart diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index b0a19b833..89c076869 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -755,7 +755,11 @@ data OrgTable = OrgTable } table :: PandocMonad m => OrgParser m (F Blocks) -table = try $ do +table = gridTableWith blocks True <|> orgTable + +-- | A normal org table +orgTable :: PandocMonad m => OrgParser m (F Blocks) +orgTable = try $ do -- don't allow a table on the first line of a list item; org requires that -- tables start at first non-space character on the line let isFirstInListItem st = (orgStateParserContext st == ListItemState) && @@ -854,28 +858,28 @@ normalizeTable (OrgTable colProps heads rows) = rowToContent :: OrgTable -> OrgTableRow -> F OrgTable -rowToContent orgTable row = +rowToContent tbl row = case row of OrgHlineRow -> return singleRowPromotedToHeader OrgAlignRow props -> return . setProperties $ props OrgContentRow cs -> appendToBody cs where singleRowPromotedToHeader :: OrgTable - singleRowPromotedToHeader = case orgTable of + singleRowPromotedToHeader = case tbl of OrgTable{ orgTableHeader = [], orgTableRows = b:[] } -> - orgTable{ orgTableHeader = b , orgTableRows = [] } - _ -> orgTable + tbl{ orgTableHeader = b , orgTableRows = [] } + _ -> tbl setProperties :: [ColumnProperty] -> OrgTable - setProperties ps = orgTable{ orgTableColumnProperties = ps } + setProperties ps = tbl{ orgTableColumnProperties = ps } appendToBody :: F [Blocks] -> F OrgTable appendToBody frow = do newRow <- frow - let oldRows = orgTableRows orgTable + let oldRows = orgTableRows tbl -- NOTE: This is an inefficient O(n) operation. This should be changed -- if performance ever becomes a problem. - return orgTable{ orgTableRows = oldRows ++ [newRow] } + return tbl{ orgTableRows = oldRows ++ [newRow] } -- diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 464ef9ca6..aa3a08279 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -70,6 +70,7 @@ module Text.Pandoc.Readers.Org.Parsing , dash , ellipses , citeKey + , gridTableWith -- * Re-exports from Text.Pandoc.Parsec , runParser , runParserT diff --git a/test/command/3314.md b/test/command/3314.md new file mode 100644 index 000000000..064b04cbd --- /dev/null +++ b/test/command/3314.md @@ -0,0 +1,34 @@ +See #3315 and . + +``` +% pandoc -f org -t html5 ++-----------+-------+----------+ +| First | 12.0 | Example | +| | | row | +| | | spanning | +| | | lines | ++-----------+-------+----------+ +| Second | 5.0 | Another | ++-----------+-------+----------+ +^D + +++++ + + + + + + + + + + + + +
First12.0Example row spanning lines
Second5.0Another
+``` + -- cgit v1.2.3 From 430e6be1f41358bed21b2edf02bcdb41dbee88cc Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 4 May 2017 12:36:52 +0300 Subject: Muse writer: omit automatic header identifiers (#3633) --- src/Text/Pandoc/Writers/Muse.hs | 11 ++++++++++- test/writer.muse | 40 ---------------------------------------- 2 files changed, 10 insertions(+), 41 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 8f6493975..8b083e2c6 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -53,6 +53,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared +import qualified Data.Set as Set type Notes = [[Block]] data WriterState = @@ -60,6 +61,7 @@ data WriterState = , stOptions :: WriterOptions , stTopLevel :: Bool , stInsideBlock :: Bool + , stIds :: Set.Set String } -- | Convert Pandoc to Muse. @@ -72,6 +74,7 @@ writeMuse opts document = , stOptions = opts , stTopLevel = True , stInsideBlock = False + , stIds = Set.empty } in evalStateT (pandocToMuse document) st @@ -184,8 +187,14 @@ blockToMuse (DefinitionList items) = do let ind = offset label'' return $ hang ind label'' contents blockToMuse (Header level (ident,_,_) inlines) = do + opts <- gets stOptions contents <- inlineListToMuse inlines - let attr' = if null ident + + ids <- gets stIds + let autoId = uniqueIdent inlines ids + modify $ \st -> st{ stIds = Set.insert autoId ids } + + let attr' = if null ident || (isEnabled Ext_auto_identifiers opts && ident == autoId) then empty else "#" <> text ident <> cr let header' = text $ replicate level '*' diff --git a/test/writer.muse b/test/writer.muse index c19cb8ab2..73f1cf604 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -9,47 +9,30 @@ markdown test suite. * Headers -#headers - ** Level 2 with an [[/url][embedded link]] -#level-2-with-an-embedded-link - *** Level 3 with emphasis -#level-3-with-emphasis - **** Level 4 -#level-4 - ***** Level 5 -#level-5 - * Level 1 -#level-1 - ** Level 2 with emphasis -#level-2-with-emphasis - *** Level 3 -#level-3 with no blank line ** Level 2 -#level-2 with no blank line ---- * Paragraphs -#paragraphs Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. @@ -65,7 +48,6 @@ here. * Block Quotes -#block-quotes E-mail style: @@ -105,7 +87,6 @@ And a following paragraph. * Code Blocks -#code-blocks Code: @@ -130,11 +111,8 @@ These should not be escaped: \$ \\ \> \[ \{ * Lists -#lists - ** Unordered -#unordered Asterisks tight: - asterisk 1 @@ -173,7 +151,6 @@ Minuses loose: ** Ordered -#ordered Tight: 1. First @@ -208,7 +185,6 @@ Multiple paragraphs: ** Nested -#nested - Tab - Tab - Tab @@ -234,7 +210,6 @@ Same thing but with paragraphs: ** Tabs and spaces -#tabs-and-spaces - this is a list item indented with tabs - this is a list item indented with spaces @@ -243,7 +218,6 @@ Same thing but with paragraphs: ** Fancy list markers -#fancy-list-markers 2. begins with 2 3. and now 3 @@ -277,7 +251,6 @@ B. Williams * Definition Lists -#definition-lists Tight using spaces: apple :: red fruit @@ -339,7 +312,6 @@ Blank line after term, indented marker, alternate markers: * HTML Blocks -#html-blocks Simple block on one line: fooAnd nested without indentation: @@ -489,7 +461,6 @@ Hr’s: * Inline Markup -#inline-markup This is emphasized, and so is this. This is strong, and so is this. @@ -521,7 +492,6 @@ spaces: a^b c^d, a~b c~d. * Smart quotes, ellipses, dashes -#smart-quotes-ellipses-dashes "Hello," said the spider. "'Shelob' is my name." 'A', 'B', and 'C' are letters. @@ -543,7 +513,6 @@ Ellipses…and…and…. * LaTeX -#latex - \cite[22-23]{smith.1899} - 2 + 2 = 4 - x ∈ y @@ -578,7 +547,6 @@ Cat & 1 \\ \hline * Special Characters -#special-characters Here is some unicode: - I hat: Î @@ -633,11 +601,8 @@ Minus: - * Links -#links - ** Explicit -#explicit Just a [[/url/][URL]]. [[/url/][URL and title]]. @@ -658,7 +623,6 @@ Just a [[/url/][URL]]. ** Reference -#reference Foo [[/url/][bar]]. Foo [[/url/][bar]]. @@ -687,7 +651,6 @@ Foo [[/url/][biz]]. ** With ampersands -#with-ampersands Here’s a [[http://example.com/?foo=1&bar=2][link with an ampersand in the URL]]. @@ -699,7 +662,6 @@ Here’s an [[/script?foo=1&bar=2][inline link in pointy braces]]. ** Autolinks -#autolinks With an ampersand: [[http://example.com/?foo=1&bar=2]] - In a list? @@ -723,7 +685,6 @@ or here: * Images -#images From "Voyage dans la Lune" by Georges Melies (1902): [[lalune.jpg][Voyage dans la Lune]] @@ -734,7 +695,6 @@ Here is a movie [[movie.jpg][movie]] icon. * Footnotes -#footnotes 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] -- cgit v1.2.3 From 1668998c460be69fb5b26c3ba727c878394be331 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 4 May 2017 16:36:35 +0200 Subject: Include `backtick_code_blocks` extension in `mardkown_mmd`. Closes #3637. --- src/Text/Pandoc/Extensions.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 24f7d56ec..374fae2c1 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -271,6 +271,7 @@ multimarkdownExtensions = extensionsFromList -- not to include these: , Ext_superscript , Ext_subscript + , Ext_backtick_code_blocks ] -- | Language extensions to be used with strict markdown. -- cgit v1.2.3 From c1b45adda09bae3c44e9e05832d54682696296c4 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 5 May 2017 17:03:27 +0200 Subject: SelfContained: Handle url() inside material retrieved from url(). This can happen e.g. with an @import of a google web font. (What is imported is some CSS which contains an url reference to the font itself.) Also, allow unescaped pipe (|) in URL. This is intended to help with #3629, but it doesn't seem to work. --- src/Text/Pandoc/SelfContained.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 53cb4a4b5..6391ef0e0 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -178,12 +178,21 @@ pCSSUrl sourceURL d = P.try $ do P.char ')' let fallback = B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ maybe "" (:[]) quote ++ ")") - case trim url of + -- pipes are used in URLs provided by Google Code fonts + -- but parseURI doesn't like them, so we escape them: + case escapeURIString (/='|') (trim url) of '#':_ -> return fallback 'd':'a':'t':'a':':':_ -> return fallback u -> do let url' = if isURI u then u else d u - enc <- lift $ getDataURI sourceURL "" url' - return (B.pack $ "url(" ++ enc ++ ")") + res <- lift $ getData sourceURL "" url' + case res of + Left uri -> return (B.pack $ "url(" ++ uri ++ ")") + Right (mt, raw) -> do + -- note that the downloaded content may + -- itself contain url(...). + raw' <- cssURLs sourceURL d raw + let enc = makeDataURI (mt, raw') + return (B.pack $ "url(" ++ enc ++ ")") getDataURI :: PandocMonad m => Maybe String -> MimeType -> String -> m String getDataURI sourceURL mimetype src = do -- cgit v1.2.3 From 89b3fcc8e050def3779fed716d70bfd4e7120a6b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 5 May 2017 23:03:31 +0200 Subject: SelfContained: special handling for css @import. We now avoid creating a data URI for the url under an @import. --- src/Text/Pandoc/SelfContained.hs | 41 +++++++++++++++++++++++++++++++++++----- 1 file changed, 36 insertions(+), 5 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 6391ef0e0..a5ae0a929 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -31,6 +31,7 @@ offline, by incorporating linked images, CSS, and scripts into the HTML using data URIs. -} module Text.Pandoc.SelfContained ( makeDataURI, makeSelfContained ) where +import Data.Monoid ((<>)) import Codec.Compression.GZip as Gzip import Control.Applicative ((<|>)) import Control.Monad.Except (throwError) @@ -149,7 +150,32 @@ cssURLs sourceURL d orig = do parseCSSUrls :: PandocMonad m => Maybe String -> FilePath -> ParsecT ByteString () m ByteString parseCSSUrls sourceURL d = B.concat <$> P.many - (pCSSWhite <|> pCSSComment <|> pCSSUrl sourceURL d <|> pCSSOther) + ( pCSSWhite + <|> pCSSComment + <|> pCSSImport sourceURL d + <|> (pCSSUrl >>= processCSSUrl sourceURL d) + <|> pCSSOther + ) + +pCSSImport :: PandocMonad m + => Maybe String -> FilePath -> ParsecT ByteString () m ByteString +pCSSImport sourceURL d = P.try $ do + P.string "@import" + P.spaces + url <- pCSSUrl + P.spaces + media <- P.manyTill P.anyChar (P.char ';') + let u = escapeURIString (/='|') (trim url) + let url' = if isURI u then u else d u + res <- lift $ getData sourceURL "" url' + case res of + Left uri -> return (B.pack $ "url(" ++ uri ++ ")") + Right (_, raw) -> do + raw' <- cssURLs sourceURL d raw + if null media + then return raw' + else return $ B.pack ("@media " ++ media ++ "{\n") <> raw' <> + B.pack "}" -- Note: some whitespace in CSS is significant, so we can't collapse it! pCSSWhite :: PandocMonad m => ParsecT ByteString () m ByteString @@ -168,16 +194,21 @@ pCSSOther = do (B.singleton <$> P.char '/') pCSSUrl :: PandocMonad m - => Maybe String -> FilePath -> ParsecT ByteString () m ByteString -pCSSUrl sourceURL d = P.try $ do + => ParsecT ByteString () m String +pCSSUrl = P.try $ do P.string "url(" P.spaces quote <- P.option Nothing (Just <$> P.oneOf "\"'") url <- P.manyTill P.anyChar (maybe (P.lookAhead (P.char ')')) P.char quote) P.spaces P.char ')' - let fallback = B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ - maybe "" (:[]) quote ++ ")") + return url + +processCSSUrl :: PandocMonad m + => Maybe String -> FilePath -> String + -> ParsecT ByteString () m ByteString +processCSSUrl sourceURL d url = do + let fallback = B.pack ("url('" ++ trim url ++ "')") -- pipes are used in URLs provided by Google Code fonts -- but parseURI doesn't like them, so we escape them: case escapeURIString (/='|') (trim url) of -- cgit v1.2.3 From 9f0a80457fb0ab343af651af8c7bc6f9dc467f55 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 5 May 2017 23:23:49 +0200 Subject: Revert "SelfContained: special handling for css @import." This reverts commit 89b3fcc8e050def3779fed716d70bfd4e7120a6b. --- src/Text/Pandoc/SelfContained.hs | 41 +++++----------------------------------- 1 file changed, 5 insertions(+), 36 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index a5ae0a929..6391ef0e0 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -31,7 +31,6 @@ offline, by incorporating linked images, CSS, and scripts into the HTML using data URIs. -} module Text.Pandoc.SelfContained ( makeDataURI, makeSelfContained ) where -import Data.Monoid ((<>)) import Codec.Compression.GZip as Gzip import Control.Applicative ((<|>)) import Control.Monad.Except (throwError) @@ -150,32 +149,7 @@ cssURLs sourceURL d orig = do parseCSSUrls :: PandocMonad m => Maybe String -> FilePath -> ParsecT ByteString () m ByteString parseCSSUrls sourceURL d = B.concat <$> P.many - ( pCSSWhite - <|> pCSSComment - <|> pCSSImport sourceURL d - <|> (pCSSUrl >>= processCSSUrl sourceURL d) - <|> pCSSOther - ) - -pCSSImport :: PandocMonad m - => Maybe String -> FilePath -> ParsecT ByteString () m ByteString -pCSSImport sourceURL d = P.try $ do - P.string "@import" - P.spaces - url <- pCSSUrl - P.spaces - media <- P.manyTill P.anyChar (P.char ';') - let u = escapeURIString (/='|') (trim url) - let url' = if isURI u then u else d u - res <- lift $ getData sourceURL "" url' - case res of - Left uri -> return (B.pack $ "url(" ++ uri ++ ")") - Right (_, raw) -> do - raw' <- cssURLs sourceURL d raw - if null media - then return raw' - else return $ B.pack ("@media " ++ media ++ "{\n") <> raw' <> - B.pack "}" + (pCSSWhite <|> pCSSComment <|> pCSSUrl sourceURL d <|> pCSSOther) -- Note: some whitespace in CSS is significant, so we can't collapse it! pCSSWhite :: PandocMonad m => ParsecT ByteString () m ByteString @@ -194,21 +168,16 @@ pCSSOther = do (B.singleton <$> P.char '/') pCSSUrl :: PandocMonad m - => ParsecT ByteString () m String -pCSSUrl = P.try $ do + => Maybe String -> FilePath -> ParsecT ByteString () m ByteString +pCSSUrl sourceURL d = P.try $ do P.string "url(" P.spaces quote <- P.option Nothing (Just <$> P.oneOf "\"'") url <- P.manyTill P.anyChar (maybe (P.lookAhead (P.char ')')) P.char quote) P.spaces P.char ')' - return url - -processCSSUrl :: PandocMonad m - => Maybe String -> FilePath -> String - -> ParsecT ByteString () m ByteString -processCSSUrl sourceURL d url = do - let fallback = B.pack ("url('" ++ trim url ++ "')") + let fallback = B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ + maybe "" (:[]) quote ++ ")") -- pipes are used in URLs provided by Google Code fonts -- but parseURI doesn't like them, so we escape them: case escapeURIString (/='|') (trim url) of -- cgit v1.2.3 From da8c153a6872a040440f8853a37f559bb3b26b02 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 6 May 2017 10:59:40 +0200 Subject: Org reader: support macros Closes: #3401 --- src/Text/Pandoc/Readers/Org/Inlines.hs | 21 +++++++++++++++++++++ src/Text/Pandoc/Readers/Org/Meta.hs | 27 ++++++++++++++++++++++++++- src/Text/Pandoc/Readers/Org/ParserState.hs | 18 ++++++++++++++++++ test/Tests/Readers/Org.hs | 18 ++++++++++++++++++ test/command/3401.md | 19 +++++++++++++++++++ 5 files changed, 102 insertions(+), 1 deletion(-) create mode 100644 test/command/3401.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 64ffb8ef5..5772e4157 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -120,6 +120,7 @@ inline = , superscript , inlineLaTeX , exportSnippet + , macro , smart , symbol ] <* (guard =<< newlinesCountWithinLimits) @@ -839,6 +840,26 @@ exportSnippet = try $ do snippet <- manyTill anyChar (try $ string "@@") returnF $ B.rawInline format snippet +macro :: PandocMonad m => OrgParser m (F Inlines) +macro = try $ do + recursionDepth <- orgStateMacroDepth <$> getState + guard $ recursionDepth < 15 + string "{{{" + name <- many alphaNum + args <- ([] <$ string "}}}") + <|> char '(' *> argument `sepBy` char ',' <* eoa + expander <- lookupMacro name <$> getState + case expander of + Nothing -> mzero + Just fn -> do + updateState $ \s -> s { orgStateMacroDepth = recursionDepth + 1 } + res <- parseFromString (mconcat <$> many inline) $ fn args + updateState $ \s -> s { orgStateMacroDepth = recursionDepth } + return res + where + argument = many $ notFollowedBy eoa *> noneOf "," + eoa = string ")}}}" + smart :: PandocMonad m => OrgParser m (F Inlines) smart = do guardEnabled Ext_smart diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 7938fc6c6..8c362f209 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -46,7 +46,7 @@ import Text.Pandoc.Definition import Control.Monad (mzero, void) import Data.Char (toLower) -import Data.List (intersperse) +import Data.List (intersperse, sort) import qualified Data.Map as M import Network.HTTP (urlEncode) @@ -151,6 +151,7 @@ optionLine = try $ do "todo" -> todoSequence >>= updateState . registerTodoSequence "seq_todo" -> todoSequence >>= updateState . registerTodoSequence "typ_todo" -> todoSequence >>= updateState . registerTodoSequence + "macro" -> macroDefinition >>= updateState . registerMacro _ -> mzero addLinkFormat :: Monad m => String @@ -218,3 +219,27 @@ todoSequence = try $ do let todoMarkers = map (TodoMarker Todo) todo doneMarkers = map (TodoMarker Done) done in todoMarkers ++ doneMarkers + +macroDefinition :: Monad m => OrgParser m (String, [String] -> String) +macroDefinition = try $ do + macroName <- many1 nonspaceChar <* skipSpaces + firstPart <- expansionPart + (elemOrder, parts) <- unzip <$> many ((,) <$> placeholder <*> expansionPart) + let expander = mconcat . alternate (firstPart:parts) . reorder elemOrder + return (macroName, expander) + where + placeholder :: Monad m => OrgParser m Int + placeholder = try . fmap read $ char '$' *> many1 digit + + expansionPart :: Monad m => OrgParser m String + expansionPart = try $ many (notFollowedBy placeholder *> noneOf "\n\r") + + alternate :: [a] -> [a] -> [a] + alternate [] ys = ys + alternate xs [] = xs + alternate (x:xs) (y:ys) = x : y : alternate xs ys + + reorder :: [Int] -> [String] -> [String] + reorder perm xs = + let element n = take 1 $ drop (n - 1) xs + in concatMap element perm diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index bdd1dc951..e47565814 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -39,6 +39,9 @@ module Text.Pandoc.Readers.Org.ParserState , TodoState (..) , activeTodoMarkers , registerTodoSequence + , MacroExpander + , lookupMacro + , registerMacro , F , askF , asksF @@ -78,6 +81,8 @@ type OrgNoteTable = [OrgNoteRecord] -- | Map of functions for link transformations. The map key is refers to the -- link-type, the corresponding function transforms the given link string. type OrgLinkFormatters = M.Map String (String -> String) +-- | Macro expander function +type MacroExpander = [String] -> String -- | The states in which a todo item can be data TodoState = Todo | Done @@ -105,6 +110,8 @@ data OrgParserState = OrgParserState , orgStateLastPreCharPos :: Maybe SourcePos , orgStateLastStrPos :: Maybe SourcePos , orgStateLinkFormatters :: OrgLinkFormatters + , orgStateMacros :: M.Map String MacroExpander + , orgStateMacroDepth :: Int , orgStateMeta :: F Meta , orgStateNotes' :: OrgNoteTable , orgStateOptions :: ReaderOptions @@ -156,6 +163,8 @@ defaultOrgParserState = OrgParserState , orgStateLastPreCharPos = Nothing , orgStateLastStrPos = Nothing , orgStateLinkFormatters = M.empty + , orgStateMacros = M.empty + , orgStateMacroDepth = 0 , orgStateMeta = return nullMeta , orgStateNotes' = [] , orgStateOptions = def @@ -185,6 +194,15 @@ activeTodoSequences st = activeTodoMarkers :: OrgParserState -> TodoSequence activeTodoMarkers = concat . activeTodoSequences +lookupMacro :: String -> OrgParserState -> Maybe MacroExpander +lookupMacro macroName = M.lookup macroName . orgStateMacros + +registerMacro :: (String, MacroExpander) -> OrgParserState -> OrgParserState +registerMacro (name, expander) st = + let curMacros = orgStateMacros st + in st{ orgStateMacros = M.insert name expander curMacros } + + -- -- Export Settings diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs index 7a7960396..278d91cfd 100644 --- a/test/Tests/Readers/Org.hs +++ b/test/Tests/Readers/Org.hs @@ -469,6 +469,24 @@ tests = , citationNoteNum = 0 , citationHash = 0} in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}") + + , "Macro" =: + unlines [ "#+MACRO: HELLO /Hello, $1/" + , "{{{HELLO(World)}}}" + ] =?> + para (emph "Hello, World") + + , "Macro repeting its argument" =: + unlines [ "#+MACRO: HELLO $1$1" + , "{{{HELLO(moin)}}}" + ] =?> + para "moinmoin" + + , "Macro called with too few arguments" =: + unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" + , "{{{HELLO()}}}" + ] =?> + para "Foo Bar" ] , testGroup "Meta Information" $ diff --git a/test/command/3401.md b/test/command/3401.md new file mode 100644 index 000000000..99528553a --- /dev/null +++ b/test/command/3401.md @@ -0,0 +1,19 @@ +See #3401 and + +``` +% pandoc -f org -t native +#+MACRO: HELLO /Hello, $1/ +{{{HELLO(World)}}} +^D +[Para [Emph [Str "Hello,",Space,Str "World"]]] +``` + +Inverted argument order + +``` +% pandoc -f org -t native +#+MACRO: A $2,$1 +{{{A(1,2)}}} +^D +[Para [Str "2,1"]] +``` -- cgit v1.2.3 From bf44b885228ae2352777372c7f06b800560d3914 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 6 May 2017 11:32:38 +0200 Subject: Drop redundant import of sort This was left in accidentally. --- src/Text/Pandoc/Readers/Org/Meta.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 8c362f209..5dc742403 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -46,7 +46,7 @@ import Text.Pandoc.Definition import Control.Monad (mzero, void) import Data.Char (toLower) -import Data.List (intersperse, sort) +import Data.List (intersperse) import qualified Data.Map as M import Network.HTTP (urlEncode) -- cgit v1.2.3 From ddf2524477e2a59b36fd37f7e5957ebb3b37c265 Mon Sep 17 00:00:00 2001 From: schrieveslaach Date: Sat, 6 May 2017 15:09:29 +0200 Subject: Fix keyval funtion: pandoc did not parse options in braces correctly.… (#3642) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit * Fix keyval funtion: pandoc did not parse options in braces correctly. Additionally, dot, dash, and colon were no valid characters * Add | as possible option value * Improved code --- src/Text/Pandoc/Readers/LaTeX.hs | 2 +- test/command/lstlisting.md | 25 +++++++++++++++++++++++++ 2 files changed, 26 insertions(+), 1 deletion(-) create mode 100644 test/command/lstlisting.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b88b6eae4..1ce92a4a2 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1095,7 +1095,7 @@ parseListingsOptions options = keyval :: PandocMonad m => LP m (String, String) keyval = try $ do key <- many1 alphaNum - val <- option "" $ char '=' >> many1 (alphaNum <|> char '.' <|> char '\\') + val <- option "" $ char '=' >> braced <|> (many1 (alphaNum <|> oneOf ".:-|\\")) skipMany spaceChar optional (char ',') skipMany spaceChar diff --git a/test/command/lstlisting.md b/test/command/lstlisting.md new file mode 100644 index 000000000..d928cc702 --- /dev/null +++ b/test/command/lstlisting.md @@ -0,0 +1,25 @@ +``` +% pandoc -f latex -t native +\begin{lstlisting}[language=Java, caption={Java Example}, label=lst:Hello-World] +public class World { + public static void main(String[] args) { + System.out.println("Hello World"); + } +} +\end{lstlisting} +^D +[CodeBlock ("lst:Hello-World",["java"],[("language","Java"),("caption","Java Example"),("label","lst:Hello-World")]) "public class World {\n public static void main(String[] args) {\n System.out.println(\"Hello World\");\n }\n}"] +``` + +``` +% pandoc -f latex -t native +\begin{lstlisting}[language=Java, escapechar=|, caption={Java Example}, label=lst:Hello-World] +public class World { + public static void main(String[] args) { + System.out.println("Hello World"); + } +} +\end{lstlisting} +^D +[CodeBlock ("lst:Hello-World",["java"],[("language","Java"),("escapechar","|"),("caption","Java Example"),("label","lst:Hello-World")]) "public class World {\n public static void main(String[] args) {\n System.out.println(\"Hello World\");\n }\n}"] +``` -- cgit v1.2.3 From f20c89e24380007a47f3e28889706a6f584bc6e0 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 6 May 2017 22:15:51 +0200 Subject: LaTeX reader: Better handling of comments inside math environments. This solves a problem with commented out `\end{eqnarray}` inside an eqnarray (among other things). Closes #3113. --- src/Text/Pandoc/Readers/LaTeX.hs | 73 +++++++++++++++++++++++----------------- test/command/3113.md | 13 +++++++ 2 files changed, 56 insertions(+), 30 deletions(-) create mode 100644 test/command/3113.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 1ce92a4a2..b13fc215b 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -492,20 +492,20 @@ isBlockCommand s = s `M.member` (blockCommands :: M.Map String (LP PandocPure Bl inlineEnvironments :: PandocMonad m => M.Map String (LP m Inlines) inlineEnvironments = M.fromList - [ ("displaymath", mathEnv id Nothing "displaymath") - , ("math", math <$> verbEnv "math") - , ("equation", mathEnv id Nothing "equation") - , ("equation*", mathEnv id Nothing "equation*") - , ("gather", mathEnv id (Just "gathered") "gather") - , ("gather*", mathEnv id (Just "gathered") "gather*") - , ("multline", mathEnv id (Just "gathered") "multline") - , ("multline*", mathEnv id (Just "gathered") "multline*") - , ("eqnarray", mathEnv id (Just "aligned") "eqnarray") - , ("eqnarray*", mathEnv id (Just "aligned") "eqnarray*") - , ("align", mathEnv id (Just "aligned") "align") - , ("align*", mathEnv id (Just "aligned") "align*") - , ("alignat", mathEnv id (Just "aligned") "alignat") - , ("alignat*", mathEnv id (Just "aligned") "alignat*") + [ ("displaymath", mathEnvWith id Nothing "displaymath") + , ("math", math <$> mathEnv "math") + , ("equation", mathEnvWith id Nothing "equation") + , ("equation*", mathEnvWith id Nothing "equation*") + , ("gather", mathEnvWith id (Just "gathered") "gather") + , ("gather*", mathEnvWith id (Just "gathered") "gather*") + , ("multline", mathEnvWith id (Just "gathered") "multline") + , ("multline*", mathEnvWith id (Just "gathered") "multline*") + , ("eqnarray", mathEnvWith id (Just "aligned") "eqnarray") + , ("eqnarray*", mathEnvWith id (Just "aligned") "eqnarray*") + , ("align", mathEnvWith id (Just "aligned") "align") + , ("align*", mathEnvWith id (Just "aligned") "align*") + , ("alignat", mathEnvWith id (Just "aligned") "alignat") + , ("alignat*", mathEnvWith id (Just "aligned") "alignat*") ] inlineCommands :: PandocMonad m => M.Map String (LP m Inlines) @@ -1187,19 +1187,19 @@ environments = M.fromList , ("obeylines", parseFromString (para . trimInlines . mconcat <$> many inline) =<< intercalate "\\\\\n" . lines <$> verbEnv "obeylines") - , ("displaymath", mathEnv para Nothing "displaymath") - , ("equation", mathEnv para Nothing "equation") - , ("equation*", mathEnv para Nothing "equation*") - , ("gather", mathEnv para (Just "gathered") "gather") - , ("gather*", mathEnv para (Just "gathered") "gather*") - , ("multline", mathEnv para (Just "gathered") "multline") - , ("multline*", mathEnv para (Just "gathered") "multline*") - , ("eqnarray", mathEnv para (Just "aligned") "eqnarray") - , ("eqnarray*", mathEnv para (Just "aligned") "eqnarray*") - , ("align", mathEnv para (Just "aligned") "align") - , ("align*", mathEnv para (Just "aligned") "align*") - , ("alignat", mathEnv para (Just "aligned") "alignat") - , ("alignat*", mathEnv para (Just "aligned") "alignat*") + , ("displaymath", mathEnvWith para Nothing "displaymath") + , ("equation", mathEnvWith para Nothing "equation") + , ("equation*", mathEnvWith para Nothing "equation*") + , ("gather", mathEnvWith para (Just "gathered") "gather") + , ("gather*", mathEnvWith para (Just "gathered") "gather*") + , ("multline", mathEnvWith para (Just "gathered") "multline") + , ("multline*", mathEnvWith para (Just "gathered") "multline*") + , ("eqnarray", mathEnvWith para (Just "aligned") "eqnarray") + , ("eqnarray*", mathEnvWith para (Just "aligned") "eqnarray*") + , ("align", mathEnvWith para (Just "aligned") "align") + , ("align*", mathEnvWith para (Just "aligned") "align*") + , ("alignat", mathEnvWith para (Just "aligned") "alignat") + , ("alignat*", mathEnvWith para (Just "aligned") "alignat*") ] figure :: PandocMonad m => LP m Blocks @@ -1264,19 +1264,32 @@ listenv name p = try $ do updateState $ \st -> st{ stateParserContext = oldCtx } return res -mathEnv :: PandocMonad m => (Inlines -> a) -> Maybe String -> String -> LP m a -mathEnv f innerEnv name = f <$> mathDisplay (inner <$> verbEnv name) +mathEnvWith :: PandocMonad m + => (Inlines -> a) -> Maybe String -> String -> LP m a +mathEnvWith f innerEnv name = f <$> mathDisplay (inner <$> mathEnv name) where inner x = case innerEnv of Nothing -> x Just y -> "\\begin{" ++ y ++ "}\n" ++ x ++ "\\end{" ++ y ++ "}" +mathEnv :: PandocMonad m => String -> LP m String +mathEnv name = do + skipopts + optional blankline + let endEnv = try $ controlSeq "end" *> braced >>= guard . (== name) + charMuncher = skipMany comment *> + (many1 (noneOf "\\%") <|> try (string "\\%") + <|> try (string "\\\\") <|> count 1 anyChar) + res <- concat <$> manyTill charMuncher endEnv + return $ stripTrailingNewlines res + verbEnv :: PandocMonad m => String -> LP m String verbEnv name = do skipopts optional blankline let endEnv = try $ controlSeq "end" *> braced >>= guard . (== name) - res <- manyTill anyChar endEnv + charMuncher = anyChar + res <- manyTill charMuncher endEnv return $ stripTrailingNewlines res fancyverbEnv :: PandocMonad m => String -> LP m Blocks diff --git a/test/command/3113.md b/test/command/3113.md new file mode 100644 index 000000000..f44e25709 --- /dev/null +++ b/test/command/3113.md @@ -0,0 +1,13 @@ +``` +% pandoc -f latex -t native +\begin{eqnarray} +A&=&B,\\ +C&=&D,\\ +%\end{eqnarray} +%\begin{eqnarray} +E&=&F +\end{eqnarray} +^D +[Para [Math DisplayMath "\\begin{aligned}\nA&=&B,\\\\\nC&=&D,\\\\\nE&=&F\\end{aligned}"]] +``` + -- cgit v1.2.3 From 82cc7fb0d462401b54bfe5172e7e49ab7b7302d9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 6 May 2017 22:56:16 +0200 Subject: Markdown reader: improved parsing of indented raw HTML blocks. Previously we inadvertently interpreted indented HTML as code blocks. This was a regression. We now seek to determine the indentation level of the contents of an HTML block, and (optionally) skip that much indentation. As a side effect, indentation may be stripped off of raw HTML blocks, if `markdown_in_html_blocks` is used. This is better than having things interpreted as indented code blocks. Closes #1841. --- src/Text/Pandoc/Readers/Markdown.hs | 8 ++++++- test/command/1841.md | 42 +++++++++++++++++++++++++++++++++++++ 2 files changed, 49 insertions(+), 1 deletion(-) create mode 100644 test/command/1841.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 5515c735b..691d4d5cf 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1088,13 +1088,19 @@ rawTeXBlock = do rawHtmlBlocks :: PandocMonad m => MarkdownParser m (F Blocks) rawHtmlBlocks = do (TagOpen tagtype _, raw) <- htmlTag isBlockTag + -- we don't want ' text' to be a code block: + skipMany spaceChar + indentlevel <- (blankline >> length <$> many (char ' ')) <|> return 0 -- try to find closing tag -- we set stateInHtmlBlock so that closing tags that can be either block or -- inline will not be parsed as inline tags oldInHtmlBlock <- stateInHtmlBlock <$> getState updateState $ \st -> st{ stateInHtmlBlock = Just tagtype } let closer = htmlTag (\x -> x ~== TagClose tagtype) - contents <- mconcat <$> many (notFollowedBy' closer >> block) + let block' = do notFollowedBy' closer + atMostSpaces indentlevel + block + contents <- mconcat <$> many block' result <- (closer >>= \(_, rawcloser) -> return ( return (B.rawBlock "html" $ stripMarkdownAttribute raw) <> diff --git a/test/command/1841.md b/test/command/1841.md new file mode 100644 index 000000000..408f224bd --- /dev/null +++ b/test/command/1841.md @@ -0,0 +1,42 @@ +``` +% pandoc + + + + + +
*one* [a link](http://google.com)
+^D + + + + + +
+one + +a link +
+``` + +``` +% pandoc + + + + + +
*one*[a link](http://google.com)
+^D + + + + + +
+one + +a link +
+``` + -- cgit v1.2.3 From e15a4badff82a62afd2356c1e1e3211ef4c6eb71 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 10:34:04 +0200 Subject: Simplify plumbing for document transformation. --- src/Text/Pandoc/App.hs | 46 +++++++++++++++++++++------------------------- 1 file changed, 21 insertions(+), 25 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index c38ebdd84..b8a3c6613 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -68,10 +68,10 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) -import Text.Pandoc.MediaBag (MediaBag, extractMediaBag, mediaDirectory) +import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) @@ -391,20 +391,16 @@ convertWithOpts opts = do E.throwIO PandocFailOnWarningError return res - let sourceToDoc :: [FilePath] -> PandocIO (Pandoc, MediaBag) + let sourceToDoc :: [FilePath] -> PandocIO Pandoc sourceToDoc sources' = case reader of StringReader r - | optFileScope opts || readerName == "json" -> do - pairs <- mapM - (readSource >=> withMediaBag . r readerOpts) sources - return (mconcat (map fst pairs), mconcat (map snd pairs)) + | optFileScope opts || readerName == "json" -> + mconcat <$> mapM (readSource >=> r readerOpts) sources | otherwise -> - readSources sources' >>= withMediaBag . r readerOpts - ByteStringReader r -> do - pairs <- mapM (readFile' >=> - withMediaBag . r readerOpts) sources - return (mconcat (map fst pairs), mconcat (map snd pairs)) + readSources sources' >>= r readerOpts + ByteStringReader r -> + mconcat <$> mapM (readFile' >=> r readerOpts) sources metadata <- if format == "jats" && lookup "csl" (optMetadata opts) == Nothing && @@ -416,16 +412,15 @@ convertWithOpts opts = do else return $ optMetadata opts runIO' $ do - (doc, media) <- sourceToDoc sources - doc' <- (maybe return (extractMedia media) (optExtractMedia opts) >=> - return . flip (foldr addMetadata) metadata >=> - applyTransforms transforms >=> - applyLuaFilters datadir (optLuaFilters opts) [format] >=> - applyFilters datadir filters' [format]) doc + (doc, media) <- withMediaBag $ sourceToDoc sources >>= + (maybe return extractMedia (optExtractMedia opts) + >=> return . flip (foldr addMetadata) metadata + >=> applyTransforms transforms + >=> applyLuaFilters datadir (optLuaFilters opts) [format] + >=> applyFilters datadir filters' [format]) case writer of - -- StringWriter f -> f writerOptions doc' >>= writerFn outputFile - ByteStringWriter f -> f writerOptions doc' >>= writeFnBinary outputFile + ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile StringWriter f | pdfOutput -> do -- make sure writer is latex, beamer, context, html5 or ms @@ -445,7 +440,7 @@ convertWithOpts opts = do when (isNothing mbPdfProg) $ liftIO $ E.throwIO $ PandocPDFProgramNotFoundError pdfprog - res <- makePDF pdfprog f writerOptions verbosity media doc' + res <- makePDF pdfprog f writerOptions verbosity media doc case res of Right pdf -> writeFnBinary outputFile pdf Left err' -> liftIO $ @@ -462,7 +457,7 @@ convertWithOpts opts = do format == "docbook") && optAscii opts then toEntities else id - output <- f writerOptions doc' + output <- f writerOptions doc selfcontain (output ++ ['\n' | not standalone]) >>= writerFn outputFile . handleEntities @@ -728,12 +723,13 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: -extractMedia :: MonadIO m => MediaBag -> FilePath -> Pandoc -> m Pandoc -extractMedia media dir d = +extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc +extractMedia dir d = do + media <- getMediaBag case [fp | (fp, _, _) <- mediaDirectory media] of [] -> return d fps -> do - extractMediaBag True dir media + liftIO $ extractMediaBag True dir media return $ walk (adjustImagePath dir fps) d adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -- cgit v1.2.3 From 400fe3188e3f5a3e48700ae114a0da05ae6e599a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 11:45:33 +0200 Subject: Allow `--extract-media` to work with non-binary input formats. If `--extract-media` is supplied with a non-binary input format, pandoc will attempt to extract the contents of all linked images, whether in local files, data: uris, or external uris. They will be named based on the sha1 hash of the contents. Closes #1583, #2289. Notes: - One thing that is slightly subideal with this commit is that identical resources will be downloaded multiple times. To improve this we could have mediabag store an original filename/url + a new name. - We might think about reusing some of this code, since more or less the same thing is done in the Docx, EPUB, PDF writers (with slight variations). --- src/Text/Pandoc/App.hs | 30 ++++++++++++++++++++++++++---- 1 file changed, 26 insertions(+), 4 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index b8a3c6613..212ae7fe2 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -45,6 +45,7 @@ import Data.Aeson (eitherDecode', encode) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) +import Data.Digest.Pure.SHA (sha1, showDigest) import qualified Data.Set as Set import Data.Foldable (foldrM) import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) @@ -68,17 +69,19 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, + fetchItem, insertMedia) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) +import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) import Text.Pandoc.Shared (headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 -import Text.Pandoc.Walk (walk) +import Text.Pandoc.Walk (walkM, walk) import Text.Pandoc.XML (toEntities) import Text.Printf #ifndef _WINDOWS @@ -413,11 +416,15 @@ convertWithOpts opts = do runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= - (maybe return extractMedia (optExtractMedia opts) + ( (if isJust (optExtractMedia opts) + then fillMedia (writerSourceURL writerOptions) + else return) + >=> maybe return extractMedia (optExtractMedia opts) >=> return . flip (foldr addMetadata) metadata >=> applyTransforms transforms >=> applyLuaFilters datadir (optLuaFilters opts) [format] - >=> applyFilters datadir filters' [format]) + >=> applyFilters datadir filters' [format] + ) case writer of ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile @@ -723,6 +730,21 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: +-- | Traverse tree, filling media bag. +fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc +fillMedia sourceURL d = walkM handleImage d + where handleImage :: Inline -> PandocIO Inline + handleImage (Image attr lab (src, tit)) = do + (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = B.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit) + handleImage x = return x + extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc extractMedia dir d = do media <- getMediaBag -- cgit v1.2.3 From f8e125f42d8568b9f2926c2d1a3eb37acba2b3d1 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 12:16:14 +0200 Subject: fillMediaBag: don't cause fatal error if resource not found. Report warning instead and change image to its alt text. --- src/Text/Pandoc/App.hs | 29 +++++++++++++++++++---------- 1 file changed, 19 insertions(+), 10 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 212ae7fe2..2efa69944 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -39,6 +39,7 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E +import Control.Monad.Except (catchError, throwError) import Control.Monad import Control.Monad.Trans import Data.Aeson (eitherDecode', encode) @@ -70,7 +71,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, - fetchItem, insertMedia) + fetchItem, insertMedia, report) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) @@ -734,15 +735,23 @@ defaultWriterName x = fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc fillMedia sourceURL d = walkM handleImage d where handleImage :: Inline -> PandocIO Inline - handleImage (Image attr lab (src, tit)) = do - (bs, mt) <- fetchItem sourceURL src - let ext = fromMaybe (takeExtension src) - (mt >>= extensionFromMimeType) - let bs' = B.fromChunks [bs] - let basename = showDigest $ sha1 bs' - let fname = basename <.> ext - insertMedia fname mt bs' - return $ Image attr lab (fname, tit) + handleImage (Image attr lab (src, tit)) = catchError + (do (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = B.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit)) + (\e -> do + case e of + PandocResourceNotFound _ -> do + report $ CouldNotFetchResource src + "replacing image with description" + -- emit alt text + return $ Span ("",["image"],[]) lab + _ -> throwError e) handleImage x = return x extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc -- cgit v1.2.3 From d414b2543a1686007e84c54bc711dff969dfb569 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 12:49:25 +0200 Subject: Remove https flag. Supporting two completely different libraries for fetching from URLs makes it difficult to trap errors, because of different error types expected from the libraries. There's no clear reason not to build with these https-capable libraires. --- pandoc.cabal | 14 ++++---------- src/Text/Pandoc/Shared.hs | 21 --------------------- stack.full.yaml | 1 - stack.pkg.yaml | 1 - stack.yaml | 1 - 5 files changed, 4 insertions(+), 34 deletions(-) (limited to 'src/Text') diff --git a/pandoc.cabal b/pandoc.cabal index f9ce1efd2..a713e9372 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -264,10 +264,6 @@ Flag weigh-pandoc Description: Build weigh-pandoc to measure memory usage. Default: False -Flag https - Description: Enable support for downloading of resources over https. - Default: True - Flag network-uri Description: Get Network.URI from the network-uri package Default: True @@ -316,7 +312,10 @@ Library JuicyPixels >= 3.1.6.1 && < 3.3, Glob >= 0.7 && < 0.8, cmark >= 0.5 && < 0.6, - doctemplates >= 0.1 && < 0.2 + doctemplates >= 0.1 && < 0.2, + http-client >= 0.4.30 && < 0.6, + http-client-tls >= 0.2.4 && < 0.4, + http-types >= 0.8 && < 0.10 if os(windows) Cpp-options: -D_WINDOWS else @@ -330,11 +329,6 @@ Library Build-Depends: network-uri >= 2.6 && < 2.7, network >= 2.6 else Build-Depends: network >= 2 && < 2.6 - if flag(https) - Build-Depends: http-client >= 0.4.30 && < 0.6, - http-client-tls >= 0.2.4 && < 0.4, - http-types >= 0.8 && < 0.10 - cpp-options: -DHTTP_CLIENT if flag(embed_data_files) cpp-options: -DEMBED_DATA_FILES build-depends: file-embed >= 0.0 && < 0.1 diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 8256d14c0..44a26509b 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -140,7 +140,6 @@ import Text.Pandoc.Data (dataFiles) #else import Paths_pandoc (getDataFileName) #endif -#ifdef HTTP_CLIENT import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, Request(port,host,requestHeaders)) import Network.HTTP.Client (parseRequest) @@ -150,12 +149,6 @@ import Network.HTTP.Client.TLS (tlsManagerSettings) import System.Environment (getEnv) import Network.HTTP.Types.Header ( hContentType, hUserAgent) import Network (withSocketsDo) -#else -import Network.URI (parseURI) -import Network.HTTP (findHeader, rspBody, - RequestMethod(..), HeaderName(..), mkRequest) -import Network.Browser (browse, setAllowRedirects, setOutHandler, request) -#endif -- | Version number of pandoc library. pandocVersion :: String @@ -715,7 +708,6 @@ openURL u let mime = takeWhile (/=',') u'' contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u'' in return (decodeLenient contents, Just mime) -#ifdef HTTP_CLIENT | otherwise = withSocketsDo $ do let parseReq = parseRequest (proxy :: Either IOError String) <- @@ -738,19 +730,6 @@ openURL u resp <- newManager tlsManagerSettings >>= httpLbs req'' return (BS.concat $ toChunks $ responseBody resp, UTF8.toString `fmap` lookup hContentType (responseHeaders resp)) -#else - | otherwise = getBodyAndMimeType `fmap` browse - (do liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..." - setOutHandler $ const (return ()) - setAllowRedirects True - request (getRequest' u')) - where getBodyAndMimeType (_, r) = (rspBody r, findHeader HdrContentType r) - getRequest' uriString = case parseURI uriString of - Nothing -> error ("Not a valid URL: " ++ - uriString) - Just v -> mkRequest GET v - u' = escapeURIString (/= '|') u -- pipes are rejected by Network.URI -#endif -- -- Error reporting diff --git a/stack.full.yaml b/stack.full.yaml index f05ccbce3..e5fff5a4e 100644 --- a/stack.full.yaml +++ b/stack.full.yaml @@ -3,7 +3,6 @@ flags: pandoc: trypandoc: false - https: true embed_data_files: false old-locale: false network-uri: true diff --git a/stack.pkg.yaml b/stack.pkg.yaml index 864982278..a131f14cb 100644 --- a/stack.pkg.yaml +++ b/stack.pkg.yaml @@ -1,7 +1,6 @@ flags: pandoc: trypandoc: false - https: true embed_data_files: true old-locale: false network-uri: true diff --git a/stack.yaml b/stack.yaml index b9f02b364..14769525a 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,7 +1,6 @@ flags: pandoc: trypandoc: false - https: true embed_data_files: false old-locale: false network-uri: true -- cgit v1.2.3 From 99be906101f7852e84e5da9c3b66dd6d99f649da Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 13:11:04 +0200 Subject: Added PandocHttpException, trap exceptions in fetching from URLs. Closes #3646. --- src/Text/Pandoc/App.hs | 17 +++++++++++++---- src/Text/Pandoc/Class.hs | 5 ++++- src/Text/Pandoc/Error.hs | 4 ++++ src/Text/Pandoc/Shared.hs | 9 +++++---- 4 files changed, 26 insertions(+), 9 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 2efa69944..a1691c5e2 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -376,7 +376,7 @@ convertWithOpts opts = do then 0 else optTabStop opts) - readSources :: (Functor m, MonadIO m) => [FilePath] -> m String + readSources :: [FilePath] -> PandocIO String readSources srcs = convertTabs . intercalate "\n" <$> mapM readSource srcs @@ -751,6 +751,11 @@ fillMedia sourceURL d = walkM handleImage d "replacing image with description" -- emit alt text return $ Span ("",["image"],[]) lab + PandocHttpError u er -> do + report $ CouldNotFetchResource u + (show er ++ "\rReplacing image with description.") + -- emit alt text + return $ Span ("",["image"],[]) lab _ -> throwError e) handleImage x = return x @@ -800,7 +805,7 @@ applyFilters mbDatadir filters args d = do expandedFilters <- mapM (expandFilterPath mbDatadir) filters foldrM ($) d $ map (flip externalFilter args) expandedFilters -readSource :: MonadIO m => FilePath -> m String +readSource :: FilePath -> PandocIO String readSource "-" = liftIO UTF8.getContents readSource src = case parseURI src of Just u | uriScheme u `elem` ["http:","https:"] -> @@ -809,8 +814,12 @@ readSource src = case parseURI src of liftIO $ UTF8.readFile (uriPath u) _ -> liftIO $ UTF8.readFile src -readURI :: MonadIO m => FilePath -> m String -readURI src = liftIO $ (UTF8.toString . fst) <$> openURL src +readURI :: FilePath -> PandocIO String +readURI src = do + res <- liftIO $ openURL src + case res of + Left e -> throwError $ PandocHttpError src e + Right (contents, _) -> return $ UTF8.toString contents readFile' :: MonadIO m => FilePath -> m B.ByteString readFile' "-" = liftIO B.getContents diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index ad9901125..939e0bd18 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -242,7 +242,10 @@ instance PandocMonad PandocIO where newUniqueHash = hashUnique <$> (liftIO IO.newUnique) openURL u = do report $ Fetching u - liftIOError IO.openURL u + res <- liftIO (IO.openURL u) + case res of + Right r -> return r + Left e -> throwError $ PandocHttpError u e readFileLazy s = liftIOError BL.readFile s readFileStrict s = liftIOError B.readFile s readDataFile mfp fname = liftIOError (IO.readDataFile mfp) fname diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index a6db5e047..9b3f1b902 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -42,10 +42,12 @@ import Text.Parsec.Pos hiding (Line) import qualified Text.Pandoc.UTF8 as UTF8 import System.Exit (exitWith, ExitCode(..)) import System.IO (stderr) +import Network.HTTP.Client (HttpException) type Input = String data PandocError = PandocIOError String IOError + | PandocHttpError String HttpException | PandocShouldNeverHappenError String | PandocSomeError String | PandocParseError String @@ -70,6 +72,8 @@ handleError (Right r) = return r handleError (Left e) = case e of PandocIOError _ err' -> ioError err' + PandocHttpError u err' -> err 61 $ + "Could not fetch " ++ u ++ "\n" ++ show err' PandocShouldNeverHappenError s -> err 62 s PandocSomeError s -> err 63 s PandocParseError s -> err 64 s diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 44a26509b..0ebaf0f89 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -141,7 +141,8 @@ import Text.Pandoc.Data (dataFiles) import Paths_pandoc (getDataFileName) #endif import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, - Request(port,host,requestHeaders)) + Request(port,host,requestHeaders), + HttpException) import Network.HTTP.Client (parseRequest) import Network.HTTP.Client (newManager) import Network.HTTP.Client.Internal (addProxy) @@ -702,13 +703,13 @@ readDataFileUTF8 userDir fname = UTF8.toString `fmap` readDataFile userDir fname -- | Read from a URL and return raw data and maybe mime type. -openURL :: String -> IO (BS.ByteString, Maybe MimeType) +openURL :: String -> IO (Either HttpException (BS.ByteString, Maybe MimeType)) openURL u | Just u'' <- stripPrefix "data:" u = let mime = takeWhile (/=',') u'' contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u'' - in return (decodeLenient contents, Just mime) - | otherwise = withSocketsDo $ do + in return $ Right (decodeLenient contents, Just mime) + | otherwise = E.try $ withSocketsDo $ do let parseReq = parseRequest (proxy :: Either IOError String) <- tryIOError $ getEnv "http_proxy" -- cgit v1.2.3 From af7215a048a490a7c69eb6ea906bf4ca5d09c1b1 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 20:42:32 +0200 Subject: Moved fillMedia, extractMedia from App to Class. Also generalized type of fillMedia to any instance of PandocMonad. --- src/Text/Pandoc/App.hs | 52 +++----------------------------------------- src/Text/Pandoc/Class.hs | 56 +++++++++++++++++++++++++++++++++++++++++++++--- 2 files changed, 56 insertions(+), 52 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index a1691c5e2..6bc345d73 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -39,14 +39,13 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E -import Control.Monad.Except (catchError, throwError) +import Control.Monad.Except (throwError) import Control.Monad import Control.Monad.Trans import Data.Aeson (eitherDecode', encode) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) -import Data.Digest.Pure.SHA (sha1, showDigest) import qualified Data.Set as Set import Data.Foldable (foldrM) import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) @@ -70,19 +69,16 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, - fetchItem, insertMedia, report) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, + extractMedia, fillMedia) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) -import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) -import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) import Text.Pandoc.Shared (headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 -import Text.Pandoc.Walk (walkM, walk) import Text.Pandoc.XML (toEntities) import Text.Printf #ifndef _WINDOWS @@ -731,48 +727,6 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: --- | Traverse tree, filling media bag. -fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc -fillMedia sourceURL d = walkM handleImage d - where handleImage :: Inline -> PandocIO Inline - handleImage (Image attr lab (src, tit)) = catchError - (do (bs, mt) <- fetchItem sourceURL src - let ext = fromMaybe (takeExtension src) - (mt >>= extensionFromMimeType) - let bs' = B.fromChunks [bs] - let basename = showDigest $ sha1 bs' - let fname = basename <.> ext - insertMedia fname mt bs' - return $ Image attr lab (fname, tit)) - (\e -> do - case e of - PandocResourceNotFound _ -> do - report $ CouldNotFetchResource src - "replacing image with description" - -- emit alt text - return $ Span ("",["image"],[]) lab - PandocHttpError u er -> do - report $ CouldNotFetchResource u - (show er ++ "\rReplacing image with description.") - -- emit alt text - return $ Span ("",["image"],[]) lab - _ -> throwError e) - handleImage x = return x - -extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc -extractMedia dir d = do - media <- getMediaBag - case [fp | (fp, _, _) <- mediaDirectory media] of - [] -> return d - fps -> do - liftIO $ extractMediaBag True dir media - return $ walk (adjustImagePath dir fps) d - -adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -adjustImagePath dir paths (Image attr lab (src, tit)) - | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) -adjustImagePath _ _ x = x - applyTransforms :: Monad m => [Transform] -> Pandoc -> m Pandoc applyTransforms transforms d = return $ foldr ($) d transforms diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 939e0bd18..7407d0799 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -61,6 +61,8 @@ module Text.Pandoc.Class ( PandocMonad(..) , runIOorExplode , runPure , withMediaBag + , fillMedia + , extractMedia ) where import Prelude hiding (readFile) @@ -76,8 +78,11 @@ import Text.Pandoc.Compat.Time (UTCTime) import Text.Pandoc.Logging import Text.Parsec (ParsecT) import qualified Text.Pandoc.Compat.Time as IO (getCurrentTime) -import Text.Pandoc.MIME (MimeType, getMimeType) +import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType) +import Text.Pandoc.Definition import Data.Char (toLower) +import Data.Digest.Pure.SHA (sha1, showDigest) +import Data.Maybe (fromMaybe) import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds , posixSecondsToUTCTime , POSIXTime ) @@ -86,13 +91,15 @@ import Network.URI ( escapeURIString, nonStrictRelativeTo, unEscapeString, parseURIReference, isAllowedInURI, parseURI, URI(..) ) import qualified Data.Time.LocalTime as IO (getCurrentTimeZone) -import Text.Pandoc.MediaBag (MediaBag, lookupMedia) +import Text.Pandoc.MediaBag (MediaBag, lookupMedia, extractMediaBag, + mediaDirectory) +import Text.Pandoc.Walk (walkM, walk) import qualified Text.Pandoc.MediaBag as MB import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import qualified System.Environment as IO (lookupEnv) import System.FilePath.Glob (match, compile) -import System.FilePath ((), takeExtension, dropExtension, isRelative) +import System.FilePath ((), (<.>), takeExtension, dropExtension, isRelative) import qualified System.FilePath.Glob as IO (glob) import qualified System.Directory as IO (getModificationTime) import Control.Monad as M (fail) @@ -338,6 +345,49 @@ withPaths (p:ps) action fp = catchError (action (p fp)) (\_ -> withPaths ps action fp) +-- | Traverse tree, filling media bag. +fillMedia :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc +fillMedia sourceURL d = walkM handleImage d + where handleImage :: PandocMonad m => Inline -> m Inline + handleImage (Image attr lab (src, tit)) = catchError + (do (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = BL.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit)) + (\e -> do + case e of + PandocResourceNotFound _ -> do + report $ CouldNotFetchResource src + "replacing image with description" + -- emit alt text + return $ Span ("",["image"],[]) lab + PandocHttpError u er -> do + report $ CouldNotFetchResource u + (show er ++ "\rReplacing image with description.") + -- emit alt text + return $ Span ("",["image"],[]) lab + _ -> throwError e) + handleImage x = return x + +-- | Extract media from the mediabag into a directory. +extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc +extractMedia dir d = do + media <- getMediaBag + case [fp | (fp, _, _) <- mediaDirectory media] of + [] -> return d + fps -> do + liftIO $ extractMediaBag True dir media + return $ walk (adjustImagePath dir fps) d + +adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline +adjustImagePath dir paths (Image attr lab (src, tit)) + | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) +adjustImagePath _ _ x = x + data PureState = PureState { stStdGen :: StdGen , stWord8Store :: [Word8] -- should be -- inifinite, -- cgit v1.2.3 From a902109c6d56f5249a0521c89ab90ca105b7b023 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 20:57:16 +0200 Subject: PDF: use fillMedia and extractMedia to extract media to tmp dir. This reduces code duplication. We should be able to do something similar in ODT, Docx, EPUB writers. --- src/Text/Pandoc/PDF.hs | 50 +++++++++++--------------------------------------- 1 file changed, 11 insertions(+), 39 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 696dbacf0..240da3ef0 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -34,14 +34,13 @@ module Text.Pandoc.PDF ( makePDF ) where import qualified Codec.Picture as JP import qualified Control.Exception as E -import Control.Monad (unless, when, (<=<)) +import Control.Monad (unless, when) import Control.Monad.Trans (MonadIO (..)) import qualified Data.ByteString as BS import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as BC -import Data.Digest.Pure.SHA (sha1, showDigest) import Data.List (isInfixOf) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) @@ -53,7 +52,7 @@ import System.IO (stdout) import System.IO.Temp (withTempDirectory, withTempFile) import Text.Pandoc.Definition import Text.Pandoc.MediaBag -import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) +import Text.Pandoc.MIME (getMimeType) import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..)) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.Shared (inDirectory, stringify, withTempDir) @@ -63,8 +62,8 @@ import Text.Pandoc.Writers.Shared (getField, metaToJSON) #ifdef _WINDOWS import Data.List (intercalate) #endif -import Text.Pandoc.Class (PandocIO, fetchItem, report, runIO, runIOorExplode, - setMediaBag, setVerbosity) +import Text.Pandoc.Class (PandocIO, report, runIO, runIOorExplode, + setMediaBag, setVerbosity, fillMedia, extractMedia) import Text.Pandoc.Logging #ifdef _WINDOWS @@ -135,40 +134,13 @@ handleImages :: Verbosity -> FilePath -- ^ temp dir to store images -> Pandoc -- ^ document -> IO Pandoc -handleImages verbosity opts mediabag tmpdir = - walkM (convertImages verbosity tmpdir) <=< - walkM (handleImage' verbosity opts mediabag tmpdir) - -handleImage' :: Verbosity - -> WriterOptions - -> MediaBag - -> FilePath - -> Inline - -> IO Inline -handleImage' verbosity opts mediabag tmpdir (Image attr ils (src,tit)) = do - exists <- doesFileExist src - if exists - then return $ Image attr ils (src,tit) - else do - res <- runIO $ do - setVerbosity verbosity - setMediaBag mediabag - fetchItem (writerSourceURL opts) src - case res of - Right (contents, Just mime) -> do - let ext = fromMaybe (takeExtension src) $ - extensionFromMimeType mime - let basename = showDigest $ sha1 $ BL.fromChunks [contents] - let fname = tmpdir basename <.> ext - BS.writeFile fname contents - return $ Image attr ils (fname,tit) - _ -> do - runIO $ do - setVerbosity verbosity - report $ CouldNotFetchResource src "skipping..." - -- return alt text - return $ Emph ils -handleImage' _ _ _ _ x = return x +handleImages verbosity opts mediabag tmpdir doc = do + doc' <- runIOorExplode $ do + setVerbosity verbosity + setMediaBag mediabag + fillMedia (writerSourceURL opts) doc >>= + extractMedia tmpdir + walkM (convertImages verbosity tmpdir) doc' convertImages :: Verbosity -> FilePath -> Inline -> IO Inline convertImages verbosity tmpdir (Image attr ils (src, tit)) = do -- cgit v1.2.3 From 6b086acae8f20ad46ca92139e47e516302280e94 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 21:03:18 +0200 Subject: Rename fillMedia -> fillMediaBag. --- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Class.hs | 6 +++--- src/Text/Pandoc/PDF.hs | 5 +++-- 3 files changed, 8 insertions(+), 7 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 6bc345d73..f340259f3 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -70,7 +70,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, - extractMedia, fillMedia) + extractMedia, fillMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) @@ -414,7 +414,7 @@ convertWithOpts opts = do runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) - then fillMedia (writerSourceURL writerOptions) + then fillMediaBag (writerSourceURL writerOptions) else return) >=> maybe return extractMedia (optExtractMedia opts) >=> return . flip (foldr addMetadata) metadata diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 7407d0799..4ef56ec33 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -61,7 +61,7 @@ module Text.Pandoc.Class ( PandocMonad(..) , runIOorExplode , runPure , withMediaBag - , fillMedia + , fillMediaBag , extractMedia ) where @@ -346,8 +346,8 @@ withPaths (p:ps) action fp = (\_ -> withPaths ps action fp) -- | Traverse tree, filling media bag. -fillMedia :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc -fillMedia sourceURL d = walkM handleImage d +fillMediaBag :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc +fillMediaBag sourceURL d = walkM handleImage d where handleImage :: PandocMonad m => Inline -> m Inline handleImage (Image attr lab (src, tit)) = catchError (do (bs, mt) <- fetchItem sourceURL src diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 240da3ef0..7097337e2 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -63,7 +63,8 @@ import Text.Pandoc.Writers.Shared (getField, metaToJSON) import Data.List (intercalate) #endif import Text.Pandoc.Class (PandocIO, report, runIO, runIOorExplode, - setMediaBag, setVerbosity, fillMedia, extractMedia) + setMediaBag, setVerbosity, + fillMediaBag, extractMedia) import Text.Pandoc.Logging #ifdef _WINDOWS @@ -138,7 +139,7 @@ handleImages verbosity opts mediabag tmpdir doc = do doc' <- runIOorExplode $ do setVerbosity verbosity setMediaBag mediabag - fillMedia (writerSourceURL opts) doc >>= + fillMediaBag (writerSourceURL opts) doc >>= extractMedia tmpdir walkM (convertImages verbosity tmpdir) doc' -- cgit v1.2.3 From 69110cde81a7bad260cdca579b4dcca306d4be2b Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 7 May 2017 22:41:38 +0300 Subject: Muse writer: Indent tables with one space (#3649) It is required to trigger Muse table rendering. --- src/Text/Pandoc/Writers/Muse.hs | 4 ++-- test/Tests/Writers/Muse.hs | 18 +++++++------- test/tables.muse | 52 ++++++++++++++++++++--------------------- 3 files changed, 37 insertions(+), 37 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 8b083e2c6..ccc6e9aef 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -216,7 +216,7 @@ blockToMuse (Table caption _ _ headers rows) = do let hpipeBlocks sep blocks = hcat $ intersperse sep' blocks where h = maximum (1 : map height blocks) sep' = lblock (length sep) $ vcat (map text $ replicate h sep) - let makeRow sep = hpipeBlocks sep . zipWith lblock widthsInChars + let makeRow sep = (" " <>) . (hpipeBlocks sep . zipWith lblock widthsInChars) let head' = makeRow " || " headers' let rowSeparator = if noHeaders then " | " else " | " rows'' <- mapM (\row -> do cols <- mapM blockListToMuse row @@ -224,7 +224,7 @@ blockToMuse (Table caption _ _ headers rows) = do let body = vcat rows'' return $ (if noHeaders then empty else head') $$ body - $$ (if null caption then empty else "|+ " <> caption' <> " +|") + $$ (if null caption then empty else " |+ " <> caption' <> " +|") $$ blankline blockToMuse (Div _ bs) = blockListToMuse bs blockToMuse Null = return empty diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 9a7dec580..65bf3e99b 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -155,8 +155,8 @@ tests = [ testGroup "block elements" ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in simpleTable [] rows =?> - unlines [ "Para 1.1 | Para 1.2" - , "Para 2.1 | Para 2.2" + unlines [ " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" ] , "table with header" =: let headers = [plain $ text "header 1", plain $ text "header 2"] @@ -164,9 +164,9 @@ tests = [ testGroup "block elements" ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in simpleTable headers rows =?> - unlines [ "header 1 || header 2" - , "Para 1.1 | Para 1.2" - , "Para 2.1 | Para 2.2" + unlines [ " header 1 || header 2" + , " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" ] , "table with header and caption" =: let caption = text "Table 1" @@ -174,10 +174,10 @@ tests = [ testGroup "block elements" rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] ,[para $ text "Para 2.1", para $ text "Para 2.2"]] in table caption mempty headers rows - =?> unlines [ "header 1 || header 2" - , "Para 1.1 | Para 1.2" - , "Para 2.1 | Para 2.2" - , "|+ Table 1 +|" + =?> unlines [ " header 1 || header 2" + , " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" + , " |+ Table 1 +|" ] ] -- Div is trivial diff --git a/test/tables.muse b/test/tables.muse index afdccd476..fdf20be49 100644 --- a/test/tables.muse +++ b/test/tables.muse @@ -1,46 +1,46 @@ Simple table with caption: -Right || Left || Center || Default -12 | 12 | 12 | 12 -123 | 123 | 123 | 123 -1 | 1 | 1 | 1 -|+ Demonstration of simple table syntax. +| + Right || Left || Center || Default + 12 | 12 | 12 | 12 + 123 | 123 | 123 | 123 + 1 | 1 | 1 | 1 + |+ Demonstration of simple table syntax. +| Simple table without caption: -Right || Left || Center || Default -12 | 12 | 12 | 12 -123 | 123 | 123 | 123 -1 | 1 | 1 | 1 + Right || Left || Center || Default + 12 | 12 | 12 | 12 + 123 | 123 | 123 | 123 + 1 | 1 | 1 | 1 Simple table indented two spaces: -Right || Left || Center || Default -12 | 12 | 12 | 12 -123 | 123 | 123 | 123 -1 | 1 | 1 | 1 -|+ Demonstration of simple table syntax. +| + Right || Left || Center || Default + 12 | 12 | 12 | 12 + 123 | 123 | 123 | 123 + 1 | 1 | 1 | 1 + |+ Demonstration of simple table syntax. +| Multiline table with caption: -Centered Header || Left Aligned || Right Aligned || Default aligned -First | row | 12.0 | Example of a row that spans multiple lines. -Second | row | 5.0 | Here’s another one. Note the blank line between rows. -|+ Here’s the caption. It may span multiple lines. +| + Centered Header || Left Aligned || Right Aligned || Default aligned + First | row | 12.0 | Example of a row that spans multiple lines. + Second | row | 5.0 | Here’s another one. Note the blank line between rows. + |+ Here’s the caption. It may span multiple lines. +| Multiline table without caption: -Centered Header || Left Aligned || Right Aligned || Default aligned -First | row | 12.0 | Example of a row that spans multiple lines. -Second | row | 5.0 | Here’s another one. Note the blank line between rows. + Centered Header || Left Aligned || Right Aligned || Default aligned + First | row | 12.0 | Example of a row that spans multiple lines. + Second | row | 5.0 | Here’s another one. Note the blank line between rows. Table without column headers: -12 | 12 | 12 | 12 -123 | 123 | 123 | 123 -1 | 1 | 1 | 1 + 12 | 12 | 12 | 12 + 123 | 123 | 123 | 123 + 1 | 1 | 1 | 1 Multiline table without column headers: -First | row | 12.0 | Example of a row that spans multiple lines. -Second | row | 5.0 | Here’s another one. Note the blank line between rows. + First | row | 12.0 | Example of a row that spans multiple lines. + Second | row | 5.0 | Here’s another one. Note the blank line between rows. -- cgit v1.2.3 From cff6d2dd73492d4c24ead814fc3564503f4d5b01 Mon Sep 17 00:00:00 2001 From: David A Roberts Date: Mon, 8 May 2017 07:11:57 +1000 Subject: Markdown writer: missing \n (#3647) --- src/Text/Pandoc/Writers/Markdown.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 7c0874278..e67dcef6c 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -788,7 +788,7 @@ blockListToMarkdown opts blocks = do isListBlock _ = False commentSep = if isEnabled Ext_raw_html opts then RawBlock "html" "\n" - else RawBlock "markdown" " " + else RawBlock "markdown" " \n" mapM (blockToMarkdown opts) (fixBlocks blocks) >>= return . cat getKey :: Doc -> Key -- cgit v1.2.3 From 4b9fb7a1280f1d923a6bcecbf42a496480020359 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Wed, 10 May 2017 23:35:45 +0200 Subject: Combine grid table parsers The grid table parsers for markdown and rst was combined into one single parser, slightly changing parsing behavior of both parsers: - The markdown parser now compactifies block content cell-wise: pure text blocks in cells are now treated as paragraphs only if the cell contains multiple paragraphs, and as plain blocks otherwise. Before, this was true only for single-column tables. - The rst parser now accepts newlines and multiple blocks in header cells. Closes: #3638 --- src/Text/Pandoc/Parsing.hs | 69 ++++++++++++++++++++++-------- src/Text/Pandoc/Readers/Markdown.hs | 84 +------------------------------------ test/command/3516.md | 4 +- test/markdown-reader-more.native | 68 +++++++++++++++--------------- test/tables-rstsubset.native | 12 +++--- 5 files changed, 94 insertions(+), 143 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e0c0e36d6..fa3ff898e 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -66,6 +66,7 @@ module Text.Pandoc.Parsing ( anyLine, tableWith, widthsFromIndices, gridTableWith, + gridTableWith', readWith, readWithM, testStringWith, @@ -770,6 +771,20 @@ tableWith :: (Stream s m Char, HasReaderOptions st, -> ParserT s st m end -> ParserT s st m (mf Blocks) tableWith headerParser rowParser lineParser footerParser = try $ do + (aligns, widths, heads, rows) <- tableWith' headerParser rowParser + lineParser footerParser + return $ B.table mempty (zip aligns widths) <$> heads <*> rows + +type TableComponents mf = ([Alignment], [Double], mf [Blocks], mf [[Blocks]]) + +tableWith' :: (Stream s m Char, HasReaderOptions st, + Functor mf, Applicative mf, Monad mf) + => ParserT s st m (mf [Blocks], [Alignment], [Int]) + -> ([Int] -> ParserT s st m (mf [Blocks])) + -> ParserT s st m sep + -> ParserT s st m end + -> ParserT s st m (TableComponents mf) +tableWith' headerParser rowParser lineParser footerParser = try $ do (heads, aligns, indices) <- headerParser lines' <- sequence <$> rowParser indices `sepEndBy1` lineParser footerParser @@ -777,7 +792,7 @@ tableWith headerParser rowParser lineParser footerParser = try $ do let widths = if (indices == []) then replicate (length aligns) 0.0 else widthsFromIndices numColumns indices - return $ B.table mempty (zip aligns widths) <$> heads <*> lines' + return $ (aligns, widths, heads, lines') -- Calculate relative widths of table columns, based on indices widthsFromIndices :: Int -- Number of columns on terminal @@ -812,24 +827,42 @@ widthsFromIndices numColumns' indices = -- ending with a footer (dashed line followed by blank line). gridTableWith :: (Stream [Char] m Char, HasReaderOptions st, Functor mf, Applicative mf, Monad mf) - => ParserT [Char] st m (mf Blocks) -- ^ Block list parser + => ParserT [Char] st m (mf Blocks) -- ^ Block list parser -> Bool -- ^ Headerless table -> ParserT [Char] st m (mf Blocks) gridTableWith blocks headless = tableWith (gridTableHeader headless blocks) (gridTableRow blocks) (gridTableSep '-') gridTableFooter +gridTableWith' :: (Stream [Char] m Char, HasReaderOptions st, + Functor mf, Applicative mf, Monad mf) + => ParserT [Char] st m (mf Blocks) -- ^ Block list parser + -> Bool -- ^ Headerless table + -> ParserT [Char] st m (TableComponents mf) +gridTableWith' blocks headless = + tableWith' (gridTableHeader headless blocks) (gridTableRow blocks) + (gridTableSep '-') gridTableFooter + gridTableSplitLine :: [Int] -> String -> [String] gridTableSplitLine indices line = map removeFinalBar $ tail $ splitStringByIndices (init indices) $ trimr line -gridPart :: Stream s m Char => Char -> ParserT s st m (Int, Int) +gridPart :: Stream s m Char => Char -> ParserT s st m ((Int, Int), Alignment) gridPart ch = do + leftColon <- option False (True <$ char ':') dashes <- many1 (char ch) + rightColon <- option False (True <$ char ':') char '+' - return (length dashes, length dashes + 1) - -gridDashedLines :: Stream s m Char => Char -> ParserT s st m [(Int,Int)] + let lengthDashes = length dashes + (if leftColon then 1 else 0) + + (if rightColon then 1 else 0) + let alignment = case (leftColon, rightColon) of + (True, True) -> AlignCenter + (True, False) -> AlignLeft + (False, True) -> AlignRight + (False, False) -> AlignDefault + return ((lengthDashes, lengthDashes + 1), alignment) + +gridDashedLines :: Stream s m Char => Char -> ParserT s st m [((Int, Int), Alignment)] gridDashedLines ch = try $ char '+' >> many1 (gridPart ch) <* blankline removeFinalBar :: String -> String @@ -853,18 +886,18 @@ gridTableHeader headless blocks = try $ do else many1 (notFollowedBy (gridTableSep '=') >> char '|' >> many1Till anyChar newline) - if headless - then return () - else gridTableSep '=' >> return () - let lines' = map snd dashes + underDashes <- if headless + then return dashes + else gridDashedLines '=' + guard $ length dashes == length underDashes + let lines' = map (snd . fst) underDashes let indices = scanl (+) 0 lines' - let aligns = replicate (length lines') AlignDefault - -- RST does not have a notion of alignments + let aligns = map snd underDashes let rawHeads = if headless - then replicate (length dashes) "" - else map (intercalate " ") $ transpose + then replicate (length underDashes) "" + else map (unlines . map trim) $ transpose $ map (gridTableSplitLine indices) rawContent - heads <- fmap sequence . mapM (parseFromString blocks) $ map trim rawHeads + heads <- fmap sequence $ mapM (parseFromString blocks . trim) rawHeads return (heads, aligns, indices) gridTableRawLine :: Stream s m Char => [Int] -> ParserT s st m [String] @@ -882,6 +915,9 @@ gridTableRow blocks indices = do colLines <- many1 (gridTableRawLine indices) let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $ transpose colLines + compactifyCell bs = case compactify [bs] of + [] -> mempty + x:_ -> x cells <- sequence <$> mapM (parseFromString blocks) cols return $ fmap (map compactifyCell) cells @@ -893,9 +929,6 @@ removeOneLeadingSpace xs = where startsWithSpace "" = True startsWithSpace (y:_) = y == ' ' -compactifyCell :: Blocks -> Blocks -compactifyCell bs = head $ compactify [bs] - -- | Parse footer for a grid table. gridTableFooter :: Stream s m Char => ParserT s st m [Char] gridTableFooter = blanklines diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 691d4d5cf..4ff5a1845 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1291,89 +1291,7 @@ multilineTableHeader headless = try $ do -- ending with a footer (dashed line followed by blank line). gridTable :: PandocMonad m => Bool -- ^ Headerless table -> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]]) -gridTable headless = - tableWith (gridTableHeader headless) gridTableRow - (gridTableSep '-') gridTableFooter - -gridTableSplitLine :: [Int] -> String -> [String] -gridTableSplitLine indices line = map removeFinalBar $ tail $ - splitStringByIndices (init indices) $ trimr line - -gridPart :: PandocMonad m => Char -> ParserT [Char] st m ((Int, Int), Alignment) -gridPart ch = do - leftColon <- option False (True <$ char ':') - dashes <- many1 (char ch) - rightColon <- option False (True <$ char ':') - char '+' - let lengthDashes = length dashes + (if leftColon then 1 else 0) + - (if rightColon then 1 else 0) - let alignment = case (leftColon, rightColon) of - (True, True) -> AlignCenter - (True, False) -> AlignLeft - (False, True) -> AlignRight - (False, False) -> AlignDefault - return ((lengthDashes, lengthDashes + 1), alignment) - -gridDashedLines :: PandocMonad m => Char -> ParserT [Char] st m [((Int, Int), Alignment)] -gridDashedLines ch = try $ char '+' >> many1 (gridPart ch) <* blankline - -removeFinalBar :: String -> String -removeFinalBar = - reverse . dropWhile (`elem` " \t") . dropWhile (=='|') . reverse - --- | Separator between rows of grid table. -gridTableSep :: PandocMonad m => Char -> MarkdownParser m Char -gridTableSep ch = try $ gridDashedLines ch >> return '\n' - --- | Parse header for a grid table. -gridTableHeader :: PandocMonad m => Bool -- ^ Headerless table - -> MarkdownParser m (F [Blocks], [Alignment], [Int]) -gridTableHeader headless = try $ do - optional blanklines - dashes <- gridDashedLines '-' - rawContent <- if headless - then return [] - else many1 (try (char '|' >> anyLine)) - underDashes <- if headless - then return dashes - else gridDashedLines '=' - guard $ length dashes == length underDashes - let lines' = map (snd . fst) underDashes - let indices = scanl (+) 0 lines' - let aligns = map snd underDashes - let rawHeads = if headless - then replicate (length underDashes) "" - else map (unlines . map trim) $ transpose - $ map (gridTableSplitLine indices) rawContent - heads <- fmap sequence $ mapM (parseFromString parseBlocks . trim) rawHeads - return (heads, aligns, indices) - -gridTableRawLine :: PandocMonad m => [Int] -> MarkdownParser m [String] -gridTableRawLine indices = do - char '|' - line <- anyLine - return (gridTableSplitLine indices line) - --- | Parse row of grid table. -gridTableRow :: PandocMonad m => [Int] - -> MarkdownParser m (F [Blocks]) -gridTableRow indices = do - colLines <- many1 (gridTableRawLine indices) - let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $ - transpose colLines - fmap compactify <$> fmap sequence (mapM (parseFromString parseBlocks) cols) - -removeOneLeadingSpace :: [String] -> [String] -removeOneLeadingSpace xs = - if all startsWithSpace xs - then map (drop 1) xs - else xs - where startsWithSpace "" = True - startsWithSpace (y:_) = y == ' ' - --- | Parse footer for a grid table. -gridTableFooter :: PandocMonad m => MarkdownParser m [Char] -gridTableFooter = blanklines +gridTable headless = gridTableWith' parseBlocks headless pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int]) pipeBreak = try $ do diff --git a/test/command/3516.md b/test/command/3516.md index 982043874..8c7e478d3 100644 --- a/test/command/3516.md +++ b/test/command/3516.md @@ -27,8 +27,8 @@ on Windows builds. [Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2] [[] ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]]] + [[[Plain [Str "1"]] + ,[Plain [Str "2"]]] ,[[] ,[]]]] ``` diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native index baafb5334..1007dbac7 100644 --- a/test/markdown-reader-more.native +++ b/test/markdown-reader-more.native @@ -99,74 +99,74 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S [[Plain [Str "col",Space,Str "1"]] ,[Plain [Str "col",Space,Str "2"]] ,[Plain [Str "col",Space,Str "3"]]] - [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Para [Str "r2",Space,Str "d"]] - ,[Para [Str "e"]] - ,[Para [Str "f"]]]] + [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,[[Plain [Str "r2",Space,Str "d"]] + ,[Plain [Str "e"]] + ,[Plain [Str "f"]]]] ,Para [Str "Headless"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[] ,[] ,[]] - [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Para [Str "r2",Space,Str "d"]] - ,[Para [Str "e"]] - ,[Para [Str "f"]]]] + [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,[[Plain [Str "r2",Space,Str "d"]] + ,[Plain [Str "e"]] + ,[Plain [Str "f"]]]] ,Para [Str "With",Space,Str "alignments"] ,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[Plain [Str "col",Space,Str "1"]] ,[Plain [Str "col",Space,Str "2"]] ,[Plain [Str "col",Space,Str "3"]]] - [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Para [Str "r2",Space,Str "d"]] - ,[Para [Str "e"]] - ,[Para [Str "f"]]]] + [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,[[Plain [Str "r2",Space,Str "d"]] + ,[Plain [Str "e"]] + ,[Plain [Str "f"]]]] ,Para [Str "Headless",Space,Str "with",Space,Str "alignments"] ,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[] ,[] ,[]] - [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Para [Str "r2",Space,Str "d"]] - ,[Para [Str "e"]] - ,[Para [Str "f"]]]] + [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,[[Plain [Str "r2",Space,Str "d"]] + ,[Plain [Str "e"]] + ,[Plain [Str "f"]]]] ,Para [Str "Spaces",Space,Str "at",Space,Str "ends",Space,Str "of",Space,Str "lines"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[] ,[] ,[]] - [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Para [Str "r2",Space,Str "d"]] - ,[Para [Str "e"]] - ,[Para [Str "f"]]]] + [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,[[Plain [Str "r2",Space,Str "d"]] + ,[Plain [Str "e"]] + ,[Plain [Str "f"]]]] ,Para [Str "Multiple",Space,Str "blocks",Space,Str "in",Space,Str "a",Space,Str "cell"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[] ,[] ,[]] [[[Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"] - ,Para [Str "col",Space,Str "1"]] + ,Plain [Str "col",Space,Str "1"]] ,[Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"] - ,Para [Str "col",Space,Str "2"]] + ,Plain [Str "col",Space,Str "2"]] ,[Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"] - ,Para [Str "col",Space,Str "3"]]] + ,Plain [Str "col",Space,Str "3"]]] ,[[Para [Str "r1",Space,Str "a"] ,Para [Str "r1",Space,Str "bis"]] ,[BulletList [[Plain [Str "b"]] ,[Plain [Str "b",Space,Str "2"]] ,[Plain [Str "b",Space,Str "2"]]]] - ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] + ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] ,Para [Str "Empty",Space,Str "cells"] ,Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2] [[] diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native index d9bb9f2fb..8b7ccdf76 100644 --- a/test/tables-rstsubset.native +++ b/test/tables-rstsubset.native @@ -54,9 +54,9 @@ ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] ,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] - [[Plain [Str "Centered",Space,Str "Header"]] - ,[Plain [Str "Left",Space,Str "Aligned"]] - ,[Plain [Str "Right",Space,Str "Aligned"]] + [[Plain [Str "Centered",SoftBreak,Str "Header"]] + ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] ,[Plain [Str "Default",Space,Str "aligned"]]] [[[Plain [Str "First"]] ,[Plain [Str "row"]] @@ -68,9 +68,9 @@ ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] - [[Plain [Str "Centered",Space,Str "Header"]] - ,[Plain [Str "Left",Space,Str "Aligned"]] - ,[Plain [Str "Right",Space,Str "Aligned"]] + [[Plain [Str "Centered",SoftBreak,Str "Header"]] + ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] ,[Plain [Str "Default",Space,Str "aligned"]]] [[[Plain [Str "First"]] ,[Plain [Str "row"]] -- cgit v1.2.3 From 2a291e437a18073e0005447245809833ce46ae5c Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Fri, 12 May 2017 11:55:45 +0300 Subject: Replace `repeat' and `take' with `replicate' once more --- src/Text/Pandoc/Readers/Org/Blocks.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 89c076869..788ec26dc 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -442,7 +442,7 @@ rawBlockContent blockType = try $ do tabsToSpaces tabLen cs'@(c:cs) = case c of ' ' -> ' ':tabsToSpaces tabLen cs - '\t' -> (take tabLen $ repeat ' ') ++ tabsToSpaces tabLen cs + '\t' -> replicate tabLen ' ' ++ tabsToSpaces tabLen cs _ -> cs' commaEscaped :: String -> String -- cgit v1.2.3 From 62d34c79b9b00cc37ea395f70abd2c25eccf4cf8 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 13 May 2017 22:14:29 +0200 Subject: Change maintainer line in Org writer module --- src/Text/Pandoc/Writers/Org.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index fc6608450..46752c7ce 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -24,7 +24,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Copyright : Copyright (C) 2010-2015 Puneeth Chaganti and John MacFarlane License : GNU GPL, version 2 or above - Maintainer : Puneeth Chaganti + Maintainer : Albert Krewinkel Stability : alpha Portability : portable -- cgit v1.2.3 From 1cbb3bad2b9d7c609959186668e3edbd496bea0b Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 13 May 2017 22:18:12 +0200 Subject: Add haddock module description to FB2 writer Copyright, maintainer etc. were missing in haddock docs for this module. --- src/Text/Pandoc/Writers/FB2.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index fb232e278..b8806a261 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -19,7 +19,17 @@ along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} -{- | Conversion of 'Pandoc' documents to FB2 (FictionBook2) format. +{- | +Module : Text.Pandoc.Writers.FB2 +Copyright : Copyright (C) 2011-2012 Sergey Astanin + 2012-2017 John MacFarlane +License : GNU GPL, version 2 or above + +Maintainer : John MacFarlane +Stability : alpha +Portability : portable + +Conversion of 'Pandoc' documents to FB2 (FictionBook2) format. FictionBook is an XML-based e-book format. For more information see: -- cgit v1.2.3 From 965f1ddd4a9d1317455094b8c41016624d92f8ce Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 13 May 2017 23:30:13 +0200 Subject: Update dates in copyright notices This follows the suggestions given by the FSF for GPL licensed software. --- COPYRIGHT | 11 ++++++----- MANUAL.txt | 2 +- README.md | 2 +- src/Text/Pandoc.hs | 4 ++-- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Asciify.hs | 4 ++-- src/Text/Pandoc/Error.hs | 4 ++-- src/Text/Pandoc/Highlighting.hs | 4 ++-- src/Text/Pandoc/ImageSize.hs | 4 ++-- src/Text/Pandoc/Logging.hs | 2 +- src/Text/Pandoc/Lua/SharedInstances.hs | 2 +- src/Text/Pandoc/Lua/StackInstances.hs | 4 ++-- src/Text/Pandoc/Lua/Util.hs | 2 +- src/Text/Pandoc/MIME.hs | 4 ++-- src/Text/Pandoc/MediaBag.hs | 4 ++-- src/Text/Pandoc/Options.hs | 4 ++-- src/Text/Pandoc/PDF.hs | 4 ++-- src/Text/Pandoc/Parsing.hs | 4 ++-- src/Text/Pandoc/Pretty.hs | 4 ++-- src/Text/Pandoc/Process.hs | 4 ++-- src/Text/Pandoc/Readers/Docx.hs | 4 ++-- src/Text/Pandoc/Readers/Docx/Lists.hs | 4 ++-- src/Text/Pandoc/Readers/Docx/Parse.hs | 4 ++-- src/Text/Pandoc/Readers/HTML.hs | 4 ++-- src/Text/Pandoc/Readers/LaTeX.hs | 4 ++-- src/Text/Pandoc/Readers/Markdown.hs | 4 ++-- src/Text/Pandoc/Readers/MediaWiki.hs | 4 ++-- src/Text/Pandoc/Readers/Native.hs | 4 ++-- src/Text/Pandoc/Readers/Org.hs | 4 ++-- src/Text/Pandoc/Readers/Org/BlockStarts.hs | 4 ++-- src/Text/Pandoc/Readers/Org/ExportSettings.hs | 2 +- src/Text/Pandoc/Readers/Org/Inlines.hs | 4 ++-- src/Text/Pandoc/Readers/Org/ParserState.hs | 4 ++-- src/Text/Pandoc/Readers/Org/Parsing.hs | 4 ++-- src/Text/Pandoc/Readers/Org/Shared.hs | 4 ++-- src/Text/Pandoc/Readers/RST.hs | 4 ++-- src/Text/Pandoc/Readers/Textile.hs | 7 ++++--- src/Text/Pandoc/SelfContained.hs | 4 ++-- src/Text/Pandoc/Shared.hs | 4 ++-- src/Text/Pandoc/Slides.hs | 4 ++-- src/Text/Pandoc/Templates.hs | 4 ++-- src/Text/Pandoc/UTF8.hs | 4 ++-- src/Text/Pandoc/UUID.hs | 4 ++-- src/Text/Pandoc/Writers.hs | 4 ++-- src/Text/Pandoc/Writers/AsciiDoc.hs | 4 ++-- src/Text/Pandoc/Writers/ConTeXt.hs | 4 ++-- src/Text/Pandoc/Writers/Custom.hs | 4 ++-- src/Text/Pandoc/Writers/Docbook.hs | 4 ++-- src/Text/Pandoc/Writers/Docx.hs | 4 ++-- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- src/Text/Pandoc/Writers/EPUB.hs | 4 ++-- src/Text/Pandoc/Writers/FB2.hs | 4 ++-- src/Text/Pandoc/Writers/HTML.hs | 4 ++-- src/Text/Pandoc/Writers/Haddock.hs | 4 ++-- src/Text/Pandoc/Writers/ICML.hs | 2 +- src/Text/Pandoc/Writers/JATS.hs | 2 +- src/Text/Pandoc/Writers/LaTeX.hs | 4 ++-- src/Text/Pandoc/Writers/Man.hs | 4 ++-- src/Text/Pandoc/Writers/Markdown.hs | 4 ++-- src/Text/Pandoc/Writers/MediaWiki.hs | 4 ++-- src/Text/Pandoc/Writers/Ms.hs | 4 ++-- src/Text/Pandoc/Writers/Native.hs | 4 ++-- src/Text/Pandoc/Writers/ODT.hs | 4 ++-- src/Text/Pandoc/Writers/OPML.hs | 4 ++-- src/Text/Pandoc/Writers/OpenDocument.hs | 4 ++-- src/Text/Pandoc/Writers/Org.hs | 8 +++++--- src/Text/Pandoc/Writers/RST.hs | 4 ++-- src/Text/Pandoc/Writers/RTF.hs | 4 ++-- src/Text/Pandoc/Writers/Shared.hs | 4 ++-- src/Text/Pandoc/Writers/TEI.hs | 4 ++-- src/Text/Pandoc/Writers/Texinfo.hs | 6 ++++-- src/Text/Pandoc/Writers/Textile.hs | 4 ++-- src/Text/Pandoc/Writers/ZimWiki.hs | 5 +++-- src/Text/Pandoc/XML.hs | 4 ++-- 74 files changed, 152 insertions(+), 145 deletions(-) (limited to 'src/Text') diff --git a/COPYRIGHT b/COPYRIGHT index 9d6a78da5..73fae62af 100644 --- a/COPYRIGHT +++ b/COPYRIGHT @@ -33,32 +33,33 @@ licenses. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/Texinfo.hs -Copyright (C) 2008-2015 John MacFarlane and Peter Wang +Copyright (C) 2008-2017 John MacFarlane and Peter Wang Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/OpenDocument.hs -Copyright (C) 2008-2015 Andrea Rossato and John MacFarlane +Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/Org.hs -Copyright (C) 2010-2015 Puneeth Chaganti and John MacFarlane +Copyright (C) 2010-2017 Puneeth Chaganti, John MacFarlane, and + Albert Krewinkel Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Readers/Textile.hs -Copyright (C) 2010-2015 Paul Rivier and John MacFarlane +Copyright (C) 2010-2017 Paul Rivier and John MacFarlane Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Readers/Org.hs test/Tests/Readers/Org.hs -Copyright (C) 2014-2015 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel Released under the GNU General Public License version 2 or later. diff --git a/MANUAL.txt b/MANUAL.txt index 032ab5972..fad4683d4 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -4148,7 +4148,7 @@ which you can modify according to your needs, do Authors ======= -© 2006-2016 John MacFarlane (jgm@berkeley.edu). Released under the +© 2006-2017 John MacFarlane (jgm@berkeley.edu). Released under the [GPL], version 2 or greater. This software carries no warranty of any kind. (See COPYRIGHT for full copyright and warranty notices.) diff --git a/README.md b/README.md index 590bddb5b..ebd5ba2e8 100644 --- a/README.md +++ b/README.md @@ -140,7 +140,7 @@ new issue. License ------- -© 2006-2016 John MacFarlane (jgm@berkeley.edu). Released under the +© 2006-2017 John MacFarlane (jgm@berkeley.edu). Released under the [GPL], version 2 or greater. This software carries no warranty of any kind. (See COPYRIGHT for full copyright and warranty notices.) diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 345ef3b18..8ee1adf13 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -2,7 +2,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index f340259f3..157100507 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.App - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs index 411a112b2..7125e5bcd 100644 --- a/src/Text/Pandoc/Asciify.hs +++ b/src/Text/Pandoc/Asciify.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2016 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Asciify - Copyright : Copyright (C) 2013-2016 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 9b3f1b902..077413056 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Error - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index f249f96ad..183155d5b 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2016 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Highlighting - Copyright : Copyright (C) 2008-2016 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 8b2d577a9..a0800e499 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} {- - Copyright (C) 2011-2016 John MacFarlane + Copyright (C) 2011-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ {- | Module : Text.Pandoc.ImageSize -Copyright : Copyright (C) 2011-2016 John MacFarlane +Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 59b010034..2cca4b7d3 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Logging - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Lua/SharedInstances.hs b/src/Text/Pandoc/Lua/SharedInstances.hs index 3d2d29ebf..019a82446 100644 --- a/src/Text/Pandoc/Lua/SharedInstances.hs +++ b/src/Text/Pandoc/Lua/SharedInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index 03f6e06e2..cfc4389c2 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2015 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.StackInstances - Copyright : © 2012-2016 John MacFarlane + Copyright : © 2012-2017 John MacFarlane © 2017 Albert Krewinkel License : GNU GPL, version 2 or above diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index f0b87c231..ff07ba7d7 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 2e4a97b71..162112634 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2011-2016 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.MIME - Copyright : Copyright (C) 2011-2016 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs index b865f97c2..980511acc 100644 --- a/src/Text/Pandoc/MediaBag.hs +++ b/src/Text/Pandoc/MediaBag.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- -Copyright (C) 2014 John MacFarlane +Copyright (C) 2014-2015, 2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.MediaBag - Copyright : Copyright (C) 2014 John MacFarlane + Copyright : Copyright (C) 2014-2015, 2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 0b09f0497..6757c6782 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Options - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 7097337e2..cc9b38f7f 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.PDF - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index fa3ff898e..e90f64c5b 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -7,7 +7,7 @@ , IncoherentInstances #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -26,7 +26,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Parsing - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 32e60843c..a432949c8 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA {- | Module : Text.Pandoc.Pretty - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs index 1014f37dd..b2a0c17f1 100644 --- a/src/Text/Pandoc/Process.hs +++ b/src/Text/Pandoc/Process.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2016 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Process - Copyright : Copyright (C) 2013-2016 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 683277993..2757314ab 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -3,7 +3,7 @@ {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Docx - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs index 94b4d919a..8be2e1894 100644 --- a/src/Text/Pandoc/Readers/Docx/Lists.hs +++ b/src/Text/Pandoc/Readers/Docx/Lists.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Docx.Lists - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 0f23555f4..e6736100f 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Docx.Parse - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 14b051539..650454ae6 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1,7 +1,7 @@ {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ViewPatterns#-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.HTML - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b13fc215b..9a887c40c 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.LaTeX - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 4ff5a1845..0c0d07140 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Markdown - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index b35f39aad..c860a0cdf 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -3,7 +3,7 @@ {-# LANGUAGE TypeSynonymInstances #-} -- RelaxedPolyRec needed for inlinesBetween on GHC < 7 {- - Copyright (C) 2012-2015 John MacFarlane + Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.MediaWiki - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 2e307fa4f..8f42a45de 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2011-2015 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Native - Copyright : Copyright (C) 2011-2015 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 5e509178d..2b29bcfda 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index f05725f16..066bde9e0 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs index 1d6fdd7e1..934191e71 100644 --- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs +++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 5772e4157..800264db0 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index e47565814..f530d1d03 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -2,7 +2,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index aa3a08279..50f5ebae5 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index f89ce6732..95424319f 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 628351f36..868bfafa4 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.RST - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 047aa061c..df057837f 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -1,6 +1,6 @@ {- -Copyright (C) 2010-2015 Paul Rivier | tr '*#' '.@' - and John MacFarlane +Copyright (C) 2010-2012 Paul Rivier | tr '*#' '.@' + 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Textile - Copyright : Copyright (C) 2010-2015 Paul Rivier and John MacFarlane + Copyright : Copyright (C) 2010-2012 Paul Rivier + 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : Paul Rivier diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 6391ef0e0..c0a12adf2 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2011-2016 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.SelfContained - Copyright : Copyright (C) 2011-2016 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 0ebaf0f89..3a61656e5 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -2,7 +2,7 @@ FlexibleContexts, ScopedTypeVariables, PatternGuards, ViewPatterns #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Shared - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs index b53e0eb6d..cd7695dbe 100644 --- a/src/Text/Pandoc/Slides.hs +++ b/src/Text/Pandoc/Slides.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Slides - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 26aeb9a73..9b635a97b 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -3,7 +3,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeSynonymInstances #-} {- -Copyright (C) 2009-2016 John MacFarlane +Copyright (C) 2009-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Templates - Copyright : Copyright (C) 2009-2016 John MacFarlane + Copyright : Copyright (C) 2009-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index d88a44948..e27a24e63 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.UTF8 - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs index 9446c4692..989dd20c6 100644 --- a/src/Text/Pandoc/UUID.hs +++ b/src/Text/Pandoc/UUID.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.UUID - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index 0181f41c9..62445c072 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 20fa7c209..e0085fb1a 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.AsciiDoc - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 57f920259..eef16d3da 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.ConTeXt - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index ce90e4834..b33acb17c 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -6,7 +6,7 @@ #else {-# LANGUAGE OverlappingInstances #-} #endif -{- Copyright (C) 2012-2015 John MacFarlane +{- Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -25,7 +25,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Custom - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index dce2cbd3e..1afdfc457 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docbook - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 620f9060e..b58c983a1 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -4,7 +4,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2012-2015 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -23,7 +23,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docx - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 5e29acbaf..81987dc44 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.DokuWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : Clare Macrae diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 5b64564ce..c8d64cf0b 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -3,7 +3,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.EPUB - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index b8806a261..0926cc331 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -1,8 +1,8 @@ {-# LANGUAGE PatternGuards #-} {- -Copyright (c) 2011-2012, Sergey Astanin -All rights reserved. +Copyright (c) 2011-2012 Sergey Astanin + 2012-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 9f41f77d1..63e839684 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.HTML - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index eae1377cd..812b46c30 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2014 John MacFarlane +Copyright (C) 2014-2015, 2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Haddock - Copyright : Copyright (C) 2014 John MacFarlane + Copyright : Copyright (C) 2014-2015,2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 4d9998665..2f7a4889f 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -4,7 +4,7 @@ {- | Module : Text.Pandoc.Writers.ICML - Copyright : Copyright (C) 2013-2016 github.com/mb21 + Copyright : Copyright (C) 2013-2017 github.com/mb21 License : GNU GPL, version 2 or above Stability : alpha diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index aca7dc969..0b5108a79 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 000f4f8fb..26508b7c3 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -2,7 +2,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.LaTeX - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 1f3e17c16..f3d356de7 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Man - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index e67dcef6c..37bb98f5f 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Markdown - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index def245e38..439bbb2f9 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.MediaWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 534f26a5a..5dd225e19 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Ms - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index b031a0231..653efb3ce 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Native - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 6c6f38dbe..68e68c659 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.ODT - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index 98510c40f..cdb6ab0d1 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} {- -Copyright (C) 2013-2015 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.OPML - Copyright : Copyright (C) 2013-2015 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 491069343..53c1d0c59 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2008-2015 Andrea Rossato +Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane. This program is free software; you can redistribute it and/or modify @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.OpenDocument - Copyright : Copyright (C) 2008-2015 Andrea Rossato and John MacFarlane + Copyright : Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane License : GNU GPL, version 2 or above Maintainer : Andrea Rossato diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 46752c7ce..ef60e2f6c 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -1,8 +1,8 @@ {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2010-2015 Puneeth Chaganti - Albert Krewinkel , - and John MacFarlane + 2010-2017 John MacFarlane + 2016-2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Org - Copyright : Copyright (C) 2010-2015 Puneeth Chaganti and John MacFarlane + Copyright : © 2010-2015 Puneeth Chaganti + 2010-2017 John MacFarlane + 2016-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 24898d62e..d16f013c0 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.RST - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 7aa2280dd..e9b29f97d 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.RTF - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 615733a78..c33655522 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2013-2015 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Shared - Copyright : Copyright (C) 2013-2015 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 0e1a0526d..7da792c9e 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docbook - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index da4f43ee5..9926daea1 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2008-2015 John MacFarlane and Peter Wang +Copyright (C) 2008-2017 John MacFarlane + 2012 Peter Wang This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +20,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Texinfo - Copyright : Copyright (C) 2008-2015 John MacFarlane and Peter Wang + Copyright : Copyright (C) 2008-2017 John MacFarlane + 2012 Peter Wang License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 0ecb746c3..d532f3ed3 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Textile - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index da8b08de1..bc2cf8f3c 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -1,5 +1,6 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane + 2017 Alex Ivkin This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.ZimWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane, 2017 Alex Ivkin + Copyright : Copyright (C) 2008-2017 John MacFarlane, 2017 Alex Ivkin License : GNU GPL, version 2 or above Maintainer : Alex Ivkin diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index d7fdc4278..b6edd6be5 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.XML - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane -- cgit v1.2.3 From 7a17c3eb9f5b7037764e9dfad854cc7d59b47abc Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sun, 14 May 2017 09:28:08 +0200 Subject: Parsing: replace partial with total function Calling `tail` on an empty list raises an exception, while calling the otherwise equivalent `drop 1` will return the empty list again. --- src/Text/Pandoc/Parsing.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e90f64c5b..e4113f31f 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -1380,5 +1380,5 @@ insertIncludedFile blocks dirs f = do bs <- blocks setInput oldInput setPosition oldPos - updateState $ \s -> s{ stateContainers = tail $ stateContainers s } + updateState $ \s -> s{ stateContainers = drop 1 $ stateContainers s } return bs -- cgit v1.2.3 From 5ff6108b4cd18ad2efdf34a79f576b2b09969123 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sun, 14 May 2017 10:00:58 +0200 Subject: Parsing: introduce `HasIncludeFiles` type class The `insertIncludeFile` function is generalized to work with all parser states which are instances of that class. --- src/Text/Pandoc/Parsing.hs | 31 ++++++++++++++++++++++--------- 1 file changed, 22 insertions(+), 9 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e4113f31f..a6a1a83dd 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -83,6 +83,7 @@ module Text.Pandoc.Parsing ( anyLine, HasMacros (..), HasLogMessages (..), HasLastStrPosition (..), + HasIncludeFiles (..), defaultParserState, HeaderType (..), ParserContext (..), @@ -1008,6 +1009,9 @@ class HasReaderOptions st where -- default getOption f = (f . extractReaderOptions) <$> getState +instance HasReaderOptions ParserState where + extractReaderOptions = stateOptions + class HasQuoteContext st m where getQuoteContext :: (Stream s m t) => ParsecT s st m QuoteContext withQuoteContext :: QuoteContext -> ParsecT s st m a -> ParsecT s st m a @@ -1023,9 +1027,6 @@ instance Monad m => HasQuoteContext ParserState m where setState newState { stateQuoteContext = oldQuoteContext } return result -instance HasReaderOptions ParserState where - extractReaderOptions = stateOptions - class HasHeaderMap st where extractHeaderMap :: st -> M.Map Inlines String updateHeaderMap :: (M.Map Inlines String -> M.Map Inlines String) -> @@ -1067,6 +1068,16 @@ instance HasLogMessages ParserState where addLogMessage msg st = st{ stateLogMessages = msg : stateLogMessages st } getLogMessages st = reverse $ stateLogMessages st +class HasIncludeFiles st where + getIncludeFiles :: st -> [String] + addIncludeFile :: String -> st -> st + dropLatestIncludeFile :: st -> st + +instance HasIncludeFiles ParserState where + getIncludeFiles = stateContainers + addIncludeFile f s = s{ stateContainers = f : stateContainers s } + dropLatestIncludeFile s = s { stateContainers = drop 1 $ stateContainers s } + defaultParserState :: ParserState defaultParserState = ParserState { stateOptions = def, @@ -1358,17 +1369,19 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs') Nothing -> cls kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs -insertIncludedFile :: PandocMonad m - => ParserT String ParserState m Blocks +-- | Parse content of include file as blocks. Circular includes result in an +-- @PandocParseError@. +insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) + => ParserT String st m Blocks -> [FilePath] -> FilePath - -> ParserT String ParserState m Blocks + -> ParserT String st m Blocks insertIncludedFile blocks dirs f = do oldPos <- getPosition oldInput <- getInput - containers <- stateContainers <$> getState + containers <- getIncludeFiles <$> getState when (f `elem` containers) $ throwError $ PandocParseError $ "Include file loop at " ++ show oldPos - updateState $ \s -> s{ stateContainers = f : stateContainers s } + updateState $ addIncludeFile f mbcontents <- readFileFromDirs dirs f contents <- case mbcontents of Just s -> return s @@ -1380,5 +1393,5 @@ insertIncludedFile blocks dirs f = do bs <- blocks setInput oldInput setPosition oldPos - updateState $ \s -> s{ stateContainers = drop 1 $ stateContainers s } + updateState dropLatestIncludeFile return bs -- cgit v1.2.3 From 9d295f4527f894493c61c5e8129b9f8616a7e2b4 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sun, 14 May 2017 12:40:16 +0200 Subject: Parsing: add `insertIncludedFilesF` which returns F blocks The `insertIncludeFiles` function was generalized and renamed to `insertIncludedFiles'`; the specialized versions are based on that. --- src/Text/Pandoc/Parsing.hs | 31 ++++++++++++++++++++++++------- 1 file changed, 24 insertions(+), 7 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index a6a1a83dd..bde13f07e 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -121,6 +121,7 @@ module Text.Pandoc.Parsing ( anyLine, (<+?>), extractIdClass, insertIncludedFile, + insertIncludedFileF, -- * Re-exports from Text.Pandoc.Parsec Stream, runParser, @@ -1369,13 +1370,12 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs') Nothing -> cls kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs --- | Parse content of include file as blocks. Circular includes result in an --- @PandocParseError@. -insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) - => ParserT String st m Blocks - -> [FilePath] -> FilePath - -> ParserT String st m Blocks -insertIncludedFile blocks dirs f = do +insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st, + Functor mf, Applicative mf, Monad mf) + => ParserT String st m (mf Blocks) + -> [FilePath] -> FilePath + -> ParserT String st m (mf Blocks) +insertIncludedFile' blocks dirs f = do oldPos <- getPosition oldInput <- getInput containers <- getIncludeFiles <$> getState @@ -1395,3 +1395,20 @@ insertIncludedFile blocks dirs f = do setPosition oldPos updateState dropLatestIncludeFile return bs + +-- | Parse content of include file as blocks. Circular includes result in an +-- @PandocParseError@. +insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) + => ParserT String st m Blocks + -> [FilePath] -> FilePath + -> ParserT String st m Blocks +insertIncludedFile blocks dirs f = + runIdentity <$> insertIncludedFile' (Identity <$> blocks) dirs f + +-- | Parse content of include file as future blocks. Circular includes result in +-- an @PandocParseError@. +insertIncludedFileF :: (PandocMonad m, HasIncludeFiles st) + => ParserT String st m (Future st Blocks) + -> [FilePath] -> FilePath + -> ParserT String st m (Future st Blocks) +insertIncludedFileF = insertIncludedFile' -- cgit v1.2.3 From af4bf91c5925b5c6a7431cef8a7997c16d4c7b2b Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sun, 14 May 2017 12:45:31 +0200 Subject: Org reader: add basic file inclusion mechanism Support for the `#+INCLUDE:` file inclusion mechanism was added. Recognized include types are *example*, *export*, *src*, and normal org file inclusion. Advanced features like line numbers and level selection are not implemented yet. Closes: #3510 --- pandoc.cabal | 3 +++ src/Text/Pandoc/Readers/Org/Blocks.hs | 36 ++++++++++++++++++++++++++---- src/Text/Pandoc/Readers/Org/ParserState.hs | 11 ++++++++- src/Text/Pandoc/Readers/Org/Parsing.hs | 1 + test/command/3510-export.latex | 1 + test/command/3510-src.hs | 1 + test/command/3510-subdoc.org | 5 +++++ test/command/3510.md | 20 +++++++++++++++++ 8 files changed, 73 insertions(+), 5 deletions(-) create mode 100644 test/command/3510-export.latex create mode 100644 test/command/3510-src.hs create mode 100644 test/command/3510-subdoc.org create mode 100644 test/command/3510.md (limited to 'src/Text') diff --git a/pandoc.cabal b/pandoc.cabal index a713e9372..bdee857b0 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -138,6 +138,9 @@ Extra-Source-Files: test/command/abbrevs test/command/sub-file-chapter-1.tex test/command/sub-file-chapter-2.tex + test/command/3510-subdoc.org + test/command/3510-export.latex + test/command/3510-src.hs test/docbook-reader.docbook test/docbook-xref.docbook test/html-reader.html diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 788ec26dc..e77a64efe 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE ViewPatterns #-} {- Copyright (C) 2014-2017 Albert Krewinkel @@ -18,7 +15,9 @@ You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} - +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Readers.Org.Options Copyright : Copyright (C) 2014-2017 Albert Krewinkel @@ -274,6 +273,7 @@ block = choice [ mempty <$ blanklines , figure , example , genericDrawer + , include , specialLine , horizontalRule , list @@ -717,6 +717,34 @@ exampleCode = B.codeBlockWith ("", ["example"], []) specialLine :: PandocMonad m => OrgParser m (F Blocks) specialLine = fmap return . try $ rawExportLine <|> metaLine <|> commentLine +-- | Include the content of a file. +include :: PandocMonad m => OrgParser m (F Blocks) +include = try $ do + metaLineStart <* stringAnyCase "include:" <* skipSpaces + filename <- includeTarget + blockType <- optionMaybe $ skipSpaces *> many1 alphaNum + blocksParser <- case blockType of + Just "example" -> do + return $ pure . B.codeBlock <$> parseRaw + Just "export" -> do + format <- skipSpaces *> many (noneOf "\n\r\t ") + return $ pure . B.rawBlock format <$> parseRaw + Just "src" -> do + language <- skipSpaces *> many (noneOf "\n\r\t ") + let attr = (mempty, [language], mempty) + return $ pure . B.codeBlockWith attr <$> parseRaw + _ -> return $ pure . B.fromList <$> blockList + anyLine + insertIncludedFileF blocksParser ["."] filename + where + includeTarget :: PandocMonad m => OrgParser m FilePath + includeTarget = do + char '"' + manyTill (noneOf "\n\r\t") (char '"') + + parseRaw :: PandocMonad m => OrgParser m String + parseRaw = many anyChar + rawExportLine :: PandocMonad m => OrgParser m Blocks rawExportLine = try $ do metaLineStart diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index f530d1d03..51666fc64 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -66,7 +66,8 @@ import Text.Pandoc.Logging import Text.Pandoc.Parsing (HasHeaderMap (..), HasIdentifierList (..), HasLogMessages (..), HasLastStrPosition (..), HasQuoteContext (..), - HasReaderOptions (..), ParserContext (..), + HasReaderOptions (..), HasIncludeFiles (..), + ParserContext (..), QuoteContext (..), SourcePos, Future, askF, asksF, returnF, runF, trimInlinesF) @@ -106,6 +107,7 @@ data OrgParserState = OrgParserState , orgStateExportSettings :: ExportSettings , orgStateHeaderMap :: M.Map Inlines String , orgStateIdentifiers :: Set.Set String + , orgStateIncludeFiles :: [String] , orgStateLastForbiddenCharPos :: Maybe SourcePos , orgStateLastPreCharPos :: Maybe SourcePos , orgStateLastStrPos :: Maybe SourcePos @@ -148,6 +150,12 @@ instance HasLogMessages OrgParserState where addLogMessage msg st = st{ orgLogMessages = msg : orgLogMessages st } getLogMessages st = reverse $ orgLogMessages st +instance HasIncludeFiles OrgParserState where + getIncludeFiles = orgStateIncludeFiles + addIncludeFile f st = st { orgStateIncludeFiles = f : orgStateIncludeFiles st } + dropLatestIncludeFile st = + st { orgStateIncludeFiles = drop 1 $ orgStateIncludeFiles st } + instance Default OrgParserState where def = defaultOrgParserState @@ -159,6 +167,7 @@ defaultOrgParserState = OrgParserState , orgStateExportSettings = def , orgStateHeaderMap = M.empty , orgStateIdentifiers = Set.empty + , orgStateIncludeFiles = [] , orgStateLastForbiddenCharPos = Nothing , orgStateLastPreCharPos = Nothing , orgStateLastStrPos = Nothing diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 50f5ebae5..c25b215df 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -71,6 +71,7 @@ module Text.Pandoc.Readers.Org.Parsing , ellipses , citeKey , gridTableWith + , insertIncludedFileF -- * Re-exports from Text.Pandoc.Parsec , runParser , runParserT diff --git a/test/command/3510-export.latex b/test/command/3510-export.latex new file mode 100644 index 000000000..6d8636322 --- /dev/null +++ b/test/command/3510-export.latex @@ -0,0 +1 @@ +\emph{Hello} \ No newline at end of file diff --git a/test/command/3510-src.hs b/test/command/3510-src.hs new file mode 100644 index 000000000..ad5744b80 --- /dev/null +++ b/test/command/3510-src.hs @@ -0,0 +1 @@ +putStrLn outString diff --git a/test/command/3510-subdoc.org b/test/command/3510-subdoc.org new file mode 100644 index 000000000..5bcc6678a --- /dev/null +++ b/test/command/3510-subdoc.org @@ -0,0 +1,5 @@ +* Subsection + +Included text + +Lorem ipsum. diff --git a/test/command/3510.md b/test/command/3510.md new file mode 100644 index 000000000..7993db848 --- /dev/null +++ b/test/command/3510.md @@ -0,0 +1,20 @@ +See +``` +% pandoc -f org -t native +Text + +#+include: "command/3510-subdoc.org" + +#+INCLUDE: "command/3510-src.hs" src haskell +#+INCLUDE: "command/3510-export.latex" export latex + +More text +^D +[Para [Str "Text"] +,Header 1 ("subsection",[],[]) [Str "Subsection"] +,Para [Str "Included",Space,Str "text"] +,Plain [Str "Lorem",Space,Str "ipsum."] +,CodeBlock ("",["haskell"],[]) "putStrLn outString\n" +,RawBlock (Format "latex") "\\emph{Hello}" +,Para [Str "More",Space,Str "text"]] +``` -- cgit v1.2.3 From 2de5208311472d4fe951acf69d36156a6465dfc1 Mon Sep 17 00:00:00 2001 From: Henri Werth Date: Mon, 15 May 2017 16:37:08 +0200 Subject: Added support for horizontal spacing in LaTeX: parse \, to \8198 (six-per-em space) --- src/Text/Pandoc/Readers/LaTeX.hs | 2 +- test/latex-reader.native | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b13fc215b..279cdd138 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -590,7 +590,7 @@ inlineCommands = M.fromList $ , ("u", option (str "u") $ try $ tok >>= accent breve) , ("i", lit "i") , ("\\", linebreak <$ (optional (bracketed inline) *> spaces')) - , (",", pure mempty) + , (",", lit "\8198") , ("@", pure mempty) , (" ", lit "\160") , ("ps", pure $ str "PS." <> space) diff --git a/test/latex-reader.native b/test/latex-reader.native index f37f1b2ca..d481a714d 100644 --- a/test/latex-reader.native +++ b/test/latex-reader.native @@ -249,10 +249,10 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",SoftBreak,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a",Math InlineMath "\\sim",Str "b",SoftBreak,Str "c",Math InlineMath "\\sim",Str "d."] ,HorizontalRule ,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"] -,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]] +,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Str "\8198",Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]] ,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."] ,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]] -,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"] +,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."],Str "\8198"],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",SoftBreak,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."] ,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two\8212three\8212four\8212five."] ,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."] -- cgit v1.2.3 From 37189667cc2bc86d308ad771318528bd77876912 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 15 May 2017 20:36:11 +0200 Subject: Textile reader: fix bug for certain links in table cells. Closes #3667. --- src/Text/Pandoc/Readers/Textile.hs | 7 +++++-- test/command/3667.md | 13 +++++++++++++ 2 files changed, 18 insertions(+), 2 deletions(-) create mode 100644 test/command/3667.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index df057837f..abf8be452 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -586,8 +586,9 @@ link = try $ do char ':' let stop = if bracketed then char ']' - else lookAhead $ space <|> - try (oneOf "!.,;:" *> (space <|> newline)) + else lookAhead $ space <|> eof' <|> + try (oneOf "!.,;:" *> + (space <|> newline <|> eof')) url <- many1Till nonspaceChar stop let name' = if B.toList name == [Str "$"] then B.str url else name return $ if attr == nullAttr @@ -728,3 +729,5 @@ groupedInlineMarkup = try $ do singleton :: a -> [a] singleton x = [x] +eof' :: Monad m => ParserT [Char] s m Char +eof' = '\n' <$ eof diff --git a/test/command/3667.md b/test/command/3667.md new file mode 100644 index 000000000..97de8f598 --- /dev/null +++ b/test/command/3667.md @@ -0,0 +1,13 @@ +``` +% pandoc -f textile +| "link text":http://example.com/ | +^D + + + + + + +
link text
+``` + -- cgit v1.2.3 From a27e2e8a4e6b4f8a28fe540511f48afccc503ef6 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 16 May 2017 22:42:34 +0200 Subject: Org reader: put tree parsing code into dedicated module --- pandoc.cabal | 1 + src/Text/Pandoc/Readers/Org/Blocks.hs | 212 +---------------------- src/Text/Pandoc/Readers/Org/DocumentTree.hs | 260 ++++++++++++++++++++++++++++ 3 files changed, 263 insertions(+), 210 deletions(-) create mode 100644 src/Text/Pandoc/Readers/Org/DocumentTree.hs (limited to 'src/Text') diff --git a/pandoc.cabal b/pandoc.cabal index bdee857b0..61ef5c522 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -445,6 +445,7 @@ Library Text.Pandoc.Readers.Odt.Arrows.Utils, Text.Pandoc.Readers.Org.BlockStarts, Text.Pandoc.Readers.Org.Blocks, + Text.Pandoc.Readers.Org.DocumentTree, Text.Pandoc.Readers.Org.ExportSettings, Text.Pandoc.Readers.Org.Inlines, Text.Pandoc.Readers.Org.Meta, diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index e77a64efe..acede0c77 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Readers.Org.Blocks ) where import Text.Pandoc.Readers.Org.BlockStarts +import Text.Pandoc.Readers.Org.DocumentTree (headline, headlineToBlocks) import Text.Pandoc.Readers.Org.Inlines import Text.Pandoc.Readers.Org.Meta (metaExport, metaKey, metaLine) import Text.Pandoc.Readers.Org.ParserState @@ -54,196 +55,6 @@ import Data.List (foldl', isPrefixOf) import Data.Maybe (fromMaybe, isNothing) import Data.Monoid ((<>)) --- --- Org headers --- -newtype Tag = Tag { fromTag :: String } - deriving (Show, Eq) - --- | Create a tag containing the given string. -toTag :: String -> Tag -toTag = Tag - --- | The key (also called name or type) of a property. -newtype PropertyKey = PropertyKey { fromKey :: String } - deriving (Show, Eq, Ord) - --- | Create a property key containing the given string. Org mode keys are --- case insensitive and are hence converted to lower case. -toPropertyKey :: String -> PropertyKey -toPropertyKey = PropertyKey . map toLower - --- | The value assigned to a property. -newtype PropertyValue = PropertyValue { fromValue :: String } - --- | Create a property value containing the given string. -toPropertyValue :: String -> PropertyValue -toPropertyValue = PropertyValue - --- | Check whether the property value is non-nil (i.e. truish). -isNonNil :: PropertyValue -> Bool -isNonNil p = map toLower (fromValue p) `notElem` ["()", "{}", "nil"] - --- | Key/value pairs from a PROPERTIES drawer -type Properties = [(PropertyKey, PropertyValue)] - --- | Org mode headline (i.e. a document subtree). -data Headline = Headline - { headlineLevel :: Int - , headlineTodoMarker :: Maybe TodoMarker - , headlineText :: Inlines - , headlineTags :: [Tag] - , headlineProperties :: Properties - , headlineContents :: Blocks - , headlineChildren :: [Headline] - } - --- --- Parsing headlines and subtrees --- - --- | Read an Org mode headline and its contents (i.e. a document subtree). --- @lvl@ gives the minimum acceptable level of the tree. -headline :: PandocMonad m => Int -> OrgParser m (F Headline) -headline lvl = try $ do - level <- headerStart - guard (lvl <= level) - todoKw <- optionMaybe todoKeyword - title <- trimInlinesF . mconcat <$> manyTill inline endOfTitle - tags <- option [] headerTags - newline - properties <- option mempty propertiesDrawer - contents <- blocks - children <- many (headline (level + 1)) - return $ do - title' <- title - contents' <- contents - children' <- sequence children - return $ Headline - { headlineLevel = level - , headlineTodoMarker = todoKw - , headlineText = title' - , headlineTags = tags - , headlineProperties = properties - , headlineContents = contents' - , headlineChildren = children' - } - where - endOfTitle :: Monad m => OrgParser m () - endOfTitle = void . lookAhead $ optional headerTags *> newline - - headerTags :: Monad m => OrgParser m [Tag] - headerTags = try $ - let tag = many1 (alphaNum <|> oneOf "@%#_") <* char ':' - in map toTag <$> (skipSpaces *> char ':' *> many1 tag <* skipSpaces) - --- | Convert an Org mode headline (i.e. a document tree) into pandoc's Blocks -headlineToBlocks :: Monad m => Headline -> OrgParser m Blocks -headlineToBlocks hdln@(Headline {..}) = do - maxHeadlineLevels <- getExportSetting exportHeadlineLevels - case () of - _ | any isNoExportTag headlineTags -> return mempty - _ | any isArchiveTag headlineTags -> archivedHeadlineToBlocks hdln - _ | isCommentTitle headlineText -> return mempty - _ | headlineLevel >= maxHeadlineLevels -> headlineToHeaderWithList hdln - _ | otherwise -> headlineToHeaderWithContents hdln - -isNoExportTag :: Tag -> Bool -isNoExportTag = (== toTag "noexport") - -isArchiveTag :: Tag -> Bool -isArchiveTag = (== toTag "ARCHIVE") - --- | Check if the title starts with COMMENT. --- FIXME: This accesses builder internals not intended for use in situations --- like these. Replace once keyword parsing is supported. -isCommentTitle :: Inlines -> Bool -isCommentTitle (B.toList -> (Str "COMMENT":_)) = True -isCommentTitle _ = False - -archivedHeadlineToBlocks :: Monad m => Headline -> OrgParser m Blocks -archivedHeadlineToBlocks hdln = do - archivedTreesOption <- getExportSetting exportArchivedTrees - case archivedTreesOption of - ArchivedTreesNoExport -> return mempty - ArchivedTreesExport -> headlineToHeaderWithContents hdln - ArchivedTreesHeadlineOnly -> headlineToHeader hdln - -headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks -headlineToHeaderWithList hdln@(Headline {..}) = do - maxHeadlineLevels <- getExportSetting exportHeadlineLevels - header <- headlineToHeader hdln - listElements <- sequence (map headlineToBlocks headlineChildren) - let listBlock = if null listElements - then mempty - else B.orderedList listElements - let headerText = if maxHeadlineLevels == headlineLevel - then header - else flattenHeader header - return $ headerText <> headlineContents <> listBlock - where - flattenHeader :: Blocks -> Blocks - flattenHeader blks = - case B.toList blks of - (Header _ _ inlns:_) -> B.para (B.fromList inlns) - _ -> mempty - -headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks -headlineToHeaderWithContents hdln@(Headline {..}) = do - header <- headlineToHeader hdln - childrenBlocks <- mconcat <$> sequence (map headlineToBlocks headlineChildren) - return $ header <> headlineContents <> childrenBlocks - -headlineToHeader :: Monad m => Headline -> OrgParser m Blocks -headlineToHeader (Headline {..}) = do - exportTodoKeyword <- getExportSetting exportWithTodoKeywords - let todoText = if exportTodoKeyword - then case headlineTodoMarker of - Just kw -> todoKeywordToInlines kw <> B.space - Nothing -> mempty - else mempty - let text = tagTitle (todoText <> headlineText) headlineTags - let propAttr = propertiesToAttr headlineProperties - attr <- registerHeader propAttr headlineText - return $ B.headerWith attr headlineLevel text - -todoKeyword :: Monad m => OrgParser m TodoMarker -todoKeyword = try $ do - taskStates <- activeTodoMarkers <$> getState - let kwParser tdm = try $ (tdm <$ string (todoMarkerName tdm) <* spaceChar) - choice (map kwParser taskStates) - -todoKeywordToInlines :: TodoMarker -> Inlines -todoKeywordToInlines tdm = - let todoText = todoMarkerName tdm - todoState = map toLower . show $ todoMarkerState tdm - classes = [todoState, todoText] - in B.spanWith (mempty, classes, mempty) (B.str todoText) - -propertiesToAttr :: Properties -> Attr -propertiesToAttr properties = - let - toStringPair prop = (fromKey (fst prop), fromValue (snd prop)) - customIdKey = toPropertyKey "custom_id" - classKey = toPropertyKey "class" - unnumberedKey = toPropertyKey "unnumbered" - specialProperties = [customIdKey, classKey, unnumberedKey] - id' = fromMaybe mempty . fmap fromValue . lookup customIdKey $ properties - cls = fromMaybe mempty . fmap fromValue . lookup classKey $ properties - kvs' = map toStringPair . filter ((`notElem` specialProperties) . fst) - $ properties - isUnnumbered = - fromMaybe False . fmap isNonNil . lookup unnumberedKey $ properties - in - (id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs') - -tagTitle :: Inlines -> [Tag] -> Inlines -tagTitle title tags = title <> (mconcat $ map tagToInline tags) - -tagToInline :: Tag -> Inlines -tagToInline t = B.spanWith ("", ["tag"], [("data-tag-name", fromTag t)]) mempty - - -- -- parsing blocks -- @@ -252,7 +63,7 @@ tagToInline t = B.spanWith ("", ["tag"], [("data-tag-name", fromTag t)]) mempty blockList :: PandocMonad m => OrgParser m [Block] blockList = do initialBlocks <- blocks - headlines <- sequence <$> manyTill (headline 1) eof + headlines <- sequence <$> manyTill (headline blocks inline 1) eof st <- getState headlineBlocks <- fmap mconcat . sequence . map headlineToBlocks $ runF headlines st return . B.toList $ (runF initialBlocks st) <> headlineBlocks @@ -631,25 +442,6 @@ drawerEnd :: Monad m => OrgParser m String drawerEnd = try $ skipSpaces *> stringAnyCase ":END:" <* skipSpaces <* newline --- | Read a :PROPERTIES: drawer and return the key/value pairs contained --- within. -propertiesDrawer :: Monad m => OrgParser m Properties -propertiesDrawer = try $ do - drawerType <- drawerStart - guard $ map toUpper drawerType == "PROPERTIES" - manyTill property (try drawerEnd) - where - property :: Monad m => OrgParser m (PropertyKey, PropertyValue) - property = try $ (,) <$> key <*> value - - key :: Monad m => OrgParser m PropertyKey - key = fmap toPropertyKey . try $ - skipSpaces *> char ':' *> many1Till nonspaceChar (char ':') - - value :: Monad m => OrgParser m PropertyValue - value = fmap toPropertyValue . try $ - skipSpaces *> manyTill anyChar (try $ skipSpaces *> newline) - -- -- Figures diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs new file mode 100644 index 000000000..3e2a046d4 --- /dev/null +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -0,0 +1,260 @@ +{- +Copyright (C) 2014-2017 Albert Krewinkel + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ViewPatterns #-} +{- | + Module : Text.Pandoc.Readers.Org.DocumentTree + Copyright : Copyright (C) 2014-2017 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel + +Parsers for org-mode headlines and document subtrees +-} +module Text.Pandoc.Readers.Org.DocumentTree + ( headline + , headlineToBlocks + ) where + +import Control.Monad (guard, void) +import Data.Char (toLower, toUpper) +import Data.Maybe (fromMaybe) +import Data.Monoid ((<>)) +import Text.Pandoc.Builder (Blocks, Inlines) +import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Definition +import Text.Pandoc.Readers.Org.BlockStarts +import Text.Pandoc.Readers.Org.Parsing +import Text.Pandoc.Readers.Org.ParserState + +import qualified Text.Pandoc.Builder as B + +-- +-- Org headers +-- +newtype Tag = Tag { fromTag :: String } + deriving (Show, Eq) + +-- | Create a tag containing the given string. +toTag :: String -> Tag +toTag = Tag + +-- | The key (also called name or type) of a property. +newtype PropertyKey = PropertyKey { fromKey :: String } + deriving (Show, Eq, Ord) + +-- | Create a property key containing the given string. Org mode keys are +-- case insensitive and are hence converted to lower case. +toPropertyKey :: String -> PropertyKey +toPropertyKey = PropertyKey . map toLower + +-- | The value assigned to a property. +newtype PropertyValue = PropertyValue { fromValue :: String } + +-- | Create a property value containing the given string. +toPropertyValue :: String -> PropertyValue +toPropertyValue = PropertyValue + +-- | Check whether the property value is non-nil (i.e. truish). +isNonNil :: PropertyValue -> Bool +isNonNil p = map toLower (fromValue p) `notElem` ["()", "{}", "nil"] + +-- | Key/value pairs from a PROPERTIES drawer +type Properties = [(PropertyKey, PropertyValue)] + +-- | Org mode headline (i.e. a document subtree). +data Headline = Headline + { headlineLevel :: Int + , headlineTodoMarker :: Maybe TodoMarker + , headlineText :: Inlines + , headlineTags :: [Tag] + , headlineProperties :: Properties + , headlineContents :: Blocks + , headlineChildren :: [Headline] + } + +-- | Read an Org mode headline and its contents (i.e. a document subtree). +-- @lvl@ gives the minimum acceptable level of the tree. +headline :: PandocMonad m + => OrgParser m (F Blocks) + -> OrgParser m (F Inlines) + -> Int + -> OrgParser m (F Headline) +headline blocks inline lvl = try $ do + level <- headerStart + guard (lvl <= level) + todoKw <- optionMaybe todoKeyword + title <- trimInlinesF . mconcat <$> manyTill inline endOfTitle + tags <- option [] headerTags + newline + properties <- option mempty propertiesDrawer + contents <- blocks + children <- many (headline blocks inline (level + 1)) + return $ do + title' <- title + contents' <- contents + children' <- sequence children + return $ Headline + { headlineLevel = level + , headlineTodoMarker = todoKw + , headlineText = title' + , headlineTags = tags + , headlineProperties = properties + , headlineContents = contents' + , headlineChildren = children' + } + where + endOfTitle :: Monad m => OrgParser m () + endOfTitle = void . lookAhead $ optional headerTags *> newline + + headerTags :: Monad m => OrgParser m [Tag] + headerTags = try $ + let tag = many1 (alphaNum <|> oneOf "@%#_") <* char ':' + in map toTag <$> (skipSpaces *> char ':' *> many1 tag <* skipSpaces) + +-- | Convert an Org mode headline (i.e. a document tree) into pandoc's Blocks +headlineToBlocks :: Monad m => Headline -> OrgParser m Blocks +headlineToBlocks hdln@(Headline {..}) = do + maxHeadlineLevels <- getExportSetting exportHeadlineLevels + case () of + _ | any isNoExportTag headlineTags -> return mempty + _ | any isArchiveTag headlineTags -> archivedHeadlineToBlocks hdln + _ | isCommentTitle headlineText -> return mempty + _ | headlineLevel >= maxHeadlineLevels -> headlineToHeaderWithList hdln + _ | otherwise -> headlineToHeaderWithContents hdln + +isNoExportTag :: Tag -> Bool +isNoExportTag = (== toTag "noexport") + +isArchiveTag :: Tag -> Bool +isArchiveTag = (== toTag "ARCHIVE") + +-- | Check if the title starts with COMMENT. +-- FIXME: This accesses builder internals not intended for use in situations +-- like these. Replace once keyword parsing is supported. +isCommentTitle :: Inlines -> Bool +isCommentTitle (B.toList -> (Str "COMMENT":_)) = True +isCommentTitle _ = False + +archivedHeadlineToBlocks :: Monad m => Headline -> OrgParser m Blocks +archivedHeadlineToBlocks hdln = do + archivedTreesOption <- getExportSetting exportArchivedTrees + case archivedTreesOption of + ArchivedTreesNoExport -> return mempty + ArchivedTreesExport -> headlineToHeaderWithContents hdln + ArchivedTreesHeadlineOnly -> headlineToHeader hdln + +headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks +headlineToHeaderWithList hdln@(Headline {..}) = do + maxHeadlineLevels <- getExportSetting exportHeadlineLevels + header <- headlineToHeader hdln + listElements <- sequence (map headlineToBlocks headlineChildren) + let listBlock = if null listElements + then mempty + else B.orderedList listElements + let headerText = if maxHeadlineLevels == headlineLevel + then header + else flattenHeader header + return $ headerText <> headlineContents <> listBlock + where + flattenHeader :: Blocks -> Blocks + flattenHeader blks = + case B.toList blks of + (Header _ _ inlns:_) -> B.para (B.fromList inlns) + _ -> mempty + +headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks +headlineToHeaderWithContents hdln@(Headline {..}) = do + header <- headlineToHeader hdln + childrenBlocks <- mconcat <$> sequence (map headlineToBlocks headlineChildren) + return $ header <> headlineContents <> childrenBlocks + +headlineToHeader :: Monad m => Headline -> OrgParser m Blocks +headlineToHeader (Headline {..}) = do + exportTodoKeyword <- getExportSetting exportWithTodoKeywords + let todoText = if exportTodoKeyword + then case headlineTodoMarker of + Just kw -> todoKeywordToInlines kw <> B.space + Nothing -> mempty + else mempty + let text = tagTitle (todoText <> headlineText) headlineTags + let propAttr = propertiesToAttr headlineProperties + attr <- registerHeader propAttr headlineText + return $ B.headerWith attr headlineLevel text + +todoKeyword :: Monad m => OrgParser m TodoMarker +todoKeyword = try $ do + taskStates <- activeTodoMarkers <$> getState + let kwParser tdm = try $ (tdm <$ string (todoMarkerName tdm) <* spaceChar) + choice (map kwParser taskStates) + +todoKeywordToInlines :: TodoMarker -> Inlines +todoKeywordToInlines tdm = + let todoText = todoMarkerName tdm + todoState = map toLower . show $ todoMarkerState tdm + classes = [todoState, todoText] + in B.spanWith (mempty, classes, mempty) (B.str todoText) + +propertiesToAttr :: Properties -> Attr +propertiesToAttr properties = + let + toStringPair prop = (fromKey (fst prop), fromValue (snd prop)) + customIdKey = toPropertyKey "custom_id" + classKey = toPropertyKey "class" + unnumberedKey = toPropertyKey "unnumbered" + specialProperties = [customIdKey, classKey, unnumberedKey] + id' = fromMaybe mempty . fmap fromValue . lookup customIdKey $ properties + cls = fromMaybe mempty . fmap fromValue . lookup classKey $ properties + kvs' = map toStringPair . filter ((`notElem` specialProperties) . fst) + $ properties + isUnnumbered = + fromMaybe False . fmap isNonNil . lookup unnumberedKey $ properties + in + (id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs') + +tagTitle :: Inlines -> [Tag] -> Inlines +tagTitle title tags = title <> (mconcat $ map tagToInline tags) + +-- | Convert +tagToInline :: Tag -> Inlines +tagToInline t = B.spanWith ("", ["tag"], [("data-tag-name", fromTag t)]) mempty + +-- | Read a :PROPERTIES: drawer and return the key/value pairs contained +-- within. +propertiesDrawer :: Monad m => OrgParser m Properties +propertiesDrawer = try $ do + drawerType <- drawerStart + guard $ map toUpper drawerType == "PROPERTIES" + manyTill property (try endOfDrawer) + where + property :: Monad m => OrgParser m (PropertyKey, PropertyValue) + property = try $ (,) <$> key <*> value + + key :: Monad m => OrgParser m PropertyKey + key = fmap toPropertyKey . try $ + skipSpaces *> char ':' *> many1Till nonspaceChar (char ':') + + value :: Monad m => OrgParser m PropertyValue + value = fmap toPropertyValue . try $ + skipSpaces *> manyTill anyChar (try $ skipSpaces *> newline) + + endOfDrawer :: Monad m => OrgParser m String + endOfDrawer = try $ + skipSpaces *> stringAnyCase ":END:" <* skipSpaces <* newline + -- cgit v1.2.3 From 602cd6a327ad41e68e47689d3842f349cf33444d Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 16 May 2017 22:49:52 +0200 Subject: Org reader: replace `sequence . map` with `mapM` --- src/Text/Pandoc/Readers/Org/Blocks.hs | 2 +- src/Text/Pandoc/Readers/Org/DocumentTree.hs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index acede0c77..8c78e5157 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -65,7 +65,7 @@ blockList = do initialBlocks <- blocks headlines <- sequence <$> manyTill (headline blocks inline 1) eof st <- getState - headlineBlocks <- fmap mconcat . sequence . map headlineToBlocks $ runF headlines st + headlineBlocks <- fmap mconcat . mapM headlineToBlocks $ runF headlines st return . B.toList $ (runF initialBlocks st) <> headlineBlocks -- | Get the meta information saved in the state. diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index 3e2a046d4..53ec2ef57 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -164,7 +164,7 @@ headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks headlineToHeaderWithList hdln@(Headline {..}) = do maxHeadlineLevels <- getExportSetting exportHeadlineLevels header <- headlineToHeader hdln - listElements <- sequence (map headlineToBlocks headlineChildren) + listElements <- mapM headlineToBlocks headlineChildren let listBlock = if null listElements then mempty else B.orderedList listElements @@ -182,7 +182,7 @@ headlineToHeaderWithList hdln@(Headline {..}) = do headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks headlineToHeaderWithContents hdln@(Headline {..}) = do header <- headlineToHeader hdln - childrenBlocks <- mconcat <$> sequence (map headlineToBlocks headlineChildren) + childrenBlocks <- mconcat <$> mapM headlineToBlocks headlineChildren return $ header <> headlineContents <> childrenBlocks headlineToHeader :: Monad m => Headline -> OrgParser m Blocks -- cgit v1.2.3 From e74bd06cc8b05c0820601cb764ddb679fc9fca77 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 17 May 2017 02:12:24 +0300 Subject: Txt2Tags parser: newline is not indentation space parses '\n', while spaceChar parses only ' ' and '\t' --- src/Text/Pandoc/Readers/Txt2Tags.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 33f785109..012ab7cb1 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -281,7 +281,7 @@ anyLineNewline :: T2T String anyLineNewline = (++ "\n") <$> anyLine indentWith :: Int -> T2T String -indentWith n = count n space +indentWith n = count n spaceChar -- Table -- cgit v1.2.3 From 55ce47d050fd6e1a38db765c7632e1989d60854d Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Wed, 17 May 2017 01:52:48 +0300 Subject: Move anyLineNewline to Parsing.hs --- src/Text/Pandoc/Parsing.hs | 5 +++++ src/Text/Pandoc/Readers/Markdown.hs | 2 +- src/Text/Pandoc/Readers/Org/Blocks.hs | 4 ---- src/Text/Pandoc/Readers/Org/Parsing.hs | 1 + src/Text/Pandoc/Readers/Txt2Tags.hs | 3 --- 5 files changed, 7 insertions(+), 8 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e90f64c5b..766d0fd49 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -36,6 +36,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA A utility library with parsers used in pandoc readers. -} module Text.Pandoc.Parsing ( anyLine, + anyLineNewline, many1Till, notFollowedBy', oneOfStrings, @@ -253,6 +254,10 @@ anyLine = do return this _ -> mzero +-- | Parse any line, include the final newline in the output +anyLineNewline :: Stream [Char] m Char => ParserT [Char] st m [Char] +anyLineNewline = (++ "\n") <$> anyLine + -- | Like @manyTill@, but reads at least one item. many1Till :: Stream s m t => ParserT s st m a diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 0c0d07140..7434ef1f6 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -614,7 +614,7 @@ hrule = try $ do -- indentedLine :: PandocMonad m => MarkdownParser m String -indentedLine = indentSpaces >> anyLine >>= return . (++ "\n") +indentedLine = indentSpaces >> anyLineNewline blockDelimiter :: PandocMonad m => (Char -> Bool) diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 788ec26dc..f0740ede4 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -1017,7 +1017,3 @@ listContinuation markerLength = try $ then count num (char ' ') else choice [ try (count num (char ' ')) , try (char '\t' >> count (num - tabStop) (char ' ')) ] - --- | Parse any line, include the final newline in the output. -anyLineNewline :: Monad m => OrgParser m String -anyLineNewline = (++ "\n") <$> anyLine diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 50f5ebae5..c62718346 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -31,6 +31,7 @@ functions are adapted to Org-mode specific functionality. module Text.Pandoc.Readers.Org.Parsing ( OrgParser , anyLine + , anyLineNewline , blanklines , newline , parseFromString diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 33f785109..d8b6c016c 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -277,9 +277,6 @@ listContinuation markerLength = try $ <*> many blankline) where listLine = try $ indentWith markerLength *> anyLineNewline -anyLineNewline :: T2T String -anyLineNewline = (++ "\n") <$> anyLine - indentWith :: Int -> T2T String indentWith n = count n space -- cgit v1.2.3 From 7b3aaee15ab69cdf3125a214c2124b91622af759 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 17 May 2017 16:23:33 +0200 Subject: Markdown writer: Fixed duplicated reference links with `--reference-links` and `--reference-location=section`. Also ensure that there are no empty link references `[]`. Closes #3674. --- src/Text/Pandoc/Writers/Markdown.hs | 26 +++++++++++++++----------- test/command/3674.md | 26 ++++++++++++++++++++++++++ 2 files changed, 41 insertions(+), 11 deletions(-) create mode 100644 test/command/3674.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 37bb98f5f..b70716181 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -91,6 +91,7 @@ instance Default WriterEnv data WriterState = WriterState { stNotes :: Notes , stRefs :: Refs + , stKeys :: Set.Set Key , stIds :: Set.Set String , stNoteNum :: Int } @@ -98,6 +99,7 @@ data WriterState = WriterState { stNotes :: Notes instance Default WriterState where def = WriterState{ stNotes = [] , stRefs = [] + , stKeys = Set.empty , stIds = Set.empty , stNoteNum = 1 } @@ -798,19 +800,21 @@ getKey = toKey . render Nothing -- Prefer label if possible; otherwise, generate a unique key. getReference :: PandocMonad m => Attr -> Doc -> Target -> MD m Doc getReference attr label target = do - st <- get - let keys = map (\(l,_,_) -> getKey l) (stRefs st) - case find (\(_,t,a) -> t == target && a == attr) (stRefs st) of + refs <- gets stRefs + case find (\(_,t,a) -> t == target && a == attr) refs of Just (ref, _, _) -> return ref Nothing -> do - label' <- case getKey label `elem` keys of - True -> -- label is used; generate numerical label - case find (\n -> Key n `notElem` keys) $ - map show [1..(10000 :: Integer)] of - Just x -> return $ text x - Nothing -> throwError $ PandocSomeError "no unique label" - False -> return label - modify (\s -> s{ stRefs = (label', target, attr) : stRefs st }) + keys <- gets stKeys + label' <- if isEmpty label || getKey label `Set.member` keys + then case find (\n -> not (Key n `Set.member` keys)) $ + map show [1..(10000 :: Integer)] of + Just x -> return $ text x + Nothing -> + throwError $ PandocSomeError "no unique label" + else return label + modify (\s -> s{ stRefs = (label', target, attr) : stRefs s, + stKeys = Set.insert (getKey label') (stKeys s) + }) return label' -- | Convert list of Pandoc inline elements to markdown. diff --git a/test/command/3674.md b/test/command/3674.md new file mode 100644 index 000000000..09f4e0d1e --- /dev/null +++ b/test/command/3674.md @@ -0,0 +1,26 @@ +Make sure we don't get duplicate reference links, even with +`--reference-location=section`. + +``` +% pandoc --reference-links -t markdown --reference-location=section --atx-headers +# a + +![](a) + +# b + +![](b) + +^D +# a + +![][1] + + [1]: a + +# b + +![][2] + + [2]: b +``` -- cgit v1.2.3 From 6b8240fc2f45ced4f16403316cab76df15ceaf7a Mon Sep 17 00:00:00 2001 From: Stefan Dresselhaus Date: Wed, 17 May 2017 15:13:35 +0200 Subject: Add `--eol` flag and writer option to control line endings. * Add `--eol=crlf|lf` CLI option. * Add `optEol` to `WriterOptions` [API change] * In `Text.Pandoc.UTF8`, add new functions parameterized on `Newline`: `writeFileWith`, `putStrWith`, `putStrLnWith`, `hPutStrWith`, `hPutStrLnWith`. [API change] * Document option in MANUAL.txt. Closes #3663. Closes #2097. --- MANUAL.txt | 7 +++++++ src/Text/Pandoc/App.hs | 26 +++++++++++++++++++++----- src/Text/Pandoc/UTF8.hs | 41 +++++++++++++++++++++++++++++++++-------- 3 files changed, 61 insertions(+), 13 deletions(-) (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index f41d96ffa..d99cd0600 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -593,7 +593,14 @@ General writer options : Print a system default data file. Files in the user data directory are ignored. +`--eol=crlf`|`lf` + +: Manually specify line endings: `crlf` (Windows) or `lf` + (MacOS/linux/unix). The default is to use the line endings + appropriate for the OS. + `--dpi`=*NUMBER* + : Specify the dpi (dots per inch) value for conversion from pixels to inch/centimeters and vice versa. The default is 96dpi. Technically, the correct term would be ppi (pixels per inch). diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 157100507..9c8e1bde4 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -65,7 +65,7 @@ import System.Directory (Permissions (..), doesFileExist, findExecutable, import System.Environment (getArgs, getEnvironment, getProgName) import System.Exit (ExitCode (..), exitSuccess) import System.FilePath -import System.IO (stdout) +import System.IO (stdout, nativeNewline, Newline(..)) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) @@ -411,6 +411,8 @@ convertWithOpts opts = do return $ ("csl", jatsEncoded) : optMetadata opts else return $ optMetadata opts + let eol = fromMaybe nativeNewline $ optEol opts + runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) @@ -463,7 +465,7 @@ convertWithOpts opts = do else id output <- f writerOptions doc selfcontain (output ++ ['\n' | not standalone]) >>= - writerFn outputFile . handleEntities + writerFn eol outputFile . handleEntities type Transform = Pandoc -> Pandoc @@ -567,6 +569,7 @@ data Opt = Opt , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header + , optEol :: Maybe Newline -- ^ Enforce line-endings } -- | Defaults for command-line options. @@ -635,6 +638,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] + , optEol = Nothing } addMetadata :: (String, String) -> Pandoc -> Pandoc @@ -783,9 +787,9 @@ writeFnBinary :: MonadIO m => FilePath -> B.ByteString -> m () writeFnBinary "-" = liftIO . B.putStr writeFnBinary f = liftIO . B.writeFile (UTF8.encodePath f) -writerFn :: MonadIO m => FilePath -> String -> m () -writerFn "-" = liftIO . UTF8.putStr -writerFn f = liftIO . UTF8.writeFile f +writerFn :: MonadIO m => Newline -> FilePath -> String -> m () +writerFn eol "-" = liftIO . UTF8.putStrWith eol +writerFn eol f = liftIO . UTF8.writeFileWith eol f lookupHighlightStyle :: Maybe String -> IO (Maybe Style) lookupHighlightStyle Nothing = return Nothing @@ -958,6 +962,18 @@ options = "NUMBER") "" -- "Dpi (default 96)" + , Option "" ["eol"] + (ReqArg + (\arg opt -> + case toLower <$> arg of + "crlf" -> return opt { optEol = Just CRLF } + "lf" -> return opt { optEol = Just LF } + -- mac-syntax (cr) is not supported in ghc-base. + _ -> E.throwIO $ PandocOptionError + "--eol must be one of crlf (Windows), lf (Unix)") + "crlf|lf") + "" -- "EOL (default OS-dependent)" + , Option "" ["wrap"] (ReqArg (\arg opt -> diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index e27a24e63..84043d4cb 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -28,11 +28,16 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA UTF-8 aware string IO functions that will work with GHC 6.10, 6.12, or 7. -} module Text.Pandoc.UTF8 ( readFile - , writeFile , getContents + , writeFileWith + , writeFile + , putStrWith , putStr + , putStrLnWith , putStrLn + , hPutStrWith , hPutStr + , hPutStrLnWith , hPutStrLn , hGetContents , toString @@ -61,23 +66,43 @@ readFile f = do h <- openFile (encodePath f) ReadMode hGetContents h -writeFile :: FilePath -> String -> IO () -writeFile f s = withFile (encodePath f) WriteMode $ \h -> hPutStr h s - getContents :: IO String getContents = hGetContents stdin +writeFileWith :: Newline -> FilePath -> String -> IO () +writeFileWith eol f s = + withFile (encodePath f) WriteMode $ \h -> hPutStrWith eol h s + +writeFile :: FilePath -> String -> IO () +writeFile = writeFileWith nativeNewline + +putStrWith :: Newline -> String -> IO () +putStrWith eol s = hPutStrWith eol stdout s + putStr :: String -> IO () -putStr s = hPutStr stdout s +putStr = putStrWith nativeNewline + +putStrLnWith :: Newline -> String -> IO () +putStrLnWith eol s = hPutStrLnWith eol stdout s putStrLn :: String -> IO () -putStrLn s = hPutStrLn stdout s +putStrLn = putStrLnWith nativeNewline + +hPutStrWith :: Newline -> Handle -> String -> IO () +hPutStrWith eol h s = + hSetNewlineMode h (NewlineMode eol eol) >> + hSetEncoding h utf8 >> IO.hPutStr h s hPutStr :: Handle -> String -> IO () -hPutStr h s = hSetEncoding h utf8 >> IO.hPutStr h s +hPutStr = hPutStrWith nativeNewline + +hPutStrLnWith :: Newline -> Handle -> String -> IO () +hPutStrLnWith eol h s = + hSetNewlineMode h (NewlineMode eol eol) >> + hSetEncoding h utf8 >> IO.hPutStrLn h s hPutStrLn :: Handle -> String -> IO () -hPutStrLn h s = hSetEncoding h utf8 >> IO.hPutStrLn h s +hPutStrLn = hPutStrLnWith nativeNewline hGetContents :: Handle -> IO String hGetContents = fmap toString . B.hGetContents -- cgit v1.2.3 From 818d5c2f354cd4896659493452722c030ae7c766 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 18 May 2017 13:20:32 +0200 Subject: Markdown: allow attributes in reference links to start on next line. This addresses a subsidiary issue in #3674. --- src/Text/Pandoc/Readers/Markdown.hs | 4 +++- test/command/3674.md | 13 +++++++++++++ 2 files changed, 16 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 7434ef1f6..af7588562 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -392,7 +392,9 @@ referenceKey = try $ do src <- try betweenAngles <|> sourceURL tit <- option "" referenceTitle attr <- option nullAttr $ try $ - guardEnabled Ext_link_attributes >> skipSpaces >> attributes + do guardEnabled Ext_link_attributes + skipSpaces >> optional newline >> skipSpaces + attributes addKvs <- option [] $ guardEnabled Ext_mmd_link_attributes >> many (try $ spnl >> keyValAttr) blanklines diff --git a/test/command/3674.md b/test/command/3674.md index 09f4e0d1e..92ed4bed7 100644 --- a/test/command/3674.md +++ b/test/command/3674.md @@ -24,3 +24,16 @@ Make sure we don't get duplicate reference links, even with [2]: b ``` + +Subsidiary issue: allow line break between reference link +url/title and attributes: + +``` +% pandoc +[a] + +[a]: url +{.class} +^D +

a

+``` -- cgit v1.2.3 From 0f6458c0c13380969ccac82d54a0e68a3ec76200 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 18 May 2017 13:38:19 +0200 Subject: Don't double extract images from docx. This fixes a regression that was introduced when `--extract-media` was generalized to work with any input format. We were getting two versions of each image extracted from a docx, one with a hash, one with the original filename, though only the hash one was used. This patch restores the original behavior (using the original filename). Pointed out in comments on #3674. Thanks to @laperouse. --- src/Text/Pandoc/Class.hs | 23 ++++++++++++++--------- 1 file changed, 14 insertions(+), 9 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 4ef56ec33..8b2adc507 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -345,19 +345,24 @@ withPaths (p:ps) action fp = catchError (action (p fp)) (\_ -> withPaths ps action fp) --- | Traverse tree, filling media bag. +-- | Traverse tree, filling media bag for any images that +-- aren't already in the media bag. fillMediaBag :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc fillMediaBag sourceURL d = walkM handleImage d where handleImage :: PandocMonad m => Inline -> m Inline handleImage (Image attr lab (src, tit)) = catchError - (do (bs, mt) <- fetchItem sourceURL src - let ext = fromMaybe (takeExtension src) - (mt >>= extensionFromMimeType) - let bs' = BL.fromChunks [bs] - let basename = showDigest $ sha1 bs' - let fname = basename <.> ext - insertMedia fname mt bs' - return $ Image attr lab (fname, tit)) + (do mediabag <- getMediaBag + case lookupMedia src mediabag of + Just (_, _) -> return $ Image attr lab (src, tit) + Nothing -> do + (bs, mt) <- downloadOrRead sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = BL.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit)) (\e -> do case e of PandocResourceNotFound _ -> do -- cgit v1.2.3 From b9185b02162ea56ee685594e1c5cfb816e796754 Mon Sep 17 00:00:00 2001 From: Ian Date: Fri, 19 May 2017 04:34:13 +0800 Subject: Docx writer: Change FigureWithCaption to CaptionedFigure (#3658) Edit styles.xml as part of the fix for #3656 --- data/docx/word/styles.xml | 4 ++-- src/Text/Pandoc/Writers/Docx.hs | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) (limited to 'src/Text') diff --git a/data/docx/word/styles.xml b/data/docx/word/styles.xml index 5d09a67b0..67d336db1 100644 --- a/data/docx/word/styles.xml +++ b/data/docx/word/styles.xml @@ -400,8 +400,8 @@ - - + + diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index b58c983a1..2282a5c58 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -875,7 +875,7 @@ blockToOpenXML' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do let prop = pCustomStyle $ if null alt then "Figure" - else "FigureWithCaption" + else "CaptionedFigure" paraProps <- local (\env -> env { envParaProperties = prop : envParaProperties env }) (getParaProps False) contents <- inlinesToOpenXML opts [Image attr alt (src,tit)] captionNode <- withParaProp (pCustomStyle "ImageCaption") -- cgit v1.2.3 From f870a2d8ea8cca5c8cf9ca30d87e0ff758618f18 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 18 May 2017 22:50:07 +0200 Subject: Don't render LaTeX images with data: URIs. LaTeX can't handle these. Note that --extract-media can be used when the input contains data: URIs. Closes #3636. --- src/Text/Pandoc/Writers/LaTeX.hs | 3 +++ 1 file changed, 3 insertions(+) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 26508b7c3..31c70e99d 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1062,6 +1062,9 @@ inlineToLaTeX (Link _ txt (src, _)) = src' <- stringToLaTeX URLString (escapeURI src) return $ text ("\\href{" ++ src' ++ "}{") <> contents <> char '}' +inlineToLaTeX il@(Image _ _ ('d':'a':'t':'a':':':_, _)) = do + report $ InlineNotRendered il + return empty inlineToLaTeX (Image attr _ (source, _)) = do setEmptyLine False modify $ \s -> s{ stGraphics = True } -- cgit v1.2.3 From 7a09b7b21dbbee34332047d07eae88fe152340b8 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Thu, 18 May 2017 23:12:17 +0200 Subject: Org reader: fix smart parsing behavior Parsing of smart quotes and special characters can either be enabled via the `smart` language extension or the `'` and `-` export options. Smart parsing is active if either the extension or export option is enabled. Only smart parsing of special characters (like ellipses and en and em dashes) is enabled by default, while smart quotes are disabled. This means that all smart parsing features will be enabled by adding the `smart` language extension. Fine-grained control is possible by leaving the language extension disabled. In that case, smart parsing is controlled via the aforementioned export OPTIONS only. Previously, all smart parsing was disabled unless the language extension was enabled. --- src/Text/Pandoc/Readers/Org/Inlines.hs | 23 ++++++++++++++--------- src/Text/Pandoc/Readers/Org/ParserState.hs | 2 +- test/Tests/Readers/Org.hs | 4 ++-- 3 files changed, 17 insertions(+), 12 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 800264db0..aa376fe25 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -862,24 +862,29 @@ macro = try $ do smart :: PandocMonad m => OrgParser m (F Inlines) smart = do - guardEnabled Ext_smart doubleQuoted <|> singleQuoted <|> choice (map (return <$>) [orgApostrophe, orgDash, orgEllipses]) where orgDash = do - guard =<< getExportSetting exportSpecialStrings + guardOrSmartEnabled =<< getExportSetting exportSpecialStrings dash <* updatePositions '-' orgEllipses = do - guard =<< getExportSetting exportSpecialStrings + guardOrSmartEnabled =<< getExportSetting exportSpecialStrings ellipses <* updatePositions '.' - orgApostrophe = - (char '\'' <|> char '\8217') <* updateLastPreCharPos - <* updateLastForbiddenCharPos - *> return (B.str "\x2019") + orgApostrophe = do + guardEnabled Ext_smart + (char '\'' <|> char '\8217') <* updateLastPreCharPos + <* updateLastForbiddenCharPos + return (B.str "\x2019") + +guardOrSmartEnabled :: PandocMonad m => Bool -> OrgParser m () +guardOrSmartEnabled b = do + smartExtension <- extensionEnabled Ext_smart <$> getOption readerExtensions + guard (b || smartExtension) singleQuoted :: PandocMonad m => OrgParser m (F Inlines) singleQuoted = try $ do - guard =<< getExportSetting exportSmartQuotes + guardOrSmartEnabled =<< getExportSetting exportSmartQuotes singleQuoteStart updatePositions '\'' withQuoteContext InSingleQuote $ @@ -891,7 +896,7 @@ singleQuoted = try $ do -- in the same paragraph. doubleQuoted :: PandocMonad m => OrgParser m (F Inlines) doubleQuoted = try $ do - guard =<< getExportSetting exportSmartQuotes + guardOrSmartEnabled =<< getExportSetting exportSmartQuotes doubleQuoteStart updatePositions '"' contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 51666fc64..1736cd881 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -252,7 +252,7 @@ defaultExportSettings = ExportSettings , exportDrawers = Left ["LOGBOOK"] , exportEmphasizedText = True , exportHeadlineLevels = 3 - , exportSmartQuotes = True + , exportSmartQuotes = False , exportSpecialStrings = True , exportSubSuperscripts = True , exportWithAuthor = True diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs index 1419604ac..eb5b68dc9 100644 --- a/test/Tests/Readers/Org.hs +++ b/test/Tests/Readers/Org.hs @@ -961,8 +961,8 @@ tests = ] , "Not a Horizontal Rule" =: - "----- five dashes" =?> - (para $ spcSep [ "-----", "five", "dashes" ]) + "----- em and en dash" =?> + para "\8212\8211 em and en dash" , "Comment Block" =: unlines [ "#+BEGIN_COMMENT" -- cgit v1.2.3 From ca77f0a95e03cace027a235ebbc1effa99ea030a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 19 May 2017 21:01:45 +0200 Subject: RST writer: add empty comments when needed... to avoid including a blocquote in the indented content of a preceding block. Closes #3675. --- src/Text/Pandoc/Writers/RST.hs | 28 +++++++++++++++++++++++++--- test/command/3675.md | 15 +++++++++++++++ test/writer.rst | 6 ++++++ 3 files changed, 46 insertions(+), 3 deletions(-) create mode 100644 test/command/3675.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index d16f013c0..5dc2ba31a 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -57,6 +57,7 @@ data WriterState = , stHasRawTeX :: Bool , stOptions :: WriterOptions , stTopLevel :: Bool + , stLastNested :: Bool } type RST = StateT WriterState @@ -67,7 +68,7 @@ writeRST opts document = do let st = WriterState { stNotes = [], stLinks = [], stImages = [], stHasMath = False, stHasRawTeX = False, stOptions = opts, - stTopLevel = True} + stTopLevel = True, stLastNested = False} evalStateT (pandocToRST document) st -- | Return RST representation of document. @@ -343,11 +344,32 @@ blockListToRST' :: PandocMonad m -> RST m Doc blockListToRST' topLevel blocks = do tl <- gets stTopLevel - modify (\s->s{stTopLevel=topLevel}) - res <- vcat `fmap` mapM blockToRST blocks + modify (\s->s{stTopLevel=topLevel, stLastNested=False}) + res <- vcat `fmap` mapM blockToRST' blocks modify (\s->s{stTopLevel=tl}) return res +blockToRST' :: PandocMonad m => Block -> RST m Doc +blockToRST' (x@BlockQuote{}) = do + lastNested <- gets stLastNested + res <- blockToRST x + modify (\s -> s{stLastNested = True}) + return $ if lastNested + then ".." $+$ res + else res +blockToRST' x = do + modify (\s -> s{stLastNested = + case x of + Para [Image _ _ (_,'f':'i':'g':':':_)] -> True + Para{} -> False + Plain{} -> False + Header{} -> False + LineBlock{} -> False + HorizontalRule -> False + _ -> True + }) + blockToRST x + blockListToRST :: PandocMonad m => [Block] -- ^ List of block elements -> RST m Doc diff --git a/test/command/3675.md b/test/command/3675.md new file mode 100644 index 000000000..b129c7a63 --- /dev/null +++ b/test/command/3675.md @@ -0,0 +1,15 @@ +```` +% pandoc -t rst +```python +print("hello") +``` +> block quote +^D +.. code:: python + + print("hello") + +.. + + block quote +```` diff --git a/test/writer.rst b/test/writer.rst index 1aeeacacb..1b2f6d1e9 100644 --- a/test/writer.rst +++ b/test/writer.rst @@ -75,6 +75,8 @@ E-mail style: This is a block quote. It is pretty short. +.. + Code in a block quote: :: @@ -92,6 +94,8 @@ E-mail style: nested + .. + nested This should not be a block quote: 2 > 1. @@ -342,6 +346,8 @@ Multiple blocks with italics: { orange code block } + .. + orange block quote Multiple definitions, tight: -- cgit v1.2.3 From 8d4fbe6a2a50d93bff0e9c7ada73774ff1bc17c6 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 17:09:47 +0200 Subject: SelfContained: fixed problem with embedded fonts. Closes #3629. However, there is still room for improvement. `@import` with following media declaration is not handled. Also `@import` with a simple filename (rather than `url(...)` is not handled. --- src/Text/Pandoc/SelfContained.hs | 54 ++++++++++++++++++++++++++++++---------- 1 file changed, 41 insertions(+), 13 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index c0a12adf2..e9a91b690 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -35,6 +35,7 @@ import Codec.Compression.GZip as Gzip import Control.Applicative ((<|>)) import Control.Monad.Except (throwError) import Control.Monad.Trans (lift) +import Data.Monoid ((<>)) import Data.ByteString (ByteString) import Data.ByteString.Base64 import qualified Data.ByteString.Char8 as B @@ -95,9 +96,9 @@ convertTags sourceURL (t@(TagOpen "script" as):TagClose "script":ts) = (("src",dataUri) : [(x,y) | (x,y) <- as, x /= "src"]) : TagClose "script" : rest Right (mime, bs) - | (mime == "text/javascript" || - mime == "application/javascript" || - mime == "application/x-javascript") && + | ("text/javascript" `isPrefixOf` mime || + "application/javascript" `isPrefixOf` mime || + "application/x-javascript" `isPrefixOf` mime) && not (" return $ TagOpen "script" [("type", typeAttr)|not (null typeAttr)] @@ -121,11 +122,12 @@ convertTags sourceURL (t@(TagOpen "link" as):ts) = (("href",dataUri) : [(x,y) | (x,y) <- as, x /= "href"]) : rest Right (mime, bs) - | mime == "text/css" && not (" do + | "text/css" `isPrefixOf` mime + && not (" do rest <- convertTags sourceURL $ dropWhile (==TagClose "link") ts return $ - TagOpen "style" [("type", "text/css")] + TagOpen "style" [("type", mime)] : TagText (toString bs) : TagClose "style" : rest @@ -149,7 +151,20 @@ cssURLs sourceURL d orig = do parseCSSUrls :: PandocMonad m => Maybe String -> FilePath -> ParsecT ByteString () m ByteString parseCSSUrls sourceURL d = B.concat <$> P.many - (pCSSWhite <|> pCSSComment <|> pCSSUrl sourceURL d <|> pCSSOther) + (pCSSWhite <|> pCSSComment <|> pCSSImport sourceURL d <|> + pCSSUrl sourceURL d <|> pCSSOther) + +pCSSImport :: PandocMonad m => Maybe String -> FilePath + -> ParsecT ByteString () m ByteString +pCSSImport sourceURL d = P.try $ do + P.string "@import" + P.spaces + res <- pCSSUrl' sourceURL d + P.spaces + P.optional $ P.char ';' >> P.spaces + case res of + Left b -> return $ B.pack "@import " <> b + Right (_, b) -> return b -- Note: some whitespace in CSS is significant, so we can't collapse it! pCSSWhite :: PandocMonad m => ParsecT ByteString () m ByteString @@ -170,13 +185,25 @@ pCSSOther = do pCSSUrl :: PandocMonad m => Maybe String -> FilePath -> ParsecT ByteString () m ByteString pCSSUrl sourceURL d = P.try $ do + res <- pCSSUrl' sourceURL d + case res of + Left b -> return b + Right (mt,b) -> do + let enc = makeDataURI (mt, b) + return (B.pack $ "url(" ++ enc ++ ")") + +pCSSUrl' :: PandocMonad m + => Maybe String -> FilePath + -> ParsecT ByteString () m (Either ByteString (MimeType, ByteString)) +pCSSUrl' sourceURL d = P.try $ do P.string "url(" P.spaces quote <- P.option Nothing (Just <$> P.oneOf "\"'") url <- P.manyTill P.anyChar (maybe (P.lookAhead (P.char ')')) P.char quote) P.spaces P.char ')' - let fallback = B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ + let fallback = Left $ + B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ maybe "" (:[]) quote ++ ")") -- pipes are used in URLs provided by Google Code fonts -- but parseURI doesn't like them, so we escape them: @@ -186,13 +213,14 @@ pCSSUrl sourceURL d = P.try $ do u -> do let url' = if isURI u then u else d u res <- lift $ getData sourceURL "" url' case res of - Left uri -> return (B.pack $ "url(" ++ uri ++ ")") + Left uri -> return $ Left (B.pack $ "url(" ++ uri ++ ")") Right (mt, raw) -> do - -- note that the downloaded content may + -- note that the downloaded CSS may -- itself contain url(...). - raw' <- cssURLs sourceURL d raw - let enc = makeDataURI (mt, raw') - return (B.pack $ "url(" ++ enc ++ ")") + b <- if "text/css" `isPrefixOf` mt + then cssURLs sourceURL d raw + else return raw + return $ Right (mt, b) getDataURI :: PandocMonad m => Maybe String -> MimeType -> String -> m String getDataURI sourceURL mimetype src = do @@ -224,7 +252,7 @@ getData sourceURL mimetype src = do uriQuery = "", uriFragment = "" } _ -> Nothing - result <- if mime == "text/css" + result <- if "text/css" `isPrefixOf` mime then cssURLs cssSourceURL (takeDirectory src) raw' else return raw' return $ Right (mime, result) -- cgit v1.2.3 From 93eaf33e6e7fbb364c83e6bde66f253a8b14297b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 17:27:07 +0200 Subject: SelfContained: handle @import with quoted string. --- src/Text/Pandoc/SelfContained.hs | 36 +++++++++++++++++++++++++----------- 1 file changed, 25 insertions(+), 11 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index e9a91b690..f8ad43b1e 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -159,9 +159,10 @@ pCSSImport :: PandocMonad m => Maybe String -> FilePath pCSSImport sourceURL d = P.try $ do P.string "@import" P.spaces - res <- pCSSUrl' sourceURL d + res <- (pQuoted <|> pUrl) >>= handleCSSUrl sourceURL d + P.spaces + P.char ';' P.spaces - P.optional $ P.char ';' >> P.spaces case res of Left b -> return $ B.pack "@import " <> b Right (_, b) -> return b @@ -185,31 +186,44 @@ pCSSOther = do pCSSUrl :: PandocMonad m => Maybe String -> FilePath -> ParsecT ByteString () m ByteString pCSSUrl sourceURL d = P.try $ do - res <- pCSSUrl' sourceURL d + res <- pUrl >>= handleCSSUrl sourceURL d case res of Left b -> return b Right (mt,b) -> do let enc = makeDataURI (mt, b) return (B.pack $ "url(" ++ enc ++ ")") -pCSSUrl' :: PandocMonad m - => Maybe String -> FilePath - -> ParsecT ByteString () m (Either ByteString (MimeType, ByteString)) -pCSSUrl' sourceURL d = P.try $ do +pQuoted :: PandocMonad m + => ParsecT ByteString () m (String, ByteString) +pQuoted = P.try $ do + quote <- P.oneOf "\"'" + url <- P.manyTill P.anyChar (P.char quote) + let fallback = B.pack ([quote] ++ trim url ++ [quote]) + return (url, fallback) + +pUrl :: PandocMonad m + => ParsecT ByteString () m (String, ByteString) +pUrl = P.try $ do P.string "url(" P.spaces quote <- P.option Nothing (Just <$> P.oneOf "\"'") url <- P.manyTill P.anyChar (maybe (P.lookAhead (P.char ')')) P.char quote) P.spaces P.char ')' - let fallback = Left $ - B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ + let fallback = B.pack ("url(" ++ maybe "" (:[]) quote ++ trim url ++ maybe "" (:[]) quote ++ ")") + return (url, fallback) + +handleCSSUrl :: PandocMonad m + => Maybe String -> FilePath -> (String, ByteString) + -> ParsecT ByteString () m + (Either ByteString (MimeType, ByteString)) +handleCSSUrl sourceURL d (url, fallback) = do -- pipes are used in URLs provided by Google Code fonts -- but parseURI doesn't like them, so we escape them: case escapeURIString (/='|') (trim url) of - '#':_ -> return fallback - 'd':'a':'t':'a':':':_ -> return fallback + '#':_ -> return $ Left fallback + 'd':'a':'t':'a':':':_ -> return $ Left fallback u -> do let url' = if isURI u then u else d u res <- lift $ getData sourceURL "" url' case res of -- cgit v1.2.3 From fd6e65b00ffc628488c27171f7dd9ab833c436c6 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 21:43:53 +0200 Subject: Added `--resource-path=SEARCHPATH` command line option. SEARCHPATH is separated by the usual character, depending on OS (: on unix, ; on windows). Note: This does not yet work for PDF output, because the routine that creates PDFs runs outside PandocMonad. (This has to do with its use of inTemporaryDirectory and its interaction with our exceptions.) The best solution would be to figure out how to move the PDF creation routines into PandocMonad. Second-best, just pass an extra parameter in? See #852. --- MANUAL.txt | 6 ++++++ src/Text/Pandoc/App.hs | 13 ++++++++++++- 2 files changed, 18 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index 51b324817..8c65789b9 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -690,6 +690,12 @@ General writer options repeatedly to include multiple files. They will be included in the order specified. Implies `--standalone`. +`--resource-path=`*SEARCHPATH* + +: List of paths to search for images and other resources. + The paths should be separated by `:` on linux, unix, and + MacOS systems, and by `;` on Windows. + Options affecting specific writers ---------------------------------- diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 9c8e1bde4..a4967e5d1 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -70,7 +70,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, - extractMedia, fillMediaBag) + extractMedia, fillMediaBag, setResourcePath) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) @@ -414,6 +414,7 @@ convertWithOpts opts = do let eol = fromMaybe nativeNewline $ optEol opts runIO' $ do + setResourcePath $ "." : (optResourcePath opts) (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) then fillMediaBag (writerSourceURL writerOptions) @@ -569,6 +570,7 @@ data Opt = Opt , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header + , optResourcePath :: [FilePath] -- ^ Path to search for images etc , optEol :: Maybe Newline -- ^ Enforce line-endings } @@ -638,6 +640,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] + , optResourcePath = [] , optEol = Nothing } @@ -1052,6 +1055,14 @@ options = "FILE") "" -- "File to include after document body" + , Option "" ["resource-path"] + (ReqArg + (\arg opt -> return opt { optResourcePath = + splitSearchPath arg }) + "SEARCHPATH") + "" -- "Paths to search for images and other resources" + + , Option "" ["self-contained"] (NoArg (\opt -> return opt { optSelfContained = True, -- cgit v1.2.3 From 5c44fd554fbebc2e01a0aa9f569468789f353bf4 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 22:42:30 +0200 Subject: PDF: Refactoring, makePDF is now in PandocIO [API change]. --- src/Text/Pandoc/PDF.hs | 21 ++++++++------------- 1 file changed, 8 insertions(+), 13 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index cc9b38f7f..822067e78 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -72,16 +72,15 @@ changePathSeparators :: FilePath -> FilePath changePathSeparators = intercalate "/" . splitDirectories #endif -makePDF :: MonadIO m - => String -- ^ pdf creator (pdflatex, lualatex, +makePDF :: String -- ^ pdf creator (pdflatex, lualatex, -- xelatex, context, wkhtmltopdf, pdfroff) -> (WriterOptions -> Pandoc -> PandocIO String) -- ^ writer -> WriterOptions -- ^ options -> Verbosity -- ^ verbosity level -> MediaBag -- ^ media -> Pandoc -- ^ document - -> m (Either ByteString ByteString) -makePDF "wkhtmltopdf" writer opts verbosity _ doc@(Pandoc meta _) = liftIO $ do + -> PandocIO (Either ByteString ByteString) +makePDF "wkhtmltopdf" writer opts verbosity _ doc@(Pandoc meta _) = do let mathArgs = case writerHTMLMathMethod opts of -- with MathJax, wait til all math is rendered: MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });", @@ -102,17 +101,13 @@ makePDF "wkhtmltopdf" writer opts verbosity _ doc@(Pandoc meta _) = liftIO $ do ,("margin-left", fromMaybe (Just "1.25in") (getField "margin-left" meta')) ] - source <- runIOorExplode $ do - setVerbosity verbosity - writer opts doc - html2pdf verbosity args source -makePDF "pdfroff" writer opts verbosity _mediabag doc = liftIO $ do - source <- runIOorExplode $ do - setVerbosity verbosity - writer opts doc + source <- writer opts doc + liftIO $ html2pdf verbosity args source +makePDF "pdfroff" writer opts verbosity _mediabag doc = do + source <- writer opts doc let args = ["-ms", "-mpdfmark", "-e", "-t", "-k", "-KUTF-8", "-i", "--no-toc-relocation"] - ms2pdf verbosity args source + liftIO $ ms2pdf verbosity args source makePDF program writer opts verbosity mediabag doc = do let withTemp = if takeBaseName program == "context" then withTempDirectory "." -- cgit v1.2.3 From 03cb05f4c614f08600bcd8e90a7fd1ca13ae33a2 Mon Sep 17 00:00:00 2001 From: Marc Schreiber Date: Thu, 20 Apr 2017 11:11:01 +0200 Subject: Improve SVG image size code. The old code made some unwise assumptions about how the svg file would look. See #3580. --- pandoc.cabal | 4 + src/Text/Pandoc/ImageSize.hs | 2 +- test/command/SVG_logo-without-xml-declaration.svg | 32 ++++++ test/command/SVG_logo.svg | 33 ++++++ test/command/corrupt.svg | 5 + test/command/inkscape-cube.svg | 119 ++++++++++++++++++++ test/command/svg.md | 129 ++++++++++++++++++++++ 7 files changed, 323 insertions(+), 1 deletion(-) create mode 100644 test/command/SVG_logo-without-xml-declaration.svg create mode 100644 test/command/SVG_logo.svg create mode 100644 test/command/corrupt.svg create mode 100644 test/command/inkscape-cube.svg create mode 100644 test/command/svg.md (limited to 'src/Text') diff --git a/pandoc.cabal b/pandoc.cabal index 61ef5c522..14a407b85 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -136,6 +136,10 @@ Extra-Source-Files: test/*.native test/command/*.md test/command/abbrevs + test/command/SVG_logo-without-xml-declaration.svg + test/command/SVG_logo.svg + test/command/corrupt.svg + test/command/inkscape-cube.svg test/command/sub-file-chapter-1.tex test/command/sub-file-chapter-2.tex test/command/3510-subdoc.org diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index a0800e499..4d914a10c 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -116,7 +116,7 @@ imageType img = case B.take 4 img of _ -> mzero findSvgTag :: ByteString -> Bool -findSvgTag img = B.null $ snd (B.breakSubstring img " ByteString -> Either String ImageSize imageSize opts img = diff --git a/test/command/SVG_logo-without-xml-declaration.svg b/test/command/SVG_logo-without-xml-declaration.svg new file mode 100644 index 000000000..febcab6ca --- /dev/null +++ b/test/command/SVG_logo-without-xml-declaration.svg @@ -0,0 +1,32 @@ + +SVG Logo + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/test/command/SVG_logo.svg b/test/command/SVG_logo.svg new file mode 100644 index 000000000..5333a5ddb --- /dev/null +++ b/test/command/SVG_logo.svg @@ -0,0 +1,33 @@ + + +SVG Logo + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff --git a/test/command/corrupt.svg b/test/command/corrupt.svg new file mode 100644 index 000000000..cfaa697f0 --- /dev/null +++ b/test/command/corrupt.svg @@ -0,0 +1,5 @@ +Lorem ipsum dolor sit amet etiam. A pede dolor neque pretium luctus pharetra vel rutrum. Orci nonummy ac. At eu est tempor +proin wisi. Nunc tincidunt proin. Suspendisse lorem commodo. Integer diam diam semper commodo dictum et tellus eu ultrices +nec erat pulvinar porttitor nulla nulla mauris orci libero eros elementum et possimus voluptate. Velit morbi et. Luctus diam +in. Lorem tincidunt sem dolor rerum mauris. Dis taciti posuere pellentesque sed rutrum. Lectus donec fusce in dictum pede. +In etiam congue. Aliquam aliquet elit arcu mauris enim. Risus at enim. diff --git a/test/command/inkscape-cube.svg b/test/command/inkscape-cube.svg new file mode 100644 index 000000000..995c3c734 --- /dev/null +++ b/test/command/inkscape-cube.svg @@ -0,0 +1,119 @@ + + + + + + + + + + + + image/svg+xml + + + + + + + + + + + + + + + + diff --git a/test/command/svg.md b/test/command/svg.md new file mode 100644 index 000000000..bcf00ddae --- /dev/null +++ b/test/command/svg.md @@ -0,0 +1,129 @@ +``` +% pandoc -f latex -t icml +\includegraphics{command/corrupt.svg} +^D + + + + + + + + + + + + + + + + + + + $ID/Embedded + + + + + + + +``` + +``` +% pandoc -f latex -t icml +\includegraphics{command/SVG_logo.svg} +^D + + + + + + + + + + + + + + + + + + + $ID/Embedded + + + + + + + +``` + +``` +% pandoc -f latex -t icml +\includegraphics{command/SVG_logo-without-xml-declaration.svg} +^D + + + + + + + + + + + + + + + + + + + $ID/Embedded + + + + + + + +``` + + +``` +% pandoc -f latex -t icml +\includegraphics{command/inkscape-cube.svg} +^D + + + + + + + + + + + + + + + + + + + $ID/Embedded + + + + + + + +``` + -- cgit v1.2.3 From 753d5811e2d08ac27dd77659e43a6968b7ebd72a Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 21 May 2017 00:14:08 +0300 Subject: RST reader: make use of anyLineNewline (#3686) --- src/Text/Pandoc/Readers/RST.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 868bfafa4..e85ebade1 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -559,8 +559,7 @@ listLine :: Monad m => Int -> RSTParser m [Char] listLine markerLength = try $ do notFollowedBy blankline indentWith markerLength - line <- anyLine - return $ line ++ "\n" + anyLineNewline -- indent by specified number of spaces (or equiv. tabs) indentWith :: Monad m => Int -> RSTParser m [Char] -- cgit v1.2.3 From d109c8be8fe97631fa29affed0de6c4d50f56a95 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 23:23:52 +0200 Subject: PDF: better error message for non-converted svg images. --- src/Text/Pandoc/PDF.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src/Text') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 822067e78..090bcbc6d 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -159,6 +159,7 @@ convertImage tmpdir fname = Just "image/png" -> doNothing Just "image/jpeg" -> doNothing Just "application/pdf" -> doNothing + Just "image/svg+xml" -> return $ Left "conversion from svg not supported" _ -> JP.readImage fname >>= \res -> case res of Left e -> return $ Left e -- cgit v1.2.3 From 6a7f980247bd2e3fcb7b977edbbcd1fc17758074 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 23:46:31 +0200 Subject: PDF: Got --resource-path working with pdf output. See #852. --- src/Text/Pandoc/PDF.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 090bcbc6d..e8a826e4c 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -63,8 +63,8 @@ import Text.Pandoc.Writers.Shared (getField, metaToJSON) import Data.List (intercalate) #endif import Text.Pandoc.Class (PandocIO, report, runIO, runIOorExplode, - setMediaBag, setVerbosity, - fillMediaBag, extractMedia) + setMediaBag, setVerbosity, getResourcePath, + setResourcePath, fillMediaBag, extractMedia) import Text.Pandoc.Logging #ifdef _WINDOWS @@ -112,8 +112,9 @@ makePDF program writer opts verbosity mediabag doc = do let withTemp = if takeBaseName program == "context" then withTempDirectory "." else withTempDir + resourcePath <- getResourcePath liftIO $ withTemp "tex2pdf." $ \tmpdir -> do - doc' <- handleImages verbosity opts mediabag tmpdir doc + doc' <- handleImages verbosity opts resourcePath mediabag tmpdir doc source <- runIOorExplode $ do setVerbosity verbosity writer opts doc' @@ -126,13 +127,15 @@ makePDF program writer opts verbosity mediabag doc = do handleImages :: Verbosity -> WriterOptions + -> [FilePath] -> MediaBag -> FilePath -- ^ temp dir to store images -> Pandoc -- ^ document -> IO Pandoc -handleImages verbosity opts mediabag tmpdir doc = do +handleImages verbosity opts resourcePath mediabag tmpdir doc = do doc' <- runIOorExplode $ do setVerbosity verbosity + setResourcePath resourcePath setMediaBag mediabag fillMediaBag (writerSourceURL opts) doc >>= extractMedia tmpdir -- cgit v1.2.3 From 8c1b81bbef7125a9a2fde9d6894578f06bf4cedd Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 21 May 2017 08:59:06 +0200 Subject: Finished implemtation of `--resource-path`. * Default is just working directory. * Working directory must be explicitly specifide if `--resource-path` option is used. --- MANUAL.txt | 8 +++++++- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Readers/LaTeX.hs | 4 ++-- 3 files changed, 11 insertions(+), 5 deletions(-) (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index 8c65789b9..c7aa299c4 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -694,7 +694,13 @@ General writer options : List of paths to search for images and other resources. The paths should be separated by `:` on linux, unix, and - MacOS systems, and by `;` on Windows. + MacOS systems, and by `;` on Windows. If `--resource-path` + is not specified, the default resource path is the working + directory. Note that, if `--resource-path` is specified, + the working directory must be explicitly listed or it + will not be searched. For example: + `--resource-path=.:test` will search the working directory + and the `test` subdirectory, in that order. Options affecting specific writers ---------------------------------- diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index a4967e5d1..c874a2cde 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -414,7 +414,7 @@ convertWithOpts opts = do let eol = fromMaybe nativeNewline $ optEol opts runIO' $ do - setResourcePath $ "." : (optResourcePath opts) + setResourcePath (optResourcePath opts) (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) then fillMediaBag (writerSourceURL writerOptions) @@ -640,7 +640,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] - , optResourcePath = [] + , optResourcePath = ["."] , optEol = Nothing } diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 30c788666..84758d309 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -46,7 +46,7 @@ import Safe (minimumDef) import System.FilePath (addExtension, replaceExtension, takeExtension) import Text.Pandoc.Builder import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, readFileFromDirs, - report, setResourcePath) + report, setResourcePath, getResourcePath) import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension) import Text.Pandoc.ImageSize (numUnit, showFl) import Text.Pandoc.Logging @@ -417,7 +417,7 @@ blockCommands = M.fromList $ graphicsPath :: PandocMonad m => LP m Blocks graphicsPath = do ps <- bgroup *> (manyTill braced egroup) - setResourcePath (".":ps) + getResourcePath >>= setResourcePath . (++ ps) return mempty addMeta :: PandocMonad m => ToMetaValue a => String -> a -> LP m () -- cgit v1.2.3 From aa1e39858dd0ad25fd5e0cf0e2e19182bd4f157b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 21 May 2017 11:42:50 +0200 Subject: Text.Pandoc.App: ToJSON and FromJSON instances for Opts. This can be used e.g. to pass options via web interface, such as trypandoc. --- src/Text/Pandoc/App.hs | 27 ++++++++++++++++++++++----- src/Text/Pandoc/Logging.hs | 10 ++++++++++ src/Text/Pandoc/Options.hs | 34 ++++++++++++++++++++++++++++++++++ 3 files changed, 66 insertions(+), 5 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index c874a2cde..eee72fd3c 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1,6 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} +{-# LANGUAGE DeriveGeneric #-} {- Copyright (C) 2006-2017 John MacFarlane @@ -42,12 +43,14 @@ import qualified Control.Exception as E import Control.Monad.Except (throwError) import Control.Monad import Control.Monad.Trans -import Data.Aeson (eitherDecode', encode) +import Data.Aeson (eitherDecode', encode, ToJSON(..), FromJSON(..), + genericToEncoding, defaultOptions) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) import qualified Data.Set as Set import Data.Foldable (foldrM) +import GHC.Generics import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) @@ -65,7 +68,8 @@ import System.Directory (Permissions (..), doesFileExist, findExecutable, import System.Environment (getArgs, getEnvironment, getProgName) import System.Exit (ExitCode (..), exitSuccess) import System.FilePath -import System.IO (stdout, nativeNewline, Newline(..)) +import System.IO (stdout, nativeNewline) +import qualified System.IO as IO (Newline(..)) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) @@ -86,6 +90,12 @@ import System.Posix.IO (stdOutput) import System.Posix.Terminal (queryTerminal) #endif +data Newline = LF | CRLF deriving (Show, Generic) + +instance ToJSON Newline where + toEncoding = genericToEncoding defaultOptions +instance FromJSON Newline + parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt parseOptions options' defaults = do rawArgs <- map UTF8.decodeArg <$> getArgs @@ -411,7 +421,10 @@ convertWithOpts opts = do return $ ("csl", jatsEncoded) : optMetadata opts else return $ optMetadata opts - let eol = fromMaybe nativeNewline $ optEol opts + let eol = case optEol opts of + Just CRLF -> IO.CRLF + Just LF -> IO.LF + Nothing -> nativeNewline runIO' $ do setResourcePath (optResourcePath opts) @@ -572,7 +585,11 @@ data Opt = Opt , optIncludeInHeader :: [FilePath] -- ^ Files to include in header , optResourcePath :: [FilePath] -- ^ Path to search for images etc , optEol :: Maybe Newline -- ^ Enforce line-endings - } + } deriving (Generic, Show) + +instance ToJSON Opt where + toEncoding = genericToEncoding defaultOptions +instance FromJSON Opt -- | Defaults for command-line options. defaultOpts :: Opt @@ -790,7 +807,7 @@ writeFnBinary :: MonadIO m => FilePath -> B.ByteString -> m () writeFnBinary "-" = liftIO . B.putStr writeFnBinary f = liftIO . B.writeFile (UTF8.encodePath f) -writerFn :: MonadIO m => Newline -> FilePath -> String -> m () +writerFn :: MonadIO m => IO.Newline -> FilePath -> String -> m () writerFn eol "-" = liftIO . UTF8.putStrWith eol writerFn eol f = liftIO . UTF8.writeFileWith eol f diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 2cca4b7d3..bf7f33d29 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -39,6 +39,7 @@ module Text.Pandoc.Logging ( , messageVerbosity ) where +import Control.Monad (mzero) import Data.Aeson import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder) @@ -56,6 +57,15 @@ data Verbosity = ERROR | WARNING | INFO | DEBUG instance ToJSON Verbosity where toJSON x = toJSON (show x) +instance FromJSON Verbosity where + parseJSON (String t) = + case t of + "ERROR" -> return ERROR + "WARNING" -> return WARNING + "INFO" -> return INFO + "DEBUG" -> return DEBUG + _ -> mzero + parseJSON _ = mzero data LogMessage = SkippedContent String SourcePos diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 6757c6782..c7211c86e 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -45,6 +45,8 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions , def , isEnabled ) where +import Data.Aeson (ToJSON(..), FromJSON(..), + genericToEncoding, defaultOptions) import Data.Data (Data) import Data.Default import qualified Data.Set as Set @@ -104,17 +106,29 @@ data HTMLMathMethod = PlainMath | KaTeX String String -- url of stylesheet and katex.js deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON HTMLMathMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON HTMLMathMethod + data CiteMethod = Citeproc -- use citeproc to render them | Natbib -- output natbib cite commands | Biblatex -- output biblatex cite commands deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON CiteMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON CiteMethod + -- | Methods for obfuscating email addresses in HTML. data ObfuscationMethod = NoObfuscation | ReferenceObfuscation | JavascriptObfuscation deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON ObfuscationMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON ObfuscationMethod + -- | Varieties of HTML slide shows. data HTMLSlideVariant = S5Slides | SlidySlides @@ -124,18 +138,30 @@ data HTMLSlideVariant = S5Slides | NoSlides deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON HTMLSlideVariant where + toEncoding = genericToEncoding defaultOptions +instance FromJSON HTMLSlideVariant + -- | Options for accepting or rejecting MS Word track-changes. data TrackChanges = AcceptChanges | RejectChanges | AllChanges deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON TrackChanges where + toEncoding = genericToEncoding defaultOptions +instance FromJSON TrackChanges + -- | Options for wrapping text in the output. data WrapOption = WrapAuto -- ^ Automatically wrap to width | WrapNone -- ^ No non-semantic newlines | WrapPreserve -- ^ Preserve wrapping of input source deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON WrapOption where + toEncoding = genericToEncoding defaultOptions +instance FromJSON WrapOption + -- | Options defining the type of top-level headers. data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts | TopLevelChapter -- ^ Top-level headers become chapters @@ -144,12 +170,20 @@ data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts -- heuristics deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON TopLevelDivision where + toEncoding = genericToEncoding defaultOptions +instance FromJSON TopLevelDivision + -- | Locations for footnotes and references in markdown output data ReferenceLocation = EndOfBlock -- ^ End of block | EndOfSection -- ^ prior to next section header (or end of document) | EndOfDocument -- ^ at end of document deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON ReferenceLocation where + toEncoding = genericToEncoding defaultOptions +instance FromJSON ReferenceLocation + -- | Options for writers data WriterOptions = WriterOptions { writerTemplate :: Maybe String -- ^ Template to use -- cgit v1.2.3 From 30a3deadcce18dd53a79a4915d915beb815702cf Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 22 May 2017 11:10:15 +0300 Subject: Move indentWith to Text.Pandoc.Parsing (#3687) --- src/Text/Pandoc/Parsing.hs | 12 ++++++++++++ src/Text/Pandoc/Readers/Org/Blocks.hs | 9 --------- src/Text/Pandoc/Readers/Org/Parsing.hs | 1 + src/Text/Pandoc/Readers/RST.hs | 9 --------- src/Text/Pandoc/Readers/Txt2Tags.hs | 3 --- 5 files changed, 13 insertions(+), 21 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index ce2523d12..e430c7cb5 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -37,6 +37,7 @@ A utility library with parsers used in pandoc readers. -} module Text.Pandoc.Parsing ( anyLine, anyLineNewline, + indentWith, many1Till, notFollowedBy', oneOfStrings, @@ -260,6 +261,17 @@ anyLine = do anyLineNewline :: Stream [Char] m Char => ParserT [Char] st m [Char] anyLineNewline = (++ "\n") <$> anyLine +-- | Parse indent by specified number of spaces (or equiv. tabs) +indentWith :: Stream [Char] m Char + => HasReaderOptions st + => Int -> ParserT [Char] st m [Char] +indentWith num = do + tabStop <- getOption readerTabStop + if (num < tabStop) + then count num (char ' ') + else choice [ try (count num (char ' ')) + , try (char '\t' >> indentWith (num - tabStop)) ] + -- | Like @manyTill@, but reads at least one item. many1Till :: Stream s m t => ParserT s st m a diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index f5823c7aa..fa2f7fac5 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -828,12 +828,3 @@ listContinuation markerLength = try $ <*> many blankline) where listLine = try $ indentWith markerLength *> anyLineNewline - - -- indent by specified number of spaces (or equiv. tabs) - indentWith :: Monad m => Int -> OrgParser m String - indentWith num = do - tabStop <- getOption readerTabStop - if num < tabStop - then count num (char ' ') - else choice [ try (count num (char ' ')) - , try (char '\t' >> count (num - tabStop) (char ' ')) ] diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 5c93a7eca..1d3e8c257 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -32,6 +32,7 @@ module Text.Pandoc.Readers.Org.Parsing ( OrgParser , anyLine , anyLineNewline + , indentWith , blanklines , newline , parseFromString diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index e85ebade1..ac1f4f834 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -561,15 +561,6 @@ listLine markerLength = try $ do indentWith markerLength anyLineNewline --- indent by specified number of spaces (or equiv. tabs) -indentWith :: Monad m => Int -> RSTParser m [Char] -indentWith num = do - tabStop <- getOption readerTabStop - if (num < tabStop) - then count num (char ' ') - else choice [ try (count num (char ' ')), - (try (char '\t' >> count (num - tabStop) (char ' '))) ] - -- parse raw text for one list item, excluding start marker and continuations rawListItem :: Monad m => RSTParser m Int -> RSTParser m (Int, [Char]) diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index aa7774b4c..ba2b20083 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -277,9 +277,6 @@ listContinuation markerLength = try $ <*> many blankline) where listLine = try $ indentWith markerLength *> anyLineNewline -indentWith :: Int -> T2T String -indentWith n = count n spaceChar - -- Table table :: T2T Blocks -- cgit v1.2.3 From 4d1e9b8e4198990e515185fd3a0d6047f7999a61 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 22 May 2017 10:10:04 +0200 Subject: Let `--eol` take `native` as an argument. Add `Native` to the `LineEnding` type. Make `optEol` a `Native` rather than `Maybe Native`. --- MANUAL.txt | 9 +++++---- src/Text/Pandoc/App.hs | 25 +++++++++++++------------ 2 files changed, 18 insertions(+), 16 deletions(-) (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index c7aa299c4..ae518054d 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -593,11 +593,12 @@ General writer options : Print a system default data file. Files in the user data directory are ignored. -`--eol=crlf`|`lf` +`--eol=crlf`|`lf`|`native` -: Manually specify line endings: `crlf` (Windows) or `lf` - (MacOS/linux/unix). The default is to use the line endings - appropriate for the OS. +: Manually specify line endings: `crlf` (Windows), `lf` + (MacOS/linux/unix), or `native` (line endings appropriate + to the OS on which pandoc is being run). The default is + `native`. `--dpi`=*NUMBER* diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index eee72fd3c..97954764a 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -90,11 +90,11 @@ import System.Posix.IO (stdOutput) import System.Posix.Terminal (queryTerminal) #endif -data Newline = LF | CRLF deriving (Show, Generic) +data LineEnding = LF | CRLF | Native deriving (Show, Generic) -instance ToJSON Newline where +instance ToJSON LineEnding where toEncoding = genericToEncoding defaultOptions -instance FromJSON Newline +instance FromJSON LineEnding parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt parseOptions options' defaults = do @@ -422,9 +422,9 @@ convertWithOpts opts = do else return $ optMetadata opts let eol = case optEol opts of - Just CRLF -> IO.CRLF - Just LF -> IO.LF - Nothing -> nativeNewline + CRLF -> IO.CRLF + LF -> IO.LF + Native -> nativeNewline runIO' $ do setResourcePath (optResourcePath opts) @@ -584,7 +584,7 @@ data Opt = Opt , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header , optResourcePath :: [FilePath] -- ^ Path to search for images etc - , optEol :: Maybe Newline -- ^ Enforce line-endings + , optEol :: LineEnding -- ^ Style of line-endings to use } deriving (Generic, Show) instance ToJSON Opt where @@ -658,7 +658,7 @@ defaultOpts = Opt , optIncludeAfterBody = [] , optIncludeInHeader = [] , optResourcePath = ["."] - , optEol = Nothing + , optEol = Native } addMetadata :: (String, String) -> Pandoc -> Pandoc @@ -986,12 +986,13 @@ options = (ReqArg (\arg opt -> case toLower <$> arg of - "crlf" -> return opt { optEol = Just CRLF } - "lf" -> return opt { optEol = Just LF } + "crlf" -> return opt { optEol = CRLF } + "lf" -> return opt { optEol = LF } + "native" -> return opt { optEol = Native } -- mac-syntax (cr) is not supported in ghc-base. _ -> E.throwIO $ PandocOptionError - "--eol must be one of crlf (Windows), lf (Unix)") - "crlf|lf") + "--eol must be crlf, lf, or native") + "crlf|lf|native") "" -- "EOL (default OS-dependent)" , Option "" ["wrap"] -- cgit v1.2.3 From 5debb0da0f94d1454d51cacede7c4844f01cc2f5 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 23 May 2017 09:48:11 +0200 Subject: Shared: Provide custom isURI that rejects unknown schemes [isURI] We also export the set of known `schemes`. The new function replaces the function of the same name from `Network.URI`, as the latter did not check whether a scheme is well-known. E.g. MediaWiki wikis frequently feature pages with names like `User:John`. These links were interpreted as URIs, thus turning internal links into global links. This is prevented by also checking whether the scheme of a URI is frequently used (i.e. is IANA registered or an otherwise well-known scheme). Fixes: #2713 Update set of well-known URIs from IANA list All official IANA schemes (as of 2017-05-22) are included in the set of known schemes. The four non-official schemes doi, isbn, javascript, and pmid are kept. --- src/Text/Pandoc/App.hs | 4 +-- src/Text/Pandoc/Parsing.hs | 27 +------------- src/Text/Pandoc/Readers/Txt2Tags.hs | 1 - src/Text/Pandoc/SelfContained.hs | 4 +-- src/Text/Pandoc/Shared.hs | 69 +++++++++++++++++++++++++++++++++++- src/Text/Pandoc/Writers/ConTeXt.hs | 2 +- src/Text/Pandoc/Writers/DokuWiki.hs | 3 +- src/Text/Pandoc/Writers/FB2.hs | 3 +- src/Text/Pandoc/Writers/Haddock.hs | 1 - src/Text/Pandoc/Writers/ICML.hs | 3 +- src/Text/Pandoc/Writers/LaTeX.hs | 2 +- src/Text/Pandoc/Writers/Markdown.hs | 1 - src/Text/Pandoc/Writers/MediaWiki.hs | 1 - src/Text/Pandoc/Writers/RST.hs | 1 - src/Text/Pandoc/Writers/Texinfo.hs | 2 +- src/Text/Pandoc/Writers/ZimWiki.hs | 5 ++- 16 files changed, 81 insertions(+), 48 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 97954764a..845146f34 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -57,7 +57,7 @@ import Data.Maybe (fromMaybe, isJust, isNothing) import qualified Data.Text as T import Data.Yaml (decode) import qualified Data.Yaml as Yaml -import Network.URI (URI (..), isURI, parseURI) +import Network.URI (URI (..), parseURI) import Paths_pandoc (getDataDir) import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme) import Skylighting.Parser (missingIncludes, parseSyntaxDefinition, @@ -80,7 +80,7 @@ import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) -import Text.Pandoc.Shared (headerShift, openURL, readDataFile, +import Text.Pandoc.Shared (isURI, headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.XML (toEntities) diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e430c7cb5..c6be48d19 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -465,33 +465,8 @@ emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain) sepby1 p sep = (:) <$> p <*> (many (try $ sep >> p)) --- Schemes from http://www.iana.org/assignments/uri-schemes.html plus --- the unofficial schemes coap, doi, javascript, isbn, pmid -schemes :: [String] -schemes = ["coap","doi","javascript","aaa","aaas","about","acap","cap","cid", - "crid","data","dav","dict","dns","file","ftp","geo","go","gopher", - "h323","http","https","iax","icap","im","imap","info","ipp","iris", - "iris.beep","iris.xpc","iris.xpcs","iris.lwz","ldap","mailto","mid", - "msrp","msrps","mtqp","mupdate","news","nfs","ni","nih","nntp", - "opaquelocktoken","pop","pres","rtsp","service","session","shttp","sieve", - "sip","sips","sms","snmp","soap.beep","soap.beeps","tag","tel","telnet", - "tftp","thismessage","tn3270","tip","tv","urn","vemmi","ws","wss","xcon", - "xcon-userid","xmlrpc.beep","xmlrpc.beeps","xmpp","z39.50r","z39.50s", - "adiumxtra","afp","afs","aim","apt","attachment","aw","beshare","bitcoin", - "bolo","callto","chrome","chrome-extension","com-eventbrite-attendee", - "content", "cvs","dlna-playsingle","dlna-playcontainer","dtn","dvb", - "ed2k","facetime","feed","finger","fish","gg","git","gizmoproject", - "gtalk","hcp","icon","ipn","irc","irc6","ircs","itms","jar","jms", - "keyparc","lastfm","ldaps","magnet","maps","market","message","mms", - "ms-help","msnim","mumble","mvn","notes","oid","palm","paparazzi", - "platform","proxy","psyc","query","res","resource","rmi","rsync", - "rtmp","secondlife","sftp","sgn","skype","smb","soldat","spotify", - "ssh","steam","svn","teamspeak","things","udp","unreal","ut2004", - "ventrilo","view-source","webcal","wtai","wyciwyg","xfire","xri", - "ymsgr", "isbn", "pmid"] - uriScheme :: Stream s m Char => ParserT s st m String -uriScheme = oneOfStringsCI schemes +uriScheme = oneOfStringsCI (Set.toList schemes) -- | Parses a URI. Returns pair of original and URI-escaped version. uri :: Stream [Char] m Char => ParserT [Char] st m (String, String) diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index ba2b20083..05c6c9a69 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -42,7 +42,6 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (macro, space, spaces, uri) import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI) ---import Network.URI (isURI) -- Not sure whether to use this function import Control.Monad (guard, void, when) import Control.Monad.Reader (Reader, asks, runReader) import Data.Default diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index f8ad43b1e..55df147b6 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -42,7 +42,7 @@ import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy as L import Data.Char (isAlphaNum, isAscii, toLower) import Data.List (isPrefixOf) -import Network.URI (URI (..), escapeURIString, isURI, parseURI) +import Network.URI (URI (..), escapeURIString, parseURI) import System.FilePath (takeDirectory, takeExtension, ()) import Text.HTML.TagSoup import Text.Pandoc.Class (PandocMonad (..), fetchItem, report) @@ -50,7 +50,7 @@ import Text.Pandoc.Error import Text.Pandoc.Logging import Text.Pandoc.MIME (MimeType) import Text.Pandoc.Options (WriterOptions (..)) -import Text.Pandoc.Shared (renderTags', trim) +import Text.Pandoc.Shared (isURI, renderTags', trim) import Text.Pandoc.UTF8 (toString) import Text.Parsec (ParsecT, runParserT) import qualified Text.Parsec as P diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 3a61656e5..7a1e6f3e3 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -81,6 +81,9 @@ module Text.Pandoc.Shared ( openURL, collapseFilePath, filteredFilesFromArchive, + -- * URI handling + schemes, + isURI, -- * Error handling mapLeft, -- * for squashing blocks @@ -104,7 +107,7 @@ import Data.List ( find, stripPrefix, intercalate ) import Data.Maybe (mapMaybe) import Data.Version ( showVersion ) import qualified Data.Map as M -import Network.URI ( escapeURIString, unEscapeString ) +import Network.URI ( URI(uriScheme), escapeURIString, unEscapeString, parseURI ) import qualified Data.Set as Set import System.Directory import System.FilePath (splitDirectories, isPathSeparator) @@ -774,6 +777,70 @@ filteredFilesFromArchive zf f = fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString) fileAndBinary a fp = findEntryByPath fp a >>= \e -> Just (fp, fromEntry e) + +-- +-- IANA URIs +-- + +-- | Schemes from http://www.iana.org/assignments/uri-schemes.html plus +-- the unofficial schemes doi, javascript, isbn, pmid. +schemes :: Set.Set String +schemes = Set.fromList + -- Official IANA schemes + [ "aaa", "aaas", "about", "acap", "acct", "acr", "adiumxtra", "afp", "afs" + , "aim", "appdata", "apt", "attachment", "aw", "barion", "beshare", "bitcoin" + , "blob", "bolo", "browserext", "callto", "cap", "chrome", "chrome-extension" + , "cid", "coap", "coaps", "com-eventbrite-attendee", "content", "crid", "cvs" + , "data", "dav", "dict", "dis", "dlna-playcontainer", "dlna-playsingle" + , "dns", "dntp", "dtn", "dvb", "ed2k", "example", "facetime", "fax", "feed" + , "feedready", "file", "filesystem", "finger", "fish", "ftp", "geo", "gg" + , "git", "gizmoproject", "go", "gopher", "graph", "gtalk", "h323", "ham" + , "hcp", "http", "https", "hxxp", "hxxps", "hydrazone", "iax", "icap", "icon" + , "im", "imap", "info", "iotdisco", "ipn", "ipp", "ipps", "irc", "irc6" + , "ircs", "iris", "iris.beep", "iris.lwz", "iris.xpc", "iris.xpcs" + , "isostore", "itms", "jabber", "jar", "jms", "keyparc", "lastfm", "ldap" + , "ldaps", "lvlt", "magnet", "mailserver", "mailto", "maps", "market" + , "message", "mid", "mms", "modem", "mongodb", "moz", "ms-access" + , "ms-browser-extension", "ms-drive-to", "ms-enrollment", "ms-excel" + , "ms-gamebarservices", "ms-getoffice", "ms-help", "ms-infopath" + , "ms-media-stream-id", "ms-officeapp", "ms-project", "ms-powerpoint" + , "ms-publisher", "ms-search-repair", "ms-secondary-screen-controller" + , "ms-secondary-screen-setup", "ms-settings", "ms-settings-airplanemode" + , "ms-settings-bluetooth", "ms-settings-camera", "ms-settings-cellular" + , "ms-settings-cloudstorage", "ms-settings-connectabledevices" + , "ms-settings-displays-topology", "ms-settings-emailandaccounts" + , "ms-settings-language", "ms-settings-location", "ms-settings-lock" + , "ms-settings-nfctransactions", "ms-settings-notifications" + , "ms-settings-power", "ms-settings-privacy", "ms-settings-proximity" + , "ms-settings-screenrotation", "ms-settings-wifi", "ms-settings-workplace" + , "ms-spd", "ms-sttoverlay", "ms-transit-to", "ms-virtualtouchpad" + , "ms-visio", "ms-walk-to", "ms-whiteboard", "ms-whiteboard-cmd", "ms-word" + , "msnim", "msrp", "msrps", "mtqp", "mumble", "mupdate", "mvn", "news", "nfs" + , "ni", "nih", "nntp", "notes", "ocf", "oid", "onenote", "onenote-cmd" + , "opaquelocktoken", "pack", "palm", "paparazzi", "pkcs11", "platform", "pop" + , "pres", "prospero", "proxy", "pwid", "psyc", "qb", "query", "redis" + , "rediss", "reload", "res", "resource", "rmi", "rsync", "rtmfp", "rtmp" + , "rtsp", "rtsps", "rtspu", "secondlife", "service", "session", "sftp", "sgn" + , "shttp", "sieve", "sip", "sips", "skype", "smb", "sms", "smtp", "snews" + , "snmp", "soap.beep", "soap.beeps", "soldat", "spotify", "ssh", "steam" + , "stun", "stuns", "submit", "svn", "tag", "teamspeak", "tel", "teliaeid" + , "telnet", "tftp", "things", "thismessage", "tip", "tn3270", "tool", "turn" + , "turns", "tv", "udp", "unreal", "urn", "ut2004", "v-event", "vemmi" + , "ventrilo", "videotex", "vnc", "view-source", "wais", "webcal", "wpid" + , "ws", "wss", "wtai", "wyciwyg", "xcon", "xcon-userid", "xfire" + , "xmlrpc.beep", "xmlrpc.beeps", "xmpp", "xri", "ymsgr", "z39.50", "z39.50r" + , "z39.50s" + -- Inofficial schemes + , "doi", "isbn", "javascript", "pmid" + ] + +-- | Check if the string is a valid URL with a IANA or frequently used but +-- unofficial scheme (see @schemes@). +isURI :: String -> Bool +isURI = maybe False hasKnownScheme . parseURI + where + hasKnownScheme = (`Set.member` schemes) . filter (/= ':') . uriScheme + --- --- Squash blocks into inlines --- diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index eef16d3da..2d4502153 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -33,7 +33,7 @@ import Control.Monad.State import Data.Char (ord) import Data.List (intercalate, intersperse) import Data.Maybe (catMaybes) -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 81987dc44..1d02a9c40 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -44,13 +44,12 @@ import Control.Monad.Reader (ReaderT, ask, local, runReaderT) import Control.Monad.State (StateT, evalStateT, gets, modify) import Data.Default (Default (..)) import Data.List (intercalate, intersect, isPrefixOf, transpose) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition import Text.Pandoc.ImageSize import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, linesToPara, +import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara, removeFormatting, substitute, trimr) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared (defField, metaToJSON) diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 0926cc331..d450513bc 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -46,7 +46,6 @@ import Data.Char (isAscii, isControl, isSpace, toLower) import Data.Either (lefts, rights) import Data.List (intercalate, intersperse, isPrefixOf, stripPrefix) import Network.HTTP (urlEncode) -import Network.URI (isURI) import Text.XML.Light import qualified Text.XML.Light as X import qualified Text.XML.Light.Cursor as XC @@ -57,7 +56,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Error import Text.Pandoc.Logging import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def) -import Text.Pandoc.Shared (capitalize, isHeaderBlock, linesToPara, +import Text.Pandoc.Shared (capitalize, isHeaderBlock, isURI, linesToPara, orderedListMarkers) -- | Data to be written at the end of the document: diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 812b46c30..cbbe5bdb4 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -36,7 +36,6 @@ module Text.Pandoc.Writers.Haddock (writeHaddock) where import Control.Monad.State import Data.Default import Data.List (intersperse, transpose) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Logging diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 2f7a4889f..f36a32015 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -21,7 +21,6 @@ import Control.Monad.State import Data.List (intersperse, isInfixOf, isPrefixOf, stripPrefix) import qualified Data.Set as Set import Data.Text as Text (breakOnAll, pack) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition @@ -29,7 +28,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty -import Text.Pandoc.Shared (linesToPara, splitBy) +import Text.Pandoc.Shared (isURI, linesToPara, splitBy) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 31c70e99d..2b3d7c878 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -43,7 +43,7 @@ import Data.List (foldl', intercalate, intersperse, isInfixOf, nub, nubBy, stripPrefix, (\\)) import Data.Maybe (catMaybes, fromMaybe, isJust) import qualified Data.Text as T -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight, diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index b70716181..e858bc43f 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -49,7 +49,6 @@ import qualified Data.Text as T import qualified Data.Vector as V import Data.Yaml (Value (Array, Bool, Number, Object, String)) import Network.HTTP (urlEncode) -import Network.URI (isURI) import Text.HTML.TagSoup (Tag (..), isTagText, parseTags) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 439bbb2f9..aa5c3bc4f 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -34,7 +34,6 @@ import Control.Monad.Reader import Control.Monad.State import Data.List (intercalate) import qualified Data.Set as Set -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 5dc2ba31a..b88fc2245 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -35,7 +35,6 @@ import Control.Monad.State import Data.Char (isSpace, toLower) import Data.List (isPrefixOf, stripPrefix) import Data.Maybe (fromMaybe) -import Network.URI (isURI) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 9926daea1..710e1dea0 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -37,7 +37,7 @@ import Data.Char (chr, ord) import Data.List (maximumBy, transpose) import Data.Ord (comparing) import qualified Data.Set as Set -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import System.FilePath import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index bc2cf8f3c..4ab8bde30 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -38,14 +38,13 @@ import Data.Default (Default (..)) import Data.List (intercalate, isInfixOf, isPrefixOf, transpose) import qualified Data.Map as Map import Data.Text (breakOnAll, pack) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition import Text.Pandoc.ImageSize import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (escapeURI, linesToPara, removeFormatting, substitute, - trimr) +import Text.Pandoc.Shared (isURI, escapeURI, linesToPara, removeFormatting, + substitute, trimr) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared (defField, metaToJSON) -- cgit v1.2.3 From 66fa38ed1c27935fc57677d9c63ac9263958e3fd Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 23 May 2017 09:49:56 +0200 Subject: Shared.isURI: allow uppercase versions of known schemes. --- src/Text/Pandoc/Shared.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 7a1e6f3e3..a6c6fb95f 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -839,7 +839,8 @@ schemes = Set.fromList isURI :: String -> Bool isURI = maybe False hasKnownScheme . parseURI where - hasKnownScheme = (`Set.member` schemes) . filter (/= ':') . uriScheme + hasKnownScheme = (`Set.member` schemes) . map toLower . + filter (/= ':') . uriScheme --- --- Squash blocks into inlines -- cgit v1.2.3 From 8edeaa9349474e3c87b9515664e597db2d32df8f Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 23 May 2017 16:58:24 +0200 Subject: Fixed handling of soft hyphen (0173) in docx writer. Closes #3691. --- src/Text/Pandoc/Writers/Docx.hs | 26 +++++++++++++++++++------- 1 file changed, 19 insertions(+), 7 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 2282a5c58..a10840033 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1059,13 +1059,24 @@ withParaPropM :: PandocMonad m => WS m Element -> WS m a -> WS m a withParaPropM = (. flip withParaProp) . (>>=) formattedString :: PandocMonad m => String -> WS m [Element] -formattedString str = do - props <- getTextProps +formattedString str = + -- properly handle soft hyphens + case splitBy (=='\173') str of + [w] -> formattedString' w + ws -> do + sh <- formattedRun [mknode "w:softHyphen" [] ()] + (intercalate sh) <$> mapM formattedString' ws + +formattedString' :: PandocMonad m => String -> WS m [Element] +formattedString' str = do inDel <- asks envInDel - return [ mknode "w:r" [] $ - props ++ - [ mknode (if inDel then "w:delText" else "w:t") - [("xml:space","preserve")] (stripInvalidChars str) ] ] + formattedRun [ mknode (if inDel then "w:delText" else "w:t") + [("xml:space","preserve")] (stripInvalidChars str) ] + +formattedRun :: PandocMonad m => [Element] -> WS m [Element] +formattedRun els = do + props <- getTextProps + return [ mknode "w:r" [] $ props ++ els ] setFirstPara :: PandocMonad m => WS m () setFirstPara = modify $ \s -> s { stFirstPara = True } @@ -1075,7 +1086,8 @@ inlineToOpenXML :: PandocMonad m => WriterOptions -> Inline -> WS m [Element] inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il inlineToOpenXML' :: PandocMonad m => WriterOptions -> Inline -> WS m [Element] -inlineToOpenXML' _ (Str str) = formattedString str +inlineToOpenXML' _ (Str str) = + formattedString str inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ") inlineToOpenXML' opts SoftBreak = inlineToOpenXML opts (Str " ") inlineToOpenXML' opts (Span (ident,classes,kvs) ils) = do -- cgit v1.2.3 From c0c54b79063379dc8534a88b4a9cccbe7c9a3b80 Mon Sep 17 00:00:00 2001 From: keiichiro shikano Date: Wed, 24 May 2017 03:53:04 +0900 Subject: RST Reader: parse list table directive (#3688) Closes #3432. --- src/Text/Pandoc/Readers/RST.hs | 29 ++++- test/command/3432.md | 289 +++++++++++++++++++++++++++++++++++++++++ 2 files changed, 317 insertions(+), 1 deletion(-) create mode 100644 test/command/3432.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index ac1f4f834..c835ecf52 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -58,7 +58,6 @@ import Text.Printf (printf) -- [ ] .. parsed-literal -- [ ] :widths: attribute in .. table -- [ ] .. csv-table --- [ ] .. list-table -- | Parse reStructuredText string and return Pandoc document. readRST :: PandocMonad m @@ -676,6 +675,7 @@ directive' = do (lengthToDim . filter (not . isSpace)) case label of "table" -> tableDirective top fields body' + "list-table" -> listTableDirective top fields body' "line-block" -> lineBlockDirective body' "raw" -> return $ B.rawBlock (trim top) (stripTrailingNewlines body) "role" -> addNewRole top $ map (\(k,v) -> (k, trim v)) fields @@ -762,6 +762,33 @@ tableDirective top _fields body = do aligns' widths' header' rows' _ -> return mempty + +-- TODO: :stub-columns:. +-- Only the first row becomes the header even if header-rows: > 1, since Pandoc doesn't support a table with multiple header rows. +-- We don't need to parse :align: as it represents the whole table align. +listTableDirective :: PandocMonad m => String -> [(String, String)] -> String -> RSTParser m Blocks +listTableDirective top fields body = do + bs <- parseFromString parseBlocks body + title <- parseFromString (trimInlines . mconcat <$> many inline) top + let rows = takeRows $ B.toList bs + headerRowsNum = fromMaybe (0 :: Int) $ lookup "header-rows" fields >>= safeRead + (headerRow,bodyRows,numOfCols) = case rows of + x:xs -> if headerRowsNum > 0 then (x, xs, length x) else ([], rows, length x) + _ -> ([],[],0) + widths = case trim <$> lookup "widths" fields of + Just "auto" -> replicate numOfCols 0 + Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $ splitBy (`elem` (" ," :: String)) specs + _ -> replicate numOfCols 0 + return $ B.table title + (zip (replicate numOfCols AlignDefault) widths) + headerRow + bodyRows + where takeRows [BulletList rows] = map takeCells rows + takeRows _ = [] + takeCells [BulletList cells] = map B.fromList cells + takeCells _ = [] + normWidths ws = map (/ max 1 (sum ws)) ws + -- TODO: -- - Only supports :format: fields with a single format for :raw: roles, -- change Text.Pandoc.Definition.Format to fix diff --git a/test/command/3432.md b/test/command/3432.md new file mode 100644 index 000000000..7264d22c3 --- /dev/null +++ b/test/command/3432.md @@ -0,0 +1,289 @@ +List-table with header-rows and widths options. + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + :widths: 15 10 30 + :header-rows: 1 + + * - Treat + - Quantity + - Description + * - Albatross + - 2.99 + - On a stick! + * - Crunchy Frog + - 1.49 + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + +++++ + + + + + + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
TreatQuantityDescription
Albatross2.99On a stick!
Crunchy Frog1.49If we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` + +List-table whose widths is "auto". + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + :header-rows: 1 + :widths: auto + + * - Treat + - Quantity + - Description + * - Albatross + - 2.99 + - On a stick! + * - Crunchy Frog + - 1.49 + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + + + + + + + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
TreatQuantityDescription
Albatross2.99On a stick!
Crunchy Frog1.49If we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` + + +List-table with header-rows which is bigger than 1. Only the first row is treated as a header. + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + :header-rows: 2 + + * - Treat + - Quantity + - Description + * - Albatross + - 2.99 + - On a stick! + * - Crunchy Frog + - 1.49 + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + + + + + + + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
TreatQuantityDescription
Albatross2.99On a stick!
Crunchy Frog1.49If we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` + +List-table without header-rows. + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + + * - Albatross + - 2.99 + - On a stick! + * - Crunchy Frog + - 1.49 + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
Albatross2.99On a stick!
Crunchy Frog1.49If we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` + +List-table with empty cells. You need a space after '-', otherwise the row will disapear. Parser for Bulletlists causes this ristriction. + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + :header-rows: 2 + + * - Treat + - Quantity + - Description + * - Albatross + - 2.99 + - + * - Crunchy Frog + - + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + + + + + + + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
TreatQuantityDescription
Albatross2.99
Crunchy FrogIf we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` + +List-table with a cell having a bulletlist + +``` +% pandoc -f rst +.. list-table:: Frozen Delights! + + * - Albatross + - 2.99 + - + On a stick! + + In a cup! + * - Crunchy Frog + - 1.49 + - If we took the bones out, it wouldn't be + crunchy, now would it? + * - Gannet Ripple + - 1.99 + - On a stick! +^D + + + + + + + + + + + + + + + + + + + +
Frozen Delights!
Albatross2.99
    +
  • On a stick!
  • +
  • In a cup!
  • +
Crunchy Frog1.49If we took the bones out, it wouldn't be crunchy, now would it?
Gannet Ripple1.99On a stick!
+``` -- cgit v1.2.3 From 5844af67b41606d6da15e14c9b7dd6cedb17321e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 23 May 2017 21:00:51 +0200 Subject: RST reader: reformatting (code line length). --- src/Text/Pandoc/Readers/RST.hs | 70 ++++++++++++++++++++++++++++-------------- 1 file changed, 47 insertions(+), 23 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index c835ecf52..e3780f89b 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -35,8 +35,8 @@ import Control.Monad (guard, liftM, mzero, when) import Control.Monad.Identity (Identity(..)) import Control.Monad.Except (throwError) import Data.Char (isHexDigit, isSpace, toLower, toUpper) -import Data.List (deleteFirstsBy, findIndex, intercalate, isInfixOf, isSuffixOf, - nub, sort, transpose, union) +import Data.List (deleteFirstsBy, findIndex, intercalate, isInfixOf, + isSuffixOf, nub, sort, transpose, union) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust) import Data.Monoid ((<>)) @@ -131,7 +131,10 @@ metaFromDefList ds meta = adjustAuthors $ foldr f meta ds adjustAuthors (Meta metamap) = Meta $ M.adjust splitAuthors "author" $ M.adjust toPlain "date" $ M.adjust toPlain "title" - $ M.mapKeys (\k -> if k == "authors" then "author" else k) + $ M.mapKeys (\k -> + if k == "authors" + then "author" + else k) $ metamap toPlain (MetaBlocks [Para xs]) = MetaInlines xs toPlain x = x @@ -595,10 +598,14 @@ listItem start = try $ do parsed <- parseFromString parseBlocks $ concat (first:rest) ++ "\n" updateState (\st -> st {stateParserContext = oldContext}) return $ case B.toList parsed of - [Para xs] -> B.singleton $ Plain xs - [Para xs, BulletList ys] -> B.fromList [Plain xs, BulletList ys] - [Para xs, OrderedList s ys] -> B.fromList [Plain xs, OrderedList s ys] - [Para xs, DefinitionList ys] -> B.fromList [Plain xs, DefinitionList ys] + [Para xs] -> + B.singleton $ Plain xs + [Para xs, BulletList ys] -> + B.fromList [Plain xs, BulletList ys] + [Para xs, OrderedList s ys] -> + B.fromList [Plain xs, OrderedList s ys] + [Para xs, DefinitionList ys] -> + B.fromList [Plain xs, DefinitionList ys] _ -> parsed orderedList :: PandocMonad m => RSTParser m Blocks @@ -726,7 +733,8 @@ directive' = do "figure" -> do (caption, legend) <- parseFromString extractCaption body' let src = escapeURI $ trim top - return $ B.para (B.imageWith (imgAttr "figclass") src "fig:" caption) <> legend + return $ B.para (B.imageWith (imgAttr "figclass") src "fig:" + caption) <> legend "image" -> do let src = escapeURI $ trim top let alt = B.str $ maybe "image" trim $ lookup "alt" fields @@ -737,7 +745,8 @@ directive' = do $ B.imageWith attr src "" alt Nothing -> B.imageWith attr src "" alt "class" -> do - let attrs = ("", (splitBy isSpace $ trim top), map (\(k,v) -> (k, trimr v)) fields) + let attrs = ("", (splitBy isSpace $ trim top), + map (\(k,v) -> (k, trimr v)) fields) -- directive content or the first immediately following element children <- case body of "" -> block @@ -764,20 +773,27 @@ tableDirective top _fields body = do -- TODO: :stub-columns:. --- Only the first row becomes the header even if header-rows: > 1, since Pandoc doesn't support a table with multiple header rows. --- We don't need to parse :align: as it represents the whole table align. -listTableDirective :: PandocMonad m => String -> [(String, String)] -> String -> RSTParser m Blocks +-- Only the first row becomes the header even if header-rows: > 1, +-- since Pandoc doesn't support a table with multiple header rows. +-- We don't need to parse :align: as it represents the whole table align. +listTableDirective :: PandocMonad m + => String -> [(String, String)] -> String + -> RSTParser m Blocks listTableDirective top fields body = do bs <- parseFromString parseBlocks body title <- parseFromString (trimInlines . mconcat <$> many inline) top let rows = takeRows $ B.toList bs - headerRowsNum = fromMaybe (0 :: Int) $ lookup "header-rows" fields >>= safeRead + headerRowsNum = fromMaybe (0 :: Int) $ + lookup "header-rows" fields >>= safeRead (headerRow,bodyRows,numOfCols) = case rows of - x:xs -> if headerRowsNum > 0 then (x, xs, length x) else ([], rows, length x) + x:xs -> if headerRowsNum > 0 + then (x, xs, length x) + else ([], rows, length x) _ -> ([],[],0) widths = case trim <$> lookup "widths" fields of Just "auto" -> replicate numOfCols 0 - Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $ splitBy (`elem` (" ," :: String)) specs + Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $ + splitBy (`elem` (" ," :: String)) specs _ -> replicate numOfCols 0 return $ B.table title (zip (replicate numOfCols AlignDefault) widths) @@ -792,7 +808,8 @@ listTableDirective top fields body = do -- TODO: -- - Only supports :format: fields with a single format for :raw: roles, -- change Text.Pandoc.Definition.Format to fix -addNewRole :: PandocMonad m => String -> [(String, String)] -> RSTParser m Blocks +addNewRole :: PandocMonad m + => String -> [(String, String)] -> RSTParser m Blocks addNewRole roleString fields = do pos <- getPosition (role, parentRole) <- parseFromString inheritedRole roleString @@ -822,7 +839,8 @@ addNewRole roleString fields = do SkippedContent ":format: [because parent of role is not :raw:]" pos _ -> logMessage $ SkippedContent (":" ++ key ++ ":") pos when (parentRole == "raw" && countKeys "format" > 1) $ - logMessage $ SkippedContent ":format: [after first in definition of role]" + logMessage $ SkippedContent + ":format: [after first in definition of role]" pos when (parentRole == "code" && countKeys "language" > 1) $ logMessage $ SkippedContent @@ -837,7 +855,8 @@ addNewRole roleString fields = do where countKeys k = length . filter (== k) . map fst $ fields inheritedRole = - (,) <$> roleName <*> ((char '(' *> roleName <* char ')') <|> pure "span") + (,) <$> roleName <*> ((char '(' *> roleName <* char ')') + <|> pure "span") -- Can contain character codes as decimal numbers or @@ -1014,7 +1033,8 @@ substKey = try $ do [Para ils] -> return $ B.fromList ils _ -> mzero let key = toKey $ stripFirstAndLast ref - updateState $ \s -> s{ stateSubstitutions = M.insert key il $ stateSubstitutions s } + updateState $ \s -> s{ stateSubstitutions = + M.insert key il $ stateSubstitutions s } anonymousKey :: Monad m => RSTParser m () anonymousKey = try $ do @@ -1023,7 +1043,8 @@ anonymousKey = try $ do pos <- getPosition let key = toKey $ "_" ++ printf "%09d" (sourceLine pos) --TODO: parse width, height, class and name attributes - updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ stateKeys s } + updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ + stateKeys s } stripTicks :: String -> String stripTicks = reverse . stripTick . reverse . stripTick @@ -1038,7 +1059,8 @@ regularKey = try $ do src <- targetURI let key = toKey $ stripTicks ref --TODO: parse width, height, class and name attributes - updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ stateKeys s } + updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ + stateKeys s } headerBlock :: PandocMonad m => RSTParser m [Char] headerBlock = do @@ -1243,7 +1265,8 @@ interpretedRole = try $ do (role, contents) <- roleBefore <|> roleAfter renderRole contents Nothing role nullAttr -renderRole :: PandocMonad m => String -> Maybe String -> String -> Attr -> RSTParser m Inlines +renderRole :: PandocMonad m + => String -> Maybe String -> String -> Attr -> RSTParser m Inlines renderRole contents fmt role attr = case role of "sup" -> return $ B.superscript $ B.str contents "superscript" -> return $ B.superscript $ B.str contents @@ -1376,7 +1399,8 @@ referenceLink = try $ do (k:_) -> return k ((src,tit), attr) <- lookupKey [] key -- if anonymous link, remove key so it won't be used again - when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable } + when (isAnonKey key) $ updateState $ \s -> + s{ stateKeys = M.delete key keyTable } return $ B.linkWith attr src tit label' -- We keep a list of oldkeys so we can detect lookup loops. -- cgit v1.2.3 From 7174776c19476701933df83ce4f2689a967a1a0a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 12:11:12 +0200 Subject: HTML reader: Add `details` tag to list of block tags. Closes #3694. --- src/Text/Pandoc/Readers/HTML.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 650454ae6..23af6171e 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -887,7 +887,8 @@ inlineHtmlTags = ["a", "abbr", "acronym", "b", "basefont", "bdo", "big", blockHtmlTags :: [String] blockHtmlTags = ["?xml", "!DOCTYPE", "address", "article", "aside", "blockquote", "body", "button", "canvas", - "caption", "center", "col", "colgroup", "dd", "dir", "div", + "caption", "center", "col", "colgroup", "dd", "details", + "dir", "div", "dl", "dt", "fieldset", "figcaption", "figure", "footer", "form", "h1", "h2", "h3", "h4", "h5", "h6", "head", "header", "hgroup", "hr", "html", -- cgit v1.2.3 From 19d3a2bbe5291dcba0bdba9f6faf0103f5f47245 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 21:46:43 +0200 Subject: Logging: Made SkippedContent WARNING not INFO. --- src/Text/Pandoc/Logging.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index bf7f33d29..70384f936 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -252,7 +252,7 @@ showLogMessage msg = messageVerbosity:: LogMessage -> Verbosity messageVerbosity msg = case msg of - SkippedContent{} -> INFO + SkippedContent{} -> WARNING CouldNotParseYamlMetadata{} -> WARNING DuplicateLinkReference{} -> WARNING DuplicateNoteReference{} -> WARNING -- cgit v1.2.3 From 1288a50380e01ac50818033a16cc9146f373bdde Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 21:46:53 +0200 Subject: LaTeX reader: parse tikzpicture as raw verbatim environment... if `raw_tex` extension is selected. Otherwise skip with a warning. This is better than trying to parse it as text! Closes #3692. --- src/Text/Pandoc/Readers/LaTeX.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 84758d309..af7c1d9b7 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1031,6 +1031,19 @@ rawEnv name = do report $ SkippedContent ("\\end{" ++ name ++ "}") pos2 return bs +rawVerbEnv :: PandocMonad m => String -> LP m Blocks +rawVerbEnv name = do + pos <- getPosition + (_, raw) <- withRaw $ verbEnv name + let raw' = "\\begin{tikzpicture}" ++ raw + exts <- getOption readerExtensions + let parseRaw = extensionEnabled Ext_raw_tex exts + if parseRaw + then return $ rawBlock "latex" raw' + else do + report $ SkippedContent raw' pos + return mempty + ---- maybeAddExtension :: String -> FilePath -> FilePath @@ -1200,6 +1213,7 @@ environments = M.fromList , ("align*", mathEnvWith para (Just "aligned") "align*") , ("alignat", mathEnvWith para (Just "aligned") "alignat") , ("alignat*", mathEnvWith para (Just "aligned") "alignat*") + , ("tikzpicture", rawVerbEnv "tikzpicture") ] figure :: PandocMonad m => LP m Blocks -- cgit v1.2.3 From bc6aac7b474495c4433c31bcd4a3570057edb850 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 22:41:47 +0200 Subject: Parsing: Provide parseFromString'. This is a verison of parseFromString specialied to ParserState, which resets stateLastStrPos at the end. This is almost always what we want. This fixes a bug where `_hi_` wasn't treated as emphasis in the following, because pandoc got confused about the position of the last word: - [o] _hi_ Closes #3690. --- src/Text/Pandoc/Parsing.hs | 18 ++++++++++++- src/Text/Pandoc/Readers/LaTeX.hs | 12 ++++----- src/Text/Pandoc/Readers/Markdown.hs | 40 +++++++++++++++-------------- src/Text/Pandoc/Readers/RST.hs | 50 ++++++++++++++++++------------------- src/Text/Pandoc/Readers/TWiki.hs | 8 +++--- src/Text/Pandoc/Readers/Textile.hs | 8 +++--- src/Text/Pandoc/Readers/Txt2Tags.hs | 6 ++--- test/command/3690.md | 8 ++++++ 8 files changed, 88 insertions(+), 62 deletions(-) create mode 100644 test/command/3690.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index c6be48d19..e6157dde3 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -50,6 +50,7 @@ module Text.Pandoc.Parsing ( anyLine, enclosed, stringAnyCase, parseFromString, + parseFromString', lineClump, charsInBalanced, romanNumeral, @@ -358,7 +359,10 @@ stringAnyCase (x:xs) = do return (firstChar:rest) -- | Parse contents of 'str' using 'parser' and return result. -parseFromString :: Monad m => ParserT String st m a -> String -> ParserT String st m a +parseFromString :: Monad m + => ParserT String st m a + -> String + -> ParserT String st m a parseFromString parser str = do oldPos <- getPosition oldInput <- getInput @@ -370,6 +374,18 @@ parseFromString parser str = do setPosition oldPos return result +-- | Like 'parseFromString' but specialized for 'ParserState'. +-- This resets 'stateLastStrPos', which is almost always what we want. +parseFromString' :: Monad m + => ParserT String ParserState m a + -> String + -> ParserT String ParserState m a +parseFromString' parser str = do + oldStrPos <- stateLastStrPos <$> getState + res <- parseFromString parser str + updateState $ \st -> st{ stateLastStrPos = oldStrPos } + return res + -- | Parse raw line block up to and including blank lines. lineClump :: Stream [Char] m Char => ParserT [Char] st m String lineClump = blanklines diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index af7c1d9b7..88be40e3e 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -304,8 +304,8 @@ blockCommand = try $ do rawcommand <- getRawCommand name' transformed <- applyMacros' rawcommand guard $ transformed /= rawcommand - notFollowedBy $ parseFromString inlines transformed - parseFromString blocks transformed + notFollowedBy $ parseFromString' inlines transformed + parseFromString' blocks transformed lookupListDefault raw [name',name] blockCommands inBrackets :: Inlines -> Inlines @@ -475,7 +475,7 @@ inlineCommand = try $ do transformed <- applyMacros' rawcommand exts <- getOption readerExtensions if transformed /= rawcommand - then parseFromString inlines transformed + then parseFromString' inlines transformed else if extensionEnabled Ext_raw_tex exts then return $ rawInline "latex" rawcommand else ignore rawcommand @@ -1021,7 +1021,7 @@ rawEnv name = do (bs, raw) <- withRaw $ env name blocks raw' <- applyMacros' $ beginCommand ++ raw if raw' /= beginCommand ++ raw - then parseFromString blocks raw' + then parseFromString' blocks raw' else if parseRaw then return $ rawBlock "latex" $ beginCommand ++ raw' else do @@ -1119,7 +1119,7 @@ keyvals :: PandocMonad m => LP m [(String, String)] keyvals = try $ char '[' *> manyTill keyval (char ']') alltt :: PandocMonad m => String -> LP m Blocks -alltt t = walk strToCode <$> parseFromString blocks +alltt t = walk strToCode <$> parseFromString' blocks (substitute " " "\\ " $ substitute "%" "\\%" $ intercalate "\\\\\n" $ lines t) where strToCode (Str s) = Code nullAttr s @@ -1503,7 +1503,7 @@ parseTableRow cols prefixes suffixes = try $ do guard $ length rawcells == cols let rawcells' = zipWith3 (\c p s -> p ++ trim c ++ s) rawcells prefixes suffixes - cells' <- mapM (parseFromString tableCell) rawcells' + cells' <- mapM (parseFromString' tableCell) rawcells' let numcells = length cells' guard $ numcells <= cols && numcells >= 1 guard $ cells' /= [mempty] diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index af7588562..17a7184c0 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -155,9 +155,11 @@ litChar = escapedChar' inlinesInBalancedBrackets :: PandocMonad m => MarkdownParser m (F Inlines) inlinesInBalancedBrackets = do char '[' + pos <- getPosition (_, raw) <- withRaw $ charsInBalancedBrackets 1 guard $ not $ null raw - parseFromString (trimInlinesF . mconcat <$> many inline) (init raw) + parseFromString' (setPosition pos >> + trimInlinesF . mconcat <$> many inline) (init raw) charsInBalancedBrackets :: PandocMonad m => Int -> MarkdownParser m () charsInBalancedBrackets 0 = return () @@ -189,7 +191,7 @@ rawTitleBlockLine = do titleLine :: PandocMonad m => MarkdownParser m (F Inlines) titleLine = try $ do raw <- rawTitleBlockLine - res <- parseFromString (many inline) raw + res <- parseFromString' (many inline) raw return $ trimInlinesF $ mconcat res authorsLine :: PandocMonad m => MarkdownParser m (F [Inlines]) @@ -200,12 +202,12 @@ authorsLine = try $ do (trimInlinesF . mconcat <$> many (try $ notFollowedBy sep >> inline)) sep - sequence <$> parseFromString pAuthors raw + sequence <$> parseFromString' pAuthors raw dateLine :: PandocMonad m => MarkdownParser m (F Inlines) dateLine = try $ do raw <- rawTitleBlockLine - res <- parseFromString (many inline) raw + res <- parseFromString' (many inline) raw return $ trimInlinesF $ mconcat res titleBlock :: PandocMonad m => MarkdownParser m () @@ -290,7 +292,7 @@ ignorable t = (T.pack "_") `T.isSuffixOf` t toMetaValue :: PandocMonad m => Text -> MarkdownParser m (F MetaValue) -toMetaValue x = toMeta <$> parseFromString parseBlocks (T.unpack x) +toMetaValue x = toMeta <$> parseFromString' parseBlocks (T.unpack x) where toMeta p = do p' <- p @@ -466,7 +468,7 @@ noteBlock = try $ do rest <- many $ try $ blanklines >> indentSpaces >> rawLines let raw = unlines (first:rest) ++ "\n" optional blanklines - parsed <- parseFromString parseBlocks raw + parsed <- parseFromString' parseBlocks raw let newnote = (ref, parsed) oldnotes <- stateNotes' <$> getState case lookup ref oldnotes of @@ -774,7 +776,7 @@ blockQuote :: PandocMonad m => MarkdownParser m (F Blocks) blockQuote = do raw <- emailBlockQuote -- parse the extracted block, which may contain various block elements: - contents <- parseFromString parseBlocks $ (intercalate "\n" raw) ++ "\n\n" + contents <- parseFromString' parseBlocks $ (intercalate "\n" raw) ++ "\n\n" return $ B.blockQuote <$> contents -- @@ -887,7 +889,7 @@ listItem start = try $ do setState $ state {stateParserContext = ListItemState} -- parse the extracted block, which may contain various block elements: let raw = concat (first:continuations) - contents <- parseFromString parseBlocks raw + contents <- parseFromString' parseBlocks raw updateState (\st -> st {stateParserContext = oldContext}) return contents @@ -934,8 +936,8 @@ definitionListItem :: PandocMonad m => Bool -> MarkdownParser m (F (Inlines, [Bl definitionListItem compact = try $ do rawLine' <- anyLine raw <- many1 $ defRawBlock compact - term <- parseFromString (trimInlinesF . mconcat <$> many inline) rawLine' - contents <- mapM (parseFromString parseBlocks . (++"\n")) raw + term <- parseFromString' (trimInlinesF . mconcat <$> many inline) rawLine' + contents <- mapM (parseFromString' parseBlocks . (++"\n")) raw optional blanklines return $ liftM2 (,) term (sequence contents) @@ -1127,7 +1129,7 @@ lineBlock :: PandocMonad m => MarkdownParser m (F Blocks) lineBlock = try $ do guardEnabled Ext_line_blocks lines' <- lineBlockLines >>= - mapM (parseFromString (trimInlinesF . mconcat <$> many inline)) + mapM (parseFromString' (trimInlinesF . mconcat <$> many inline)) return $ B.lineBlock <$> sequence lines' -- @@ -1170,7 +1172,7 @@ simpleTableHeader headless = try $ do then replicate (length dashes) "" else rawHeads heads <- fmap sequence - $ mapM (parseFromString (mconcat <$> many plain)) + $ mapM (parseFromString' (mconcat <$> many plain)) $ map trim rawHeads' return (heads, aligns, indices) @@ -1216,7 +1218,7 @@ tableLine :: PandocMonad m => [Int] -> MarkdownParser m (F [Blocks]) tableLine indices = rawTableLine indices >>= - fmap sequence . mapM (parseFromString (mconcat <$> many plain)) + fmap sequence . mapM (parseFromString' (mconcat <$> many plain)) -- Parse a multiline table row and return a list of blocks (columns). multilineRow :: PandocMonad m @@ -1225,7 +1227,7 @@ multilineRow :: PandocMonad m multilineRow indices = do colLines <- many1 (rawTableLine indices) let cols = map unlines $ transpose colLines - fmap sequence $ mapM (parseFromString (mconcat <$> many plain)) cols + fmap sequence $ mapM (parseFromString' (mconcat <$> many plain)) cols -- Parses a table caption: inlines beginning with 'Table:' -- and followed by blank lines. @@ -1283,7 +1285,7 @@ multilineTableHeader headless = try $ do then replicate (length dashes) "" else map (unlines . map trim) rawHeadsList heads <- fmap sequence $ - mapM (parseFromString (mconcat <$> many plain)) $ + mapM (parseFromString' (mconcat <$> many plain)) $ map trim rawHeads return (heads, aligns, indices) @@ -1340,7 +1342,7 @@ pipeTableRow = try $ do let chunk = void (code <|> math <|> rawHtmlInline <|> escapedChar <|> rawLaTeXInline') <|> void (noneOf "|\n\r") let cellContents = ((trim . snd) <$> withRaw (many chunk)) >>= - parseFromString pipeTableCell + parseFromString' pipeTableCell cells <- cellContents `sepEndBy1` (char '|') -- surrounding pipes needed for a one-column table: guard $ not (length cells == 1 && not openPipe) @@ -1747,8 +1749,8 @@ referenceLink constructor (lab, raw) = do when (raw' == "") $ guardEnabled Ext_shortcut_reference_links let labIsRef = raw' == "" || raw' == "[]" let key = toKey $ if labIsRef then raw else raw' - parsedRaw <- parseFromString (mconcat <$> many inline) raw' - fallback <- parseFromString (mconcat <$> many inline) $ dropBrackets raw + parsedRaw <- parseFromString' (mconcat <$> many inline) raw' + fallback <- parseFromString' (mconcat <$> many inline) $ dropBrackets raw implicitHeaderRefs <- option False $ True <$ guardEnabled Ext_implicit_header_references let makeFallback = do @@ -1954,7 +1956,7 @@ textualCite = try $ do let (spaces',raw') = span isSpace raw spc | null spaces' = mempty | otherwise = B.space - lab <- parseFromString (mconcat <$> many inline) $ dropBrackets raw' + lab <- parseFromString' (mconcat <$> many inline) $ dropBrackets raw' fallback <- referenceLink B.linkWith (lab,raw') return $ do fallback' <- fallback diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index e3780f89b..1ea142112 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -196,7 +196,7 @@ parseRST = do parseCitation :: PandocMonad m => (String, String) -> RSTParser m (Inlines, [Blocks]) parseCitation (ref, raw) = do - contents <- parseFromString parseBlocks raw + contents <- parseFromString' parseBlocks raw return $ (B.spanWith (ref, ["citation-label"], []) (B.str ref), [contents]) @@ -246,7 +246,7 @@ fieldListItem :: PandocMonad m => Int -> RSTParser m (Inlines, [Blocks]) fieldListItem minIndent = try $ do (name, raw) <- rawFieldListItem minIndent term <- parseInlineFromString name - contents <- parseFromString parseBlocks raw + contents <- parseFromString' parseBlocks raw optional blanklines return (term, [contents]) @@ -445,7 +445,7 @@ blockQuote :: PandocMonad m => RSTParser m Blocks blockQuote = do raw <- indentedBlock -- parse the extracted block, which may contain various block elements: - contents <- parseFromString parseBlocks $ raw ++ "\n\n" + contents <- parseFromString' parseBlocks $ raw ++ "\n\n" return $ B.blockQuote contents {- @@ -533,7 +533,7 @@ definitionListItem = try $ do term <- trimInlines . mconcat <$> many1Till inline endline raw <- indentedBlock -- parse the extracted block, which may contain various block elements: - contents <- parseFromString parseBlocks $ raw ++ "\n" + contents <- parseFromString' parseBlocks $ raw ++ "\n" return (term, [contents]) definitionList :: PandocMonad m => RSTParser m Blocks @@ -595,7 +595,7 @@ listItem start = try $ do let oldContext = stateParserContext state setState $ state {stateParserContext = ListItemState} -- parse the extracted block, which may itself contain block elements - parsed <- parseFromString parseBlocks $ concat (first:rest) ++ "\n" + parsed <- parseFromString' parseBlocks $ concat (first:rest) ++ "\n" updateState (\st -> st {stateParserContext = oldContext}) return $ case B.toList parsed of [Para xs] -> @@ -686,19 +686,19 @@ directive' = do "line-block" -> lineBlockDirective body' "raw" -> return $ B.rawBlock (trim top) (stripTrailingNewlines body) "role" -> addNewRole top $ map (\(k,v) -> (k, trim v)) fields - "container" -> parseFromString parseBlocks body' + "container" -> parseFromString' parseBlocks body' "replace" -> B.para <$> -- consumed by substKey parseInlineFromString (trim top) "unicode" -> B.para <$> -- consumed by substKey parseInlineFromString (trim $ unicodeTransform top) - "compound" -> parseFromString parseBlocks body' - "pull-quote" -> B.blockQuote <$> parseFromString parseBlocks body' - "epigraph" -> B.blockQuote <$> parseFromString parseBlocks body' - "highlights" -> B.blockQuote <$> parseFromString parseBlocks body' + "compound" -> parseFromString' parseBlocks body' + "pull-quote" -> B.blockQuote <$> parseFromString' parseBlocks body' + "epigraph" -> B.blockQuote <$> parseFromString' parseBlocks body' + "highlights" -> B.blockQuote <$> parseFromString' parseBlocks body' "rubric" -> B.para . B.strong <$> parseInlineFromString top _ | label `elem` ["attention","caution","danger","error","hint", "important","note","tip","warning","admonition"] -> - do bod <- parseFromString parseBlocks $ top ++ "\n\n" ++ body' + do bod <- parseFromString' parseBlocks $ top ++ "\n\n" ++ body' let lab = case label of "admonition" -> mempty (l:ls) -> B.divWith ("",["admonition-title"],[]) @@ -711,11 +711,11 @@ directive' = do (trim top ++ if null subtit then "" else (": " ++ subtit)) - bod <- parseFromString parseBlocks body' + bod <- parseFromString' parseBlocks body' return $ B.divWith ("",["sidebar"],[]) $ tit <> bod "topic" -> do tit <- B.para . B.strong <$> parseInlineFromString top - bod <- parseFromString parseBlocks body' + bod <- parseFromString' parseBlocks body' return $ B.divWith ("",["topic"],[]) $ tit <> bod "default-role" -> mempty <$ updateState (\s -> s { stateRstDefaultRole = @@ -731,7 +731,7 @@ directive' = do "math" -> return $ B.para $ mconcat $ map B.displayMath $ toChunks $ top ++ "\n\n" ++ body "figure" -> do - (caption, legend) <- parseFromString extractCaption body' + (caption, legend) <- parseFromString' extractCaption body' let src = escapeURI $ trim top return $ B.para (B.imageWith (imgAttr "figclass") src "fig:" caption) <> legend @@ -750,21 +750,21 @@ directive' = do -- directive content or the first immediately following element children <- case body of "" -> block - _ -> parseFromString parseBlocks body' + _ -> parseFromString' parseBlocks body' return $ B.divWith attrs children other -> do pos <- getPosition logMessage $ SkippedContent (".. " ++ other) pos - bod <- parseFromString parseBlocks $ top ++ "\n\n" ++ body' + bod <- parseFromString' parseBlocks $ top ++ "\n\n" ++ body' return $ B.divWith ("",[other],[]) bod tableDirective :: PandocMonad m => String -> [(String, String)] -> String -> RSTParser m Blocks tableDirective top _fields body = do - bs <- parseFromString parseBlocks body + bs <- parseFromString' parseBlocks body case B.toList bs of [Table _ aligns' widths' header' rows'] -> do - title <- parseFromString (trimInlines . mconcat <$> many inline) top + title <- parseFromString' (trimInlines . mconcat <$> many inline) top -- TODO widths -- align is not applicable since we can't represent whole table align return $ B.singleton $ Table (B.toList title) @@ -780,8 +780,8 @@ listTableDirective :: PandocMonad m => String -> [(String, String)] -> String -> RSTParser m Blocks listTableDirective top fields body = do - bs <- parseFromString parseBlocks body - title <- parseFromString (trimInlines . mconcat <$> many inline) top + bs <- parseFromString' parseBlocks body + title <- parseFromString' (trimInlines . mconcat <$> many inline) top let rows = takeRows $ B.toList bs headerRowsNum = fromMaybe (0 :: Int) $ lookup "header-rows" fields >>= safeRead @@ -812,7 +812,7 @@ addNewRole :: PandocMonad m => String -> [(String, String)] -> RSTParser m Blocks addNewRole roleString fields = do pos <- getPosition - (role, parentRole) <- parseFromString inheritedRole roleString + (role, parentRole) <- parseFromString' inheritedRole roleString customRoles <- stateRstCustomRoles <$> getState let getBaseRole (r, f, a) roles = case M.lookup r roles of @@ -1127,7 +1127,7 @@ simpleTableRow indices = do let cols = map unlines . transpose $ firstLine : conLines ++ [replicate (length indices) "" | not (null conLines)] - mapM (parseFromString parseBlocks) cols + mapM (parseFromString' parseBlocks) cols simpleTableSplitLine :: [Int] -> String -> [String] simpleTableSplitLine indices line = @@ -1150,7 +1150,7 @@ simpleTableHeader headless = try $ do let rawHeads = if headless then replicate (length dashes) "" else simpleTableSplitLine indices rawContent - heads <- mapM (parseFromString (mconcat <$> many plain)) $ + heads <- mapM (parseFromString' (mconcat <$> many plain)) $ map trim rawHeads return (heads, aligns, indices) @@ -1206,7 +1206,7 @@ inline = choice [ note -- can start with whitespace, so try before ws , symbol ] "inline" parseInlineFromString :: PandocMonad m => String -> RSTParser m Inlines -parseInlineFromString = parseFromString (trimInlines . mconcat <$> many inline) +parseInlineFromString = parseFromString' (trimInlines . mconcat <$> many inline) hyphens :: Monad m => RSTParser m Inlines hyphens = do @@ -1470,7 +1470,7 @@ note = try $ do -- Note references inside other notes are allowed in reST, but -- not yet in this implementation. updateState $ \st -> st{ stateNotes = [] } - contents <- parseFromString parseBlocks raw + contents <- parseFromString' parseBlocks raw let newnotes = if (ref == "*" || ref == "#") -- auto-numbered -- delete the note so the next auto-numbered note -- doesn't get the same contents: diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index ecb609ae9..aea55b7a9 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -106,7 +106,7 @@ parseHtmlContentWithAttrs tag parser = do parsedContent <- try $ parseContent content return (attr, parsedContent) where - parseContent = parseFromString $ nested $ manyTill parser endOfContent + parseContent = parseFromString' $ nested $ manyTill parser endOfContent endOfContent = try $ skipMany blankline >> skipSpaces >> eof parseHtmlContent :: PandocMonad m => String -> TWParser m a -> TWParser m [a] @@ -233,7 +233,7 @@ listItemLine prefix marker = lineContent >>= parseContent >>= return . mconcat filterSpaces = reverse . dropWhile (== ' ') . reverse listContinuation = notFollowedBy (string prefix >> marker) >> string " " >> lineContent - parseContent = parseFromString $ many1 $ nestedList <|> parseInline + parseContent = parseFromString' $ many1 $ nestedList <|> parseInline parseInline = many1Till inline (lastNewline <|> newlineBeforeNestedList) >>= return . B.plain . mconcat nestedList = list prefix @@ -297,7 +297,7 @@ noautolink = do setState $ st{ stateAllowLinks = True } return $ mconcat blocks where - parseContent = parseFromString $ many $ block + parseContent = parseFromString' $ many $ block para :: PandocMonad m => TWParser m B.Blocks para = many1Till inline endOfParaElement >>= return . result . mconcat @@ -525,4 +525,4 @@ linkText = do return (url, "", content) where linkContent = (char '[') >> many1Till anyChar (char ']') >>= parseLinkContent - parseLinkContent = parseFromString $ many1 inline + parseLinkContent = parseFromString' $ many1 inline diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index abf8be452..52f4f2493 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -315,7 +315,7 @@ definitionListItem = try $ do optional whitespace >> newline s <- many1Till anyChar (try (string "=:" >> newline)) -- this ++ "\n\n" does not look very good - ds <- parseFromString parseBlocks (s ++ "\n\n") + ds <- parseFromString' parseBlocks (s ++ "\n\n") return [ds] -- raw content @@ -367,7 +367,7 @@ tableCell = try $ do notFollowedBy blankline raw <- trim <$> many (noneOf "|\n" <|> try (char '\n' <* notFollowedBy blankline)) - content <- mconcat <$> parseFromString (many inline) raw + content <- mconcat <$> parseFromString' (many inline) raw return ((isHeader, alignment), B.plain content) -- | A table row is made of many table cells @@ -389,7 +389,7 @@ table = try $ do _ <- attributes char '.' rawcapt <- trim <$> anyLine - parseFromString (mconcat <$> many inline) rawcapt + parseFromString' (mconcat <$> many inline) rawcapt rawrows <- many1 $ (skipMany ignorableRow) >> tableRow skipMany ignorableRow blanklines @@ -507,7 +507,7 @@ note = try $ do notes <- stateNotes <$> getState case lookup ref notes of Nothing -> fail "note not found" - Just raw -> B.note <$> parseFromString parseBlocks raw + Just raw -> B.note <$> parseFromString' parseBlocks raw -- | Special chars markupChars :: [Char] diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 05c6c9a69..d8791869d 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -212,7 +212,7 @@ quote :: T2T Blocks quote = try $ do lookAhead tab rawQuote <- many1 (tab *> optional spaces *> anyLine) - contents <- parseFromString parseBlocks (intercalate "\n" rawQuote ++ "\n\n") + contents <- parseFromString' parseBlocks (intercalate "\n" rawQuote ++ "\n\n") return $ B.blockQuote contents commentLine :: T2T Inlines @@ -264,7 +264,7 @@ listItem start end = try $ do firstLine <- anyLineNewline blank <- option "" ("\n" <$ blankline) rest <- concat <$> many (listContinuation markerLength) - parseFromString end $ firstLine ++ blank ++ rest + parseFromString' end $ firstLine ++ blank ++ rest -- continuation of a list item - indented and separated by blankline or endline. -- Note: nested lists are parsed as continuations. @@ -439,7 +439,7 @@ inlineMarkup p f c special = try $ do Just middle -> do lastChar <- anyChar end <- many1 (char c) - let parser inp = parseFromString (mconcat <$> many p) inp + let parser inp = parseFromString' (mconcat <$> many p) inp let start' = case drop 2 start of "" -> mempty xs -> special xs diff --git a/test/command/3690.md b/test/command/3690.md new file mode 100644 index 000000000..213b88138 --- /dev/null +++ b/test/command/3690.md @@ -0,0 +1,8 @@ +``` +% pandoc +- [o] _hi_ +^D +
    +
  • [o] hi
  • +
+``` -- cgit v1.2.3 From 8f718b08834e496e98790e1b5b8a3cb9e1b932a6 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 23:04:49 +0200 Subject: LaTeX reader: Fixed failures on \ref{}, \label{} with `+raw_tex`. Now these commands are parsed as raw if `+raw_tex`; otherwise, their argument is parsed as a bracketed string. --- src/Text/Pandoc/Readers/LaTeX.hs | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 88be40e3e..7bcd120ce 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -482,9 +482,12 @@ inlineCommand = try $ do (lookupListDefault raw [name',name] inlineCommands <* optional (try (string "{}"))) -unlessParseRaw :: PandocMonad m => LP m () -unlessParseRaw = getOption readerExtensions >>= - guard . not . extensionEnabled Ext_raw_tex +rawInlineOr :: PandocMonad m => String -> LP m Inlines -> LP m Inlines +rawInlineOr name' fallback = do + parseRaw <- extensionEnabled Ext_raw_tex <$> getOption readerExtensions + if parseRaw + then rawInline "latex" <$> getRawCommand name' + else fallback isBlockCommand :: String -> Bool isBlockCommand s = s `M.member` (blockCommands :: M.Map String (LP PandocPure Blocks)) @@ -532,11 +535,11 @@ inlineCommands = M.fromList $ , ("dots", lit "…") , ("mdots", lit "…") , ("sim", lit "~") - , ("label", unlessParseRaw >> (inBrackets <$> tok)) - , ("ref", unlessParseRaw >> (inBrackets <$> tok)) + , ("label", rawInlineOr "label" (inBrackets <$> tok)) + , ("ref", rawInlineOr "ref" (inBrackets <$> tok)) , ("textgreek", tok) , ("sep", lit ",") - , ("cref", unlessParseRaw >> (inBrackets <$> tok)) -- from cleveref.sty + , ("cref", rawInlineOr "cref" (inBrackets <$> tok)) -- from cleveref.sty , ("(", mathInline $ manyTill anyChar (try $ string "\\)")) , ("[", mathDisplay $ manyTill anyChar (try $ string "\\]")) , ("ensuremath", mathInline braced) -- cgit v1.2.3 From b9a30ef9596b8d19554e03cd1ef8f0dc0695a486 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 24 May 2017 23:23:08 +0200 Subject: Markdown reader: fixed smart quotes after emphasis. E.g. in *foo*'s 'foo' Closes #2228. --- src/Text/Pandoc/Readers/Markdown.hs | 11 ++++++----- test/command/2228.md | 6 ++++++ 2 files changed, 12 insertions(+), 5 deletions(-) create mode 100644 test/command/2228.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 17a7184c0..3e3de0d9d 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1557,9 +1557,9 @@ ender c n = try $ do three :: PandocMonad m => Char -> MarkdownParser m (F Inlines) three c = do contents <- mconcat <$> many (notFollowedBy (ender c 1) >> inline) - (ender c 3 >> return ((B.strong . B.emph) <$> contents)) - <|> (ender c 2 >> one c (B.strong <$> contents)) - <|> (ender c 1 >> two c (B.emph <$> contents)) + (ender c 3 >> updateLastStrPos >> return ((B.strong . B.emph) <$> contents)) + <|> (ender c 2 >> updateLastStrPos >> one c (B.strong <$> contents)) + <|> (ender c 1 >> updateLastStrPos >> two c (B.emph <$> contents)) <|> return (return (B.str [c,c,c]) <> contents) -- Parse inlines til you hit two c's, and emit strong. @@ -1567,7 +1567,8 @@ three c = do two :: PandocMonad m => Char -> F Inlines -> MarkdownParser m (F Inlines) two c prefix' = do contents <- mconcat <$> many (try $ notFollowedBy (ender c 2) >> inline) - (ender c 2 >> return (B.strong <$> (prefix' <> contents))) + (ender c 2 >> updateLastStrPos >> + return (B.strong <$> (prefix' <> contents))) <|> return (return (B.str [c,c]) <> (prefix' <> contents)) -- Parse inlines til you hit a c, and emit emph. @@ -1578,7 +1579,7 @@ one c prefix' = do <|> try (string [c,c] >> notFollowedBy (ender c 1) >> two c mempty) ) - (ender c 1 >> return (B.emph <$> (prefix' <> contents))) + (ender c 1 >> updateLastStrPos >> return (B.emph <$> (prefix' <> contents))) <|> return (return (B.str [c]) <> (prefix' <> contents)) strongOrEmph :: PandocMonad m => MarkdownParser m (F Inlines) diff --git a/test/command/2228.md b/test/command/2228.md new file mode 100644 index 000000000..589a2350e --- /dev/null +++ b/test/command/2228.md @@ -0,0 +1,6 @@ +``` +% pandoc -f markdown+smart -t latex+smart +*foo*'s 'foo' +^D +\emph{foo}'s `foo' +``` -- cgit v1.2.3 From e6f4636a2cc6a3fa5ae834528fe21280d8f0a56a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 25 May 2017 09:19:34 +0200 Subject: MediaWiki reader: Make smart double quotes depend on `smart` extension. Closes #3585. --- src/Text/Pandoc/Readers/MediaWiki.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index c860a0cdf..b261021e0 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -688,6 +688,8 @@ strong = B.strong <$> nested (inlinesBetween start end) end = try $ sym "'''" doubleQuotes :: PandocMonad m => MWParser m Inlines -doubleQuotes = B.doubleQuoted <$> nested (inlinesBetween openDoubleQuote closeDoubleQuote) +doubleQuotes = do + guardEnabled Ext_smart + B.doubleQuoted <$> nested (inlinesBetween openDoubleQuote closeDoubleQuote) where openDoubleQuote = sym "\"" >> lookAhead nonspaceChar closeDoubleQuote = try $ sym "\"" -- cgit v1.2.3 From 41db9e826e5be45d087b1959d6d5dbeb8389e2a7 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 25 May 2017 09:35:25 +0200 Subject: MediaWiki reader: don't do curly quotes inside `` contexts. Even if `+smart`. See #3585. --- src/Text/Pandoc/Readers/MediaWiki.hs | 11 ++++++++++- test/command/3585.md | 16 ++++++++++++++++ 2 files changed, 26 insertions(+), 1 deletion(-) create mode 100644 test/command/3585.md (limited to 'src/Text') diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index b261021e0..3f6142f00 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -74,6 +74,7 @@ readMediaWiki opts s = do , mwHeaderMap = M.empty , mwIdentifierList = Set.empty , mwLogMessages = [] + , mwInTT = False } (s ++ "\n") case parsed of @@ -87,6 +88,7 @@ data MWState = MWState { mwOptions :: ReaderOptions , mwHeaderMap :: M.Map Inlines String , mwIdentifierList :: Set.Set String , mwLogMessages :: [LogMessage] + , mwInTT :: Bool } type MWParser m = ParserT [Char] MWState m @@ -569,7 +571,12 @@ inlineTag = do TagOpen "sub" _ -> B.subscript <$> inlinesInTags "sub" TagOpen "sup" _ -> B.superscript <$> inlinesInTags "sup" TagOpen "code" _ -> encode <$> inlinesInTags "code" - TagOpen "tt" _ -> encode <$> inlinesInTags "tt" + TagOpen "tt" _ -> do + inTT <- mwInTT <$> getState + updateState $ \st -> st{ mwInTT = True } + result <- encode <$> inlinesInTags "tt" + updateState $ \st -> st{ mwInTT = inTT } + return result TagOpen "hask" _ -> B.codeWith ("",["haskell"],[]) <$> charsInTags "hask" _ -> B.rawInline "html" . snd <$> htmlTag (~== tag) @@ -690,6 +697,8 @@ strong = B.strong <$> nested (inlinesBetween start end) doubleQuotes :: PandocMonad m => MWParser m Inlines doubleQuotes = do guardEnabled Ext_smart + inTT <- mwInTT <$> getState + guard (not inTT) B.doubleQuoted <$> nested (inlinesBetween openDoubleQuote closeDoubleQuote) where openDoubleQuote = sym "\"" >> lookAhead nonspaceChar closeDoubleQuote = try $ sym "\"" diff --git a/test/command/3585.md b/test/command/3585.md new file mode 100644 index 000000000..739ddeea4 --- /dev/null +++ b/test/command/3585.md @@ -0,0 +1,16 @@ +``` +% pandoc -f mediawiki+smart -t native +"Hello" + +Same but bzip2 it and nice it zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org "> /storage/c-3po/tank-storage-data-svn.dmp.bz2" +^D +[Para [Quoted DoubleQuote [Str "Hello"]] +,Para [Str "Same",Space,Str "but",Space,Str "bzip2",Space,Str "it",Space,Str "and",Space,Str "nice",Space,Str "it",Space,Code ("",[],[]) "zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org \"> /storage/c-3po/tank-storage-data-svn.dmp.bz2\""]] +``` + +``` +% pandoc -f mediawiki -t native +"Hello" +^D +[Para [Str "\"Hello\""]] +``` -- cgit v1.2.3 From 8f2c803f973d53da340c876edbbcb2b1223f35cd Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 25 May 2017 11:15:52 +0200 Subject: Markdown reader: warn for notes defined but not used. Closes #1718. Parsing.ParserState: Make stateNotes' a Map, add stateNoteRefs. --- src/Text/Pandoc/Logging.hs | 10 ++++++++++ src/Text/Pandoc/Parsing.hs | 7 +++++-- src/Text/Pandoc/Readers/Markdown.hs | 20 ++++++++++++++------ 3 files changed, 29 insertions(+), 8 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 70384f936..7afce9f5f 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -72,6 +72,7 @@ data LogMessage = | CouldNotParseYamlMetadata String SourcePos | DuplicateLinkReference String SourcePos | DuplicateNoteReference String SourcePos + | NoteDefinedButNotUsed String SourcePos | DuplicateIdentifier String SourcePos | ReferenceNotFound String SourcePos | CircularReference String SourcePos @@ -113,6 +114,11 @@ instance ToJSON LogMessage where "source" .= Text.pack (sourceName pos), "line" .= toJSON (sourceLine pos), "column" .= toJSON (sourceColumn pos)] + NoteDefinedButNotUsed s pos -> + ["key" .= Text.pack s, + "source" .= Text.pack (sourceName pos), + "line" .= toJSON (sourceLine pos), + "column" .= toJSON (sourceColumn pos)] DuplicateNoteReference s pos -> ["contents" .= Text.pack s, "source" .= Text.pack (sourceName pos), @@ -203,6 +209,9 @@ showLogMessage msg = "Duplicate link reference '" ++ s ++ "' at " ++ showPos pos DuplicateNoteReference s pos -> "Duplicate note reference '" ++ s ++ "' at " ++ showPos pos + NoteDefinedButNotUsed s pos -> + "Note with key '" ++ s ++ "' defined at " ++ showPos pos ++ + " but not used." DuplicateIdentifier s pos -> "Duplicate identifier '" ++ s ++ "' at " ++ showPos pos ReferenceNotFound s pos -> @@ -256,6 +265,7 @@ messageVerbosity msg = CouldNotParseYamlMetadata{} -> WARNING DuplicateLinkReference{} -> WARNING DuplicateNoteReference{} -> WARNING + NoteDefinedButNotUsed{} -> WARNING DuplicateIdentifier{} -> WARNING ReferenceNotFound{} -> WARNING CircularReference{} -> WARNING diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e6157dde3..225796272 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -983,6 +983,7 @@ data ParserState = ParserState stateSubstitutions :: SubstTable, -- ^ List of substitution references stateNotes :: NoteTable, -- ^ List of notes (raw bodies) stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies) + stateNoteRefs :: Set.Set String, -- ^ List of note references used stateMeta :: Meta, -- ^ Document metadata stateMeta' :: F Meta, -- ^ Document metadata stateCitations :: M.Map String String, -- ^ RST-style citations @@ -1099,7 +1100,8 @@ defaultParserState = stateHeaderKeys = M.empty, stateSubstitutions = M.empty, stateNotes = [], - stateNotes' = [], + stateNotes' = M.empty, + stateNoteRefs = Set.empty, stateMeta = nullMeta, stateMeta' = return nullMeta, stateCitations = M.empty, @@ -1166,7 +1168,8 @@ data QuoteContext type NoteTable = [(String, String)] -type NoteTable' = [(String, F Blocks)] -- used in markdown reader +type NoteTable' = M.Map String (SourcePos, F Blocks) +-- used in markdown reader newtype Key = Key String deriving (Show, Read, Eq, Ord) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 3e3de0d9d..11f35deb2 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -362,6 +362,14 @@ parseMarkdown = do optional titleBlock blocks <- parseBlocks st <- getState + -- check for notes with no corresponding note references + let notesUsed = stateNoteRefs st + let notesDefined = M.keys (stateNotes' st) + mapM_ (\n -> unless (n `Set.member` notesUsed) $ do + -- lookup to get sourcepos + case M.lookup n (stateNotes' st) of + Just (pos, _) -> report (NoteDefinedButNotUsed n pos) + Nothing -> error "The impossible happened.") notesDefined let doc = runF (do Pandoc _ bs <- B.doc <$> blocks meta <- stateMeta' st return $ Pandoc meta bs) st @@ -469,12 +477,11 @@ noteBlock = try $ do let raw = unlines (first:rest) ++ "\n" optional blanklines parsed <- parseFromString' parseBlocks raw - let newnote = (ref, parsed) oldnotes <- stateNotes' <$> getState - case lookup ref oldnotes of + case M.lookup ref oldnotes of Just _ -> logMessage $ DuplicateNoteReference ref pos Nothing -> return () - updateState $ \s -> s { stateNotes' = newnote : oldnotes } + updateState $ \s -> s { stateNotes' = M.insert ref (pos, parsed) oldnotes } return mempty -- @@ -1816,16 +1823,17 @@ note :: PandocMonad m => MarkdownParser m (F Inlines) note = try $ do guardEnabled Ext_footnotes ref <- noteMarker + updateState $ \st -> st{ stateNoteRefs = Set.insert ref (stateNoteRefs st) } return $ do notes <- asksF stateNotes' - case lookup ref notes of + case M.lookup ref notes of Nothing -> return $ B.str $ "[^" ++ ref ++ "]" - Just contents -> do + Just (_pos, contents) -> do st <- askF -- process the note in a context that doesn't resolve -- notes, to avoid infinite looping with notes inside -- notes: - let contents' = runF contents st{ stateNotes' = [] } + let contents' = runF contents st{ stateNotes' = M.empty } return $ B.note contents' inlineNote :: PandocMonad m => MarkdownParser m (F Inlines) -- cgit v1.2.3 From 650e1ac1fdbbb172c58c1898607a7f82806cf55e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 25 May 2017 12:11:46 +0200 Subject: Docx writer: Use Table rather than "Table Normal" for table style. "Table Normal" is the default table style and can't be modified. Closes #3275, further testing welcome. --- MANUAL.txt | 2 +- data/docx/word/styles.xml | 5 +++-- src/Text/Pandoc/Writers/Docx.hs | 2 +- 3 files changed, 5 insertions(+), 4 deletions(-) (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index ae518054d..170af0d6f 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -880,7 +880,7 @@ Options affecting specific writers Image Caption, Figure, Captioned Figure, TOC Heading; [character] Default Paragraph Font, Body Text Char, Verbatim Char, Footnote Reference, Hyperlink; [table] - Normal Table. + Table. ODT diff --git a/data/docx/word/styles.xml b/data/docx/word/styles.xml index 67d336db1..3596d8bbc 100644 --- a/data/docx/word/styles.xml +++ b/data/docx/word/styles.xml @@ -342,8 +342,9 @@
- - + + + diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a10840033..5b714ba41 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -953,7 +953,7 @@ blockToOpenXML' opts (Table caption aligns widths headers rows) = do caption' ++ [mknode "w:tbl" [] ( mknode "w:tblPr" [] - ( mknode "w:tblStyle" [("w:val","TableNormal")] () : + ( mknode "w:tblStyle" [("w:val","Table")] () : mknode "w:tblW" [("w:type", "pct"), ("w:w", show rowwidth)] () : mknode "w:tblLook" [("w:firstRow","1") | hasHeader ] () : [ mknode "w:tblCaption" [("w:val", captionStr)] () -- cgit v1.2.3 From 708973a33a0ce425bb21a5ffa06fbdab465d3fb8 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 25 May 2017 12:50:43 +0200 Subject: Added `spaced_reference_links` extension. This is now the default for pandoc's Markdown. It allows whitespace between the two parts of a reference link: e.g. [a] [b] [b]: url This is now forbidden by default. Closes #2602. --- MANUAL.txt | 10 +- src/Text/Pandoc/Extensions.hs | 6 +- src/Text/Pandoc/Readers/Markdown.hs | 8 +- test/command/2602.md | 18 + test/testsuite.native | 2 - test/testsuite.txt | 11 +- test/writer.asciidoc | 4 - test/writer.context | 40 +- test/writer.docbook4 | 6 - test/writer.docbook5 | 6 - test/writer.dokuwiki | 4 - test/writer.fb2 | 1014 ++++++++++++++++++++++++++++++++++- test/writer.haddock | 4 - test/writer.html4 | 2 - test/writer.html5 | 2 - test/writer.icml | 102 ++-- test/writer.jats | 6 - test/writer.latex | 4 - test/writer.man | 4 - test/writer.markdown | 4 - test/writer.mediawiki | 4 - test/writer.ms | 10 - test/writer.muse | 4 - test/writer.native | 2 - test/writer.opendocument | 4 - test/writer.opml | 2 +- test/writer.org | 4 - test/writer.plain | 4 - test/writer.rst | 4 - test/writer.rtf | 8 - test/writer.tei | 2 - test/writer.texinfo | 4 - test/writer.textile | 4 - test/writer.zimwiki | 4 - 34 files changed, 1101 insertions(+), 216 deletions(-) create mode 100644 test/command/2602.md (limited to 'src/Text') diff --git a/MANUAL.txt b/MANUAL.txt index 170af0d6f..2cd35d14d 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -3100,7 +3100,8 @@ definition, which may occur elsewhere in the document (either before or after the link). The link consists of link text in square brackets, followed by a label in -square brackets. (There can be space between the two.) The link definition +square brackets. (There cannot be space between the two unless the +`spaced_reference_links` extension is enabled.) The link definition consists of the bracketed label, followed by a colon and a space, followed by the URL, and optionally (after a space) a link title either in quotes or in parentheses. The label must not be parseable as a citation (assuming @@ -3551,6 +3552,13 @@ implied by pandoc's default `all_symbols_escapable`. Allow a list to occur right after a paragraph, with no intervening blank space. +#### Extension: `spaced_reference_links` #### + +Allow whitespace between the two components of a reference link, +for example, + + [foo] [bar]. + #### Extension: `hard_line_breaks` #### Causes all newlines within a paragraph to be interpreted as hard line diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 374fae2c1..58e8c414d 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -137,6 +137,7 @@ data Extension = | Ext_shortcut_reference_links -- ^ Shortcut reference links | Ext_smart -- ^ "Smart" quotes, apostrophes, ellipses, dashes | Ext_old_dashes -- ^ -- = em, - before number = en + | Ext_spaced_reference_links -- ^ Allow space between two parts of ref link deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable, Generic) -- | Extensions to be used with pandoc-flavored markdown. @@ -187,7 +188,7 @@ pandocExtensions = extensionsFromList , Ext_smart ] --- | Extensions to be used with github-flavored markdown. +-- | Extensions to be used with plain text output. plainExtensions :: Extensions plainExtensions = extensionsFromList [ Ext_table_captions @@ -220,6 +221,7 @@ phpMarkdownExtraExtensions = extensionsFromList , Ext_link_attributes , Ext_abbreviations , Ext_shortcut_reference_links + , Ext_spaced_reference_links ] -- | Extensions to be used with github-flavored markdown. @@ -272,6 +274,7 @@ multimarkdownExtensions = extensionsFromList , Ext_superscript , Ext_subscript , Ext_backtick_code_blocks + , Ext_spaced_reference_links ] -- | Language extensions to be used with strict markdown. @@ -279,6 +282,7 @@ strictExtensions :: Extensions strictExtensions = extensionsFromList [ Ext_raw_html , Ext_shortcut_reference_links + , Ext_spaced_reference_links ] -- | Default extensions from format-describing string. diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 11f35deb2..4fb75b344 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1750,10 +1750,12 @@ referenceLink :: PandocMonad m referenceLink constructor (lab, raw) = do sp <- (True <$ lookAhead (char ' ')) <|> return False (_,raw') <- option (mempty, "") $ - lookAhead (try (guardEnabled Ext_citations >> - spnl >> normalCite >> return (mempty, ""))) + lookAhead (try (do guardEnabled Ext_citations + guardDisabled Ext_spaced_reference_links <|> spnl + normalCite + return (mempty, ""))) <|> - try (spnl >> reference) + try ((guardDisabled Ext_spaced_reference_links <|> spnl) >> reference) when (raw' == "") $ guardEnabled Ext_shortcut_reference_links let labIsRef = raw' == "" || raw' == "[]" let key = toKey $ if labIsRef then raw else raw' diff --git a/test/command/2602.md b/test/command/2602.md new file mode 100644 index 000000000..5ed4b581c --- /dev/null +++ b/test/command/2602.md @@ -0,0 +1,18 @@ +``` +% pandoc +[a] [b] + +[b]: url +^D +

[a] b

+``` + +``` +% pandoc -f markdown+spaced_reference_links +[a] [b] + +[b]: url +^D +

a

+``` + diff --git a/test/testsuite.native b/test/testsuite.native index fa234dfc2..0587bddb8 100644 --- a/test/testsuite.native +++ b/test/testsuite.native @@ -369,8 +369,6 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,Header 2 ("reference",[],[]) [Str "Reference"] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."] -,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."] -,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."] diff --git a/test/testsuite.txt b/test/testsuite.txt index f6b0a7c95..9413cc81a 100644 --- a/test/testsuite.txt +++ b/test/testsuite.txt @@ -621,16 +621,11 @@ Just a [URL](/url/). ## Reference -Foo [bar] [a]. - Foo [bar][a]. -Foo [bar] -[a]. - [a]: /url/ -With [embedded [brackets]] [b]. +With [embedded [brackets]][b]. [b] by itself should be a link. @@ -659,9 +654,9 @@ Foo [biz](/url/ "Title with "quote" inside"). ## With ampersands -Here's a [link with an ampersand in the URL] [1]. +Here's a [link with an ampersand in the URL][1]. -Here's a link with an amersand in the link text: [AT&T] [2]. +Here's a link with an amersand in the link text: [AT&T][2]. Here's an [inline link](/script?foo=1&bar=2). diff --git a/test/writer.asciidoc b/test/writer.asciidoc index 2bf62e36f..639663743 100644 --- a/test/writer.asciidoc +++ b/test/writer.asciidoc @@ -600,10 +600,6 @@ Reference Foo link:/url/[bar]. -Foo link:/url/[bar]. - -Foo link:/url/[bar]. - With link:/url/[embedded [brackets]]. link:/url/[b] by itself should be a link. diff --git a/test/writer.context b/test/writer.context index eafc56f2a..9884c82c9 100644 --- a/test/writer.context +++ b/test/writer.context @@ -787,19 +787,15 @@ Just a \useURL[url4][/url/][][URL]\from[url4]. Foo \useURL[url13][/url/][][bar]\from[url13]. -Foo \useURL[url14][/url/][][bar]\from[url14]. +With \useURL[url14][/url/][][embedded {[}brackets{]}]\from[url14]. -Foo \useURL[url15][/url/][][bar]\from[url15]. +\useURL[url15][/url/][][b]\from[url15] by itself should be a link. -With \useURL[url16][/url/][][embedded {[}brackets{]}]\from[url16]. +Indented \useURL[url16][/url][][once]\from[url16]. -\useURL[url17][/url/][][b]\from[url17] by itself should be a link. +Indented \useURL[url17][/url][][twice]\from[url17]. -Indented \useURL[url18][/url][][once]\from[url18]. - -Indented \useURL[url19][/url][][twice]\from[url19]. - -Indented \useURL[url20][/url][][thrice]\from[url20]. +Indented \useURL[url18][/url][][thrice]\from[url18]. This should {[}not{]}{[}{]} be a link. @@ -807,41 +803,41 @@ This should {[}not{]}{[}{]} be a link. [not]: /url \stoptyping -Foo \useURL[url21][/url/][][bar]\from[url21]. +Foo \useURL[url19][/url/][][bar]\from[url19]. -Foo \useURL[url22][/url/][][biz]\from[url22]. +Foo \useURL[url20][/url/][][biz]\from[url20]. \subsection[with-ampersands]{With ampersands} -Here's a \useURL[url23][http://example.com/?foo=1&bar=2][][link with an -ampersand in the URL]\from[url23]. +Here's a \useURL[url21][http://example.com/?foo=1&bar=2][][link with an +ampersand in the URL]\from[url21]. Here's a link with an amersand in the link text: -\useURL[url24][http://att.com/][][AT&T]\from[url24]. +\useURL[url22][http://att.com/][][AT&T]\from[url22]. -Here's an \useURL[url25][/script?foo=1&bar=2][][inline link]\from[url25]. +Here's an \useURL[url23][/script?foo=1&bar=2][][inline link]\from[url23]. -Here's an \useURL[url26][/script?foo=1&bar=2][][inline link in pointy -braces]\from[url26]. +Here's an \useURL[url24][/script?foo=1&bar=2][][inline link in pointy +braces]\from[url24]. \subsection[autolinks]{Autolinks} -With an ampersand: \useURL[url27][http://example.com/?foo=1&bar=2]\from[url27] +With an ampersand: \useURL[url25][http://example.com/?foo=1&bar=2]\from[url25] \startitemize[packed] \item In a list? \item - \useURL[url28][http://example.com/]\from[url28] + \useURL[url26][http://example.com/]\from[url26] \item It should. \stopitemize An e-mail address: -\useURL[url29][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[url29] +\useURL[url27][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[url27] \startblockquote -Blockquoted: \useURL[url30][http://example.com/]\from[url30] +Blockquoted: \useURL[url28][http://example.com/]\from[url28] \stopblockquote Auto-links should not occur here: \type{} @@ -880,7 +876,7 @@ Here is a footnote reference,\footnote{Here is the footnote. It can go indent the first line of each block.\stopbuffer\footnote{\getbuffer} This should {\em not} be a footnote reference, because it contains a space.{[}^my note{]} Here is an inline note.\footnote{This is {\em easier} to type. Inline - notes may contain \useURL[url31][http://google.com][][links]\from[url31] and + notes may contain \useURL[url29][http://google.com][][links]\from[url29] and \type{]} verbatim characters, as well as {[}bracketed text{]}.} \startblockquote diff --git a/test/writer.docbook4 b/test/writer.docbook4 index eee19cdd9..163255974 100644 --- a/test/writer.docbook4 +++ b/test/writer.docbook4 @@ -1248,12 +1248,6 @@ These should not be escaped: \$ \\ \> \[ \{ Foo bar. - - Foo bar. - - - Foo bar. - With embedded [brackets]. diff --git a/test/writer.docbook5 b/test/writer.docbook5 index 07ca0f827..992cd8b63 100644 --- a/test/writer.docbook5 +++ b/test/writer.docbook5 @@ -1223,12 +1223,6 @@ These should not be escaped: \$ \\ \> \[ \{ Foo bar. - - Foo bar. - - - Foo bar. - With embedded [brackets]. diff --git a/test/writer.dokuwiki b/test/writer.dokuwiki index 79fcdde8a..4ba1b7054 100644 --- a/test/writer.dokuwiki +++ b/test/writer.dokuwiki @@ -556,10 +556,6 @@ Just a [[url/|URL]]. Foo [[url/|bar]]. -Foo [[url/|bar]]. - -Foo [[url/|bar]]. - With [[url/|embedded [brackets]]]. [[url/|b]] by itself should be a link. diff --git a/test/writer.fb2 b/test/writer.fb2 index 0412c8cf4..63d0bdfbf 100644 --- a/test/writer.fb2 +++ b/test/writer.fb2 @@ -1,3 +1,1013 @@ -Pandoc Test SuiteJohnMacFarlaneAnonymousJuly 17, 2006pandoc<p>Pandoc Test Suite</p>

John MacFarlane

Anonymous

July 17, 2006

This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.

——————————

<p>Headers</p>
<p>Level 2 with an embedded link </url></p>
<p>Level 3 with emphasis</p>
<p>Level 4</p>
<p>Level 5</p>
<p>Level 1</p>
<p>Level 2 with emphasis</p>
<p>Level 3</p>

with no blank line

<p>Level 2</p>

with no blank line

——————————

<p>Paragraphs</p>

Here’s a regular paragraph.

In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.

Here’s one with a bullet. * criminey.

There should be a hard line breakhere.

——————————

<p>Block Quotes</p>

E-mail style:

This is a block quote. It is pretty short.

Code in a block quote:

sub status {

print "working";

}

A list:

 1. item one

 2. item two

Nested block quotes:

nested

nested

This should not be a block quote: 2 > 1.

And a following paragraph.

——————————

<p>Code Blocks</p>

Code:

---- (should be four hyphens)

sub status {

print "working";

}

this code block is indented by one tab

And:

this code block is indented by two tabs

These should not be escaped: \$ \\ \> \[ \{

——————————

<p>Lists</p>
<p>Unordered</p>

Asterisks tight:

• asterisk 1

• asterisk 2

• asterisk 3

Asterisks loose:

• asterisk 1

• asterisk 2

• asterisk 3

Pluses tight:

• Plus 1

• Plus 2

• Plus 3

Pluses loose:

• Plus 1

• Plus 2

• Plus 3

Minuses tight:

• Minus 1

• Minus 2

• Minus 3

Minuses loose:

• Minus 1

• Minus 2

• Minus 3

<p>Ordered</p>

Tight:

 1. First

 2. Second

 3. Third

and:

 1. One

 2. Two

 3. Three

Loose using tabs:

 1. First

 2. Second

 3. Third

and using spaces:

 1. One

 2. Two

 3. Three

Multiple paragraphs:

 1. Item 1, graf one.Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.

 2. Item 2.

 3. Item 3.

<p>Nested</p>

• Tab

◦ Tab

* Tab

Here’s another:

 1. First

 2. Second:

   • Fee

   • Fie

   • Foe

 3. Third

Same thing but with paragraphs:

 1. First

 2. Second:

   • Fee

   • Fie

   • Foe

 3. Third

<p>Tabs and spaces</p>

• this is a list item indented with tabs

• this is a list item indented with spaces

◦ this is an example list item indented with tabs

◦ this is an example list item indented with spaces

<p>Fancy list markers</p>

 (2) begins with 2

 (3) and now 3with a continuation

 (3) iv. sublist with roman numerals, starting with 4

 (3) v. more items

 (3) v. (A) a subsublist

 (3) v. (B) a subsublist

Nesting:

 A. Upper Alpha

 A. I. Upper Roman.

 A. I. (6) Decimal start with 6

 A. I. (6) c) Lower alpha with paren

Autonumbering:

 1. Autonumber.

 2. More.

 2. 1. Nested.

Should not be a list item:

M.A. 2007

B. Williams

——————————

<p>Definition Lists</p>

Tight using spaces:

apple

    red fruit

orange

    orange fruit

banana

    yellow fruit

Tight using tabs:

apple

    red fruit

orange

    orange fruit

banana

    yellow fruit

Loose:

apple

    red fruit

orange

    orange fruit

banana

    yellow fruit

Multiple blocks with italics:

apple

    red fruit    contains seeds, crisp, pleasant to taste

orange

    orange fruit

    { orange code block }

    orange block quote

Multiple definitions, tight:

apple

    red fruit    computer

orange

    orange fruit    bank

Multiple definitions, loose:

apple

    red fruit    computer

orange

    orange fruit    bank

Blank line after term, indented marker, alternate markers:

apple

    red fruit    computer

orange

    orange fruit

 1. sublist

 2. sublist

<p>HTML Blocks</p>

Simple block on one line:

foo

And nested without indentation:

foo

bar

Interpreted markdown in a table:

This is emphasizedAnd this is strong

Here’s a simple block:

foo

This should be a code block, though:

<div>

foo

</div>

As should this:

<div>foo</div>

Now, nested:

foo

This should just be an HTML comment:

Multiline:

Code block:

<!-- Comment -->

Just plain comment, with trailing spaces on the line:

Code:

<hr />

Hr’s:

——————————

<p>Inline Markup</p>

This is emphasized, and so is this.

This is strong, and so is this.

An emphasized link[1].

This is strong and em.

So is this word.

This is strong and em.

So is this word.

This is code: >, $, \, \$, <html>.

This is strikeout.

Superscripts: abcd ahello ahello there.

Subscripts: H2O, H23O, Hmany of themO.

These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.

——————————

<p>Smart quotes, ellipses, dashes</p>

“Hello,” said the spider. “‘Shelob’ is my name.”

‘A’, ‘B’, and ‘C’ are letters.

‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’

‘He said, “I want to go.”’ Were you alive in the 70’s?

Here is some quoted ‘code’ and a “quoted link[2]”.

Some dashes: one—two — three—four — five.

Dashes between numbers: 5–7, 255–66, 1987–1999.

Ellipses…and…and….

——————————

<p>LaTeX</p>

• 

• 2+2=4

• x \in y

• \alpha \wedge \omega

• 223

• p-Tree

• Here’s some display math: \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}

• Here’s one that has a line break in it: \alpha + \omega \times x^2.

These shouldn’t be math:

• To get the famous equation, write $e = mc^2$.

• $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)

• Shoes ($20) and socks ($5).

• Escaped $: $73 this should be emphasized 23$.

Here’s a LaTeX table:

——————————

<p>Special Characters</p>

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: -

——————————

<p>Links</p>
<p>Explicit</p>

Just a URL[3].

URL and title[4].

URL and title[5].

URL and title[6].

URL and title[7]

URL and title[8]

with_underscore[9]

Email link[10]

Empty[11].

<p>Reference</p>

Foo bar[12].

Foo bar[13].

Foo bar[14].

With embedded [brackets][15].

b[16] by itself should be a link.

Indented once[17].

Indented twice[18].

Indented thrice[19].

This should [not][] be a link.

[not]: /url

Foo bar[20].

Foo biz[21].

<p>With ampersands</p>

Here’s a link with an ampersand in the URL[22].

Here’s a link with an amersand in the link text: AT&T[23].

Here’s an inline link[24].

Here’s an inline link in pointy braces[25].

<p>Autolinks</p>

With an ampersand: http://example.com/?foo=1&bar=2[26]

• In a list?

• http://example.com/[27]

• It should.

An e-mail address: nobody@nowhere.net[28]

Blockquoted: http://example.com/[29]

Auto-links should not occur here: <http://example.com/>

or here: <http://example.com/>

——————————

<p>Images</p>

From “Voyage dans la Lune” by Georges Melies (1902):

lalune

Here is a movie movie icon.

——————————

<p>Footnotes</p>

Here is a footnote reference,[30] and another.[31] This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note.[32]

Notes can go in quotes.[33]

 1. And in list items.[34]

This paragraph should not be part of the note, as it is not indented.

<p>1</p>

/url

<p>2</p>

http://example.com/?foo=1&bar=2

<p>3</p>

/url/

<p>4</p>

title: /url/

<p>5</p>

title preceded by two spaces: /url/

<p>6</p>

title preceded by a tab: /url/

<p>7</p>

title with "quotes" in it: /url/

<p>8</p>

title with single quotes: /url/

<p>9</p>

/url/with_underscore

<p>10</p>

mailto:nobody@nowhere.net

<p>11</p>

<p>12</p>

/url/

<p>13</p>

/url/

<p>14</p>

/url/

<p>15</p>

/url/

<p>16</p>

/url/

<p>17</p>

/url

<p>18</p>

/url

<p>19</p>

/url

<p>20</p>

Title with "quotes" inside: /url/

<p>21</p>

Title with "quote" inside: /url/

<p>22</p>

http://example.com/?foo=1&bar=2

<p>23</p>

AT&T: http://att.com/

<p>24</p>

/script?foo=1&bar=2

<p>25</p>

/script?foo=1&bar=2

<p>26</p>

http://example.com/?foo=1&bar=2

<p>27</p>

http://example.com/

<p>28</p>

mailto:nobody@nowhere.net

<p>29</p>

http://example.com/

<p>30</p>

Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.

<p>31</p>

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.

<p>32</p>

This is easier to type. Inline notes may contain links[32] and ] verbatim characters, as well as [bracketed text].

<p>33</p>

In quote.

<p>34</p>

In list.

/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==
- + + + +Pandoc Test Suite + +John +MacFarlane + + +Anonymous + +July 17, 2006 + + +pandoc + + + + +<p>Pandoc Test Suite</p> + + +

John MacFarlane

+

Anonymous

+

July 17, 2006

+
+
+

This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.

+ +

——————————

+ +
+
+ +<p>Headers</p> + +
+ +<p>Level 2 with an embedded link </url></p> + +
+ +<p>Level 3 with emphasis</p> + +
+ +<p>Level 4</p> + +
+ +<p>Level 5</p> + +
+
+
+
+
+
+ +<p>Level 1</p> + +
+ +<p>Level 2 with emphasis</p> + +
+ +<p>Level 3</p> + +

with no blank line

+
+
+
+ +<p>Level 2</p> + +

with no blank line

+ +

——————————

+ +
+
+
+ +<p>Paragraphs</p> + +

Here’s a regular paragraph.

+

In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.

+

Here’s one with a bullet. * criminey.

+

There should be a hard line breakhere.

+ +

——————————

+ +
+
+ +<p>Block Quotes</p> + +

E-mail style:

+ +

This is a block quote. It is pretty short.

+
+ +

Code in a block quote:

+ +

+sub status { +

+

+ print "working"; +

+

+} +

+ +

A list:

+

 1. item one

+

 2. item two

+

Nested block quotes:

+ +

nested

+
+ +

nested

+
+
+

This should not be a block quote: 2 > 1.

+

And a following paragraph.

+ +

——————————

+ +
+
+ +<p>Code Blocks</p> + +

Code:

+ +

+---- (should be four hyphens) +

+

+ + +

+

+sub status { +

+

+ print "working"; +

+

+} +

+

+ + +

+

+this code block is indented by one tab +

+ +

And:

+ +

+ this code block is indented by two tabs +

+

+ + +

+

+These should not be escaped: \$ \\ \> \[ \{ +

+ + +

——————————

+ +
+
+ +<p>Lists</p> + +
+ +<p>Unordered</p> + +

Asterisks tight:

+

• asterisk 1

+

• asterisk 2

+

• asterisk 3

+

Asterisks loose:

+

• asterisk 1 +

+

• asterisk 2 +

+

• asterisk 3 +

+

Pluses tight:

+

• Plus 1

+

• Plus 2

+

• Plus 3

+

Pluses loose:

+

• Plus 1 +

+

• Plus 2 +

+

• Plus 3 +

+

Minuses tight:

+

• Minus 1

+

• Minus 2

+

• Minus 3

+

Minuses loose:

+

• Minus 1 +

+

• Minus 2 +

+

• Minus 3 +

+
+
+ +<p>Ordered</p> + +

Tight:

+

 1. First

+

 2. Second

+

 3. Third

+

and:

+

 1. One

+

 2. Two

+

 3. Three

+

Loose using tabs:

+

 1. First +

+

 2. Second +

+

 3. Third +

+

and using spaces:

+

 1. One +

+

 2. Two +

+

 3. Three +

+

Multiple paragraphs:

+

 1. Item 1, graf one.Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. +

+

 2. Item 2. +

+

 3. Item 3. +

+
+
+ +<p>Nested</p> + +

• Tab

◦ Tab

* Tab

+

+

+

Here’s another:

+

 1. First

+

 2. Second:

   • Fee

+

   • Fie

+

   • Foe

+

+

 3. Third

+

Same thing but with paragraphs:

+

 1. First +

+

 2. Second: +

   • Fee

+

   • Fie

+

   • Foe

+

+

 3. Third +

+
+
+ +<p>Tabs and spaces</p> + +

• this is a list item indented with tabs +

+

• this is a list item indented with spaces +

◦ this is an example list item indented with tabs +

+

◦ this is an example list item indented with spaces +

+

+
+
+ +<p>Fancy list markers</p> + +

 (2) begins with 2

+

 (3) and now 3with a continuation +

 (3) iv. sublist with roman numerals, starting with 4

+

 (3) v. more items

 (3) v. (A) a subsublist

+

 (3) v. (B) a subsublist

+

+

+

Nesting:

+

 A. Upper Alpha

 A. I. Upper Roman.

 A. I. (6) Decimal start with 6

 A. I. (6) c) Lower alpha with paren

+

+

+

+

Autonumbering:

+

 1. Autonumber.

+

 2. More.

 2. 1. Nested.

+

+

Should not be a list item:

+

M.A. 2007

+

B. Williams

+ +

——————————

+ +
+
+
+ +<p>Definition Lists</p> + +

Tight using spaces:

+

+apple +

+

    red fruit +

+

+orange +

+

    orange fruit +

+

+banana +

+

    yellow fruit +

+

Tight using tabs:

+

+apple +

+

    red fruit +

+

+orange +

+

    orange fruit +

+

+banana +

+

    yellow fruit +

+

Loose:

+

+apple +

+

    red fruit +

+

+orange +

+

    orange fruit +

+

+banana +

+

    yellow fruit +

+

Multiple blocks with italics:

+

+ +apple + +

+

    red fruit    contains seeds, crisp, pleasant to taste +

+

+ +orange + +

+

    orange fruit + +

+    { orange code block } +

+ + +

    orange block quote

+
+

+

Multiple definitions, tight:

+

+apple +

+

    red fruit    computer +

+

+orange +

+

    orange fruit    bank +

+

Multiple definitions, loose:

+

+apple +

+

    red fruit    computer +

+

+orange +

+

    orange fruit    bank +

+

Blank line after term, indented marker, alternate markers:

+

+apple +

+

    red fruit    computer +

+

+orange +

+

    orange fruit +

 1. sublist

+

 2. sublist

+

+
+
+ +<p>HTML Blocks</p> + +

Simple block on one line:

foo

And nested without indentation:

+

foo

bar

Interpreted markdown in a table:

This is emphasizedAnd this is strong +

Here’s a simple block:

+

foo

+

This should be a code block, though:

+ +

+<div> +

+

+ foo +

+

+</div> +

+ +

As should this:

+ +

+<div>foo</div> +

+ +

Now, nested:

foo

This should just be an HTML comment:

+

Multiline:

+

Code block:

+ +

+<!-- Comment --> +

+ +

Just plain comment, with trailing spaces on the line:

+

Code:

+ +

+<hr /> +

+ +

Hr’s:

+ +

——————————

+ +
+
+ +<p>Inline Markup</p> + +

This is emphasized, and so is this.

+

This is strong, and so is this.

+

An emphasized link +[1] + +.

+

+ +This is strong and em. + +

+

So is +this + word.

+

+ +This is strong and em. + +

+

So is +this + word.

+

This is code: >, $, \, \$, <html>.

+

+This is strikeout. +

+

Superscripts: abcd a +hello + ahello there.

+

Subscripts: H2O, H23O, Hmany of themO.

+

These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.

+ +

——————————

+ +
+
+ +<p>Smart quotes, ellipses, dashes</p> + +

“Hello,” said the spider. “‘Shelob’ is my name.”

+

‘A’, ‘B’, and ‘C’ are letters.

+

‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’

+

‘He said, “I want to go.”’ Were you alive in the 70’s?

+

Here is some quoted ‘code’ and a “quoted link +[2] +”.

+

Some dashes: one—two — three—four — five.

+

Dashes between numbers: 5–7, 255–66, 1987–1999.

+

Ellipses…and…and….

+ +

——————————

+ +
+
+ +<p>LaTeX</p> + +

• 

+

• 2+2=4 +

+

• x \in y +

+

• \alpha \wedge \omega +

+

• 223 +

+

• p-Tree

+

• Here’s some display math: \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} +

+

• Here’s one that has a line break in it: \alpha + \omega \times x^2.

+

These shouldn’t be math:

+

• To get the famous equation, write $e = mc^2$.

+

• $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)

+

• Shoes ($20) and socks ($5).

+

• Escaped $: $73 this should be emphasized 23$.

+

Here’s a LaTeX table:

+ +

——————————

+ +
+
+ +<p>Special Characters</p> + +

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: -

+ +

——————————

+ +
+
+ +<p>Links</p> + +
+ +<p>Explicit</p> + +

Just a URL +[3] +.

+

URL and title +[4] +.

+

URL and title +[5] +.

+

URL and title +[6] +.

+

URL and title +[7] + +

+

URL and title +[8] + +

+

with_underscore +[9] + +

+

Email link +[10] + +

+

Empty +[11] +.

+
+
+ +<p>Reference</p> + +

Foo bar +[12] +.

+

With embedded [brackets] +[13] +.

+

b +[14] + by itself should be a link.

+

Indented once +[15] +.

+

Indented twice +[16] +.

+

Indented thrice +[17] +.

+

This should [not][] be a link.

+ +

+[not]: /url +

+ +

Foo bar +[18] +.

+

Foo biz +[19] +.

+
+
+ +<p>With ampersands</p> + +

Here’s a link with an ampersand in the URL +[20] +.

+

Here’s a link with an amersand in the link text: AT&T +[21] +.

+

Here’s an inline link +[22] +.

+

Here’s an inline link in pointy braces +[23] +.

+
+
+ +<p>Autolinks</p> + +

With an ampersand: http://example.com/?foo=1&bar=2 +[24] + +

+

• In a list?

+

• http://example.com/ +[25] + +

+

• It should.

+

An e-mail address: nobody@nowhere.net +[26] + +

+ +

Blockquoted: http://example.com/ +[27] + +

+
+

Auto-links should not occur here: <http://example.com/> +

+ +

+or here: <http://example.com/> +

+ + +

——————————

+ +
+
+
+ +<p>Images</p> + +

From “Voyage dans la Lune” by Georges Melies (1902):

+lalune +

Here is a movie movie icon.

+ +

——————————

+ +
+
+ +<p>Footnotes</p> + +

Here is a footnote reference, +[28] + and another. +[29] + This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note. +[30] + +

+ +

Notes can go in quotes. +[31] + +

+
+

 1. And in list items. +[32] + +

+

This paragraph should not be part of the note, as it is not indented.

+
+ + +
+ +<p>1</p> + +

+/url +

+
+
+ +<p>2</p> + +

+http://example.com/?foo=1&bar=2 +

+
+
+ +<p>3</p> + +

+/url/ +

+
+
+ +<p>4</p> + +

title: /url/ +

+
+
+ +<p>5</p> + +

title preceded by two spaces: /url/ +

+
+
+ +<p>6</p> + +

title preceded by a tab: /url/ +

+
+
+ +<p>7</p> + +

title with "quotes" in it: /url/ +

+
+
+ +<p>8</p> + +

title with single quotes: /url/ +

+
+
+ +<p>9</p> + +

+/url/with_underscore +

+
+
+ +<p>10</p> + +

+mailto:nobody@nowhere.net +

+
+
+ +<p>11</p> + +

+ + +

+
+
+ +<p>12</p> + +

+/url/ +

+
+
+ +<p>13</p> + +

+/url/ +

+
+
+ +<p>14</p> + +

+/url/ +

+
+
+ +<p>15</p> + +

+/url +

+
+
+ +<p>16</p> + +

+/url +

+
+
+ +<p>17</p> + +

+/url +

+
+
+ +<p>18</p> + +

Title with "quotes" inside: /url/ +

+
+
+ +<p>19</p> + +

Title with "quote" inside: /url/ +

+
+
+ +<p>20</p> + +

+http://example.com/?foo=1&bar=2 +

+
+
+ +<p>21</p> + +

AT&T: http://att.com/ +

+
+
+ +<p>22</p> + +

+/script?foo=1&bar=2 +

+
+
+ +<p>23</p> + +

+/script?foo=1&bar=2 +

+
+
+ +<p>24</p> + +

+http://example.com/?foo=1&bar=2 +

+
+
+ +<p>25</p> + +

+http://example.com/ +

+
+
+ +<p>26</p> + +

+mailto:nobody@nowhere.net +

+
+
+ +<p>27</p> + +

+http://example.com/ +

+
+
+ +<p>28</p> + +

Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.

+
+
+ +<p>29</p> + +

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.

+
+
+ +<p>30</p> + +

This is easier to type. Inline notes may contain links +[30] + and ] verbatim characters, as well as [bracketed text].

+
+
+ +<p>31</p> + +

In quote.

+
+
+ +<p>32</p> + +

In list.

+
+ +
diff --git a/test/writer.haddock b/test/writer.haddock index 0772331e3..7f783abd1 100644 --- a/test/writer.haddock +++ b/test/writer.haddock @@ -560,10 +560,6 @@ Just a . Foo . -Foo . - -Foo . - With . by itself should be a link. diff --git a/test/writer.html4 b/test/writer.html4 index bac16b14c..89cf07685 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -486,8 +486,6 @@ Blah

Empty.

Reference

Foo bar.

-

Foo bar.

-

Foo bar.

With embedded [brackets].

b by itself should be a link.

Indented once.

diff --git a/test/writer.html5 b/test/writer.html5 index ee921766c..6762f8198 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -489,8 +489,6 @@ Blah

Empty.

Reference

Foo bar.

-

Foo bar.

-

Foo bar.

With embedded [brackets].

b by itself should be a link.

Indented once.

diff --git a/test/writer.icml b/test/writer.icml index b498f568b..c39915120 100644 --- a/test/writer.icml +++ b/test/writer.icml @@ -2564,39 +2564,11 @@ These should not be escaped: \$ \\ \> \[ \{
- - - Foo - - - - . - - -
- - - Foo - - - - . - - -
With -
-
-