diff options
-rw-r--r-- | src/Text/Pandoc/Readers/Org/BlockStarts.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 40 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/DocumentTree.hs | 26 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ExportSettings.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Meta.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Parsing.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 2 | ||||
-rw-r--r-- | test/Tests/Readers/Org.hs | 42 | ||||
-rw-r--r-- | test/command/3706.md | 44 |
11 files changed, 122 insertions, 55 deletions
diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index 066bde9e0..fb2b52654 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.BlockStarts Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above @@ -139,4 +139,3 @@ endOfBlock = lookAhead . try $ do , void bulletListStart , void orderedListStart ] - diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 52e990584..b650721b3 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ViewPatterns #-} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.Blocks Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above @@ -122,18 +122,18 @@ attrFromBlockAttributes (BlockAttributes{..}) = kv = filter ((`notElem` ["id", "class"]) . fst) blockAttrKeyValues in (ident, classes, kv) -stringyMetaAttribute :: Monad m => (String -> Bool) -> OrgParser m (String, String) -stringyMetaAttribute attrCheck = try $ do +stringyMetaAttribute :: Monad m => OrgParser m (String, String) +stringyMetaAttribute = try $ do metaLineStart attrName <- map toUpper <$> many1Till nonspaceChar (char ':') - guard $ attrCheck attrName skipSpaces - attrValue <- anyLine + attrValue <- anyLine <|> ("" <$ newline) return (attrName, attrValue) blockAttributes :: PandocMonad m => OrgParser m BlockAttributes blockAttributes = try $ do - kv <- many (stringyMetaAttribute attrCheck) + kv <- many stringyMetaAttribute + guard $ all (attrCheck . fst) kv let caption = foldl' (appendValues "CAPTION") Nothing kv let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv let name = lookup "NAME" kv @@ -150,13 +150,7 @@ blockAttributes = try $ do } where attrCheck :: String -> Bool - attrCheck attr = - case attr of - "NAME" -> True - "LABEL" -> True - "CAPTION" -> True - "ATTR_HTML" -> True - _ -> False + attrCheck x = x `elem` ["NAME", "LABEL", "CAPTION", "ATTR_HTML", "RESULTS"] appendValues :: String -> Maybe String -> (String, String) -> Maybe String appendValues attrName accValue (key, value) = @@ -166,6 +160,7 @@ blockAttributes = try $ do Just acc -> Just $ acc ++ ' ':value Nothing -> Just value +-- | Parse key-value pairs for HTML attributes keyValues :: Monad m => OrgParser m [(String, String)] keyValues = try $ manyTill ((,) <$> key <*> value) newline @@ -301,16 +296,15 @@ codeBlock blockAttrs blockType = do skipSpaces (classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders) content <- rawBlockContent blockType - resultsContent <- trailingResultsBlock + resultsContent <- option mempty babelResultsBlock let id' = fromMaybe mempty $ blockAttrName blockAttrs let codeBlck = B.codeBlockWith ( id', classes, kv ) content let labelledBlck = maybe (pure codeBlck) (labelDiv codeBlck) (blockAttrCaption blockAttrs) - let resultBlck = fromMaybe mempty resultsContent return $ - (if exportsCode kv then labelledBlck else mempty) <> - (if exportsResults kv then resultBlck else mempty) + (if exportsCode kv then labelledBlck else mempty) <> + (if exportsResults kv then resultsContent else mempty) where labelDiv :: Blocks -> F Inlines -> F Blocks labelDiv blk value = @@ -325,12 +319,16 @@ codeBlock blockAttrs blockType = do exportsResults :: [(String, String)] -> Bool exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports" -trailingResultsBlock :: PandocMonad m => OrgParser m (Maybe (F Blocks)) -trailingResultsBlock = optionMaybe . try $ do +-- | Parse the result of an evaluated babel code block. +babelResultsBlock :: PandocMonad m => OrgParser m (F Blocks) +babelResultsBlock = try $ do blanklines - stringAnyCase "#+RESULTS:" - blankline + resultsMarker <|> + (lookAhead . void . try $ + manyTill (metaLineStart *> anyLineNewline) resultsMarker) block + where + resultsMarker = try . void $ stringAnyCase "#+RESULTS:" *> blankline -- | Parse code block arguments codeHeaderArgs :: Monad m => OrgParser m ([String], [(String, String)]) diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index 8c2a8482a..4abbe7be8 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -34,6 +34,7 @@ module Text.Pandoc.Readers.Org.DocumentTree import Control.Monad (guard, void) import Data.Char (toLower, toUpper) +import Data.List ( intersperse ) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import Text.Pandoc.Builder (Blocks, Inlines) @@ -219,12 +220,16 @@ headlineToHeaderWithContents hdln@(Headline {..}) = do headlineToHeader :: Monad m => Headline -> OrgParser m Blocks headlineToHeader (Headline {..}) = do exportTodoKeyword <- getExportSetting exportWithTodoKeywords + exportTags <- getExportSetting exportWithTags 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 text = todoText <> headlineText <> + if exportTags + then tagsToInlines headlineTags + else mempty let propAttr = propertiesToAttr headlineProperties attr <- registerHeader propAttr headlineText return $ B.headerWith attr headlineLevel text @@ -259,12 +264,21 @@ propertiesToAttr properties = in (id', words cls ++ (if isUnnumbered then ["unnumbered"] else []), kvs') -tagTitle :: Inlines -> [Tag] -> Inlines -tagTitle title tags = title <> (mconcat $ map tagToInline tags) +tagsToInlines :: [Tag] -> Inlines +tagsToInlines [] = mempty +tagsToInlines tags = + (B.space <>) . mconcat . intersperse (B.str "\160") . map tagToInline $ tags + where + tagToInline :: Tag -> Inlines + tagToInline t = tagSpan t . B.smallcaps . B.str $ fromTag t + +-- | Wrap the given inline in a span, marking it as a tag. +tagSpan :: Tag -> Inlines -> Inlines +tagSpan t = B.spanWith ("", ["tag"], [("data-tag-name", fromTag t)]) + + + --- | 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. diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs index 934191e71..11f0972d5 100644 --- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs +++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs @@ -17,8 +17,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2016 Albert Krewinkel + Module : Text.Pandoc.Readers.Org.ExportSettings + Copyright : © 2016–2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -71,7 +71,7 @@ exportSetting = choice , ignoredSetting "pri" , ignoredSetting "prop" , ignoredSetting "stat" - , ignoredSetting "tags" + , booleanSetting "tags" (\val es -> es { exportWithTags = val }) , ignoredSetting "tasks" , ignoredSetting "tex" , ignoredSetting "timestamp" diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index dcea61222..ad5a1e4de 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.Inlines Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 5dc742403..33c212bca 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -44,7 +44,7 @@ import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition -import Control.Monad (mzero, void) +import Control.Monad (mzero, void, when) import Data.Char (toLower) import Data.List (intersperse) import qualified Data.Map as M @@ -75,7 +75,9 @@ declarationLine :: PandocMonad m => OrgParser m () declarationLine = try $ do key <- map toLower <$> metaKey (key', value) <- metaValue key - updateState $ \st -> st { orgStateMeta = B.setMeta key' <$> value <*> orgStateMeta st } + when (key' /= "results") $ + updateState $ \st -> + st { orgStateMeta = B.setMeta key' <$> value <*> orgStateMeta st } metaKey :: Monad m => OrgParser m String metaKey = map toLower <$> many1 (noneOf ": \n\r") diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 1736cd881..4520a5552 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.ParserState Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above @@ -240,6 +240,7 @@ data ExportSettings = ExportSettings , exportWithAuthor :: Bool -- ^ Include author in final meta-data , exportWithCreator :: Bool -- ^ Include creator in final meta-data , exportWithEmail :: Bool -- ^ Include email in final meta-data + , exportWithTags :: Bool -- ^ Keep tags as part of headlines , exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers } @@ -258,5 +259,6 @@ defaultExportSettings = ExportSettings , exportWithAuthor = True , exportWithCreator = True , exportWithEmail = True + , exportWithTags = True , exportWithTodoKeywords = True } diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 1d3e8c257..3273c92e4 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.Parsing Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index 95424319f..d9414319a 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | - Module : Text.Pandoc.Readers.Org.Options + Module : Text.Pandoc.Readers.Org.Shared Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs index 3302e0c3e..4644d13a0 100644 --- a/test/Tests/Readers/Org.hs +++ b/test/Tests/Readers/Org.hs @@ -28,6 +28,10 @@ simpleTable' :: Int -> Blocks simpleTable' n = table "" (replicate n (AlignDefault, 0.0)) +-- | Create a span for the given tag. +tagSpan :: String -> Inlines +tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) . smallcaps $ str t + tests :: [TestTree] tests = [ testGroup "Inlines" $ @@ -729,18 +733,17 @@ tests = , "* old :ARCHIVE:" , " boring" ] =?> - let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty - in mconcat [ headerWith ("old", [], mempty) 1 ("old" <> tagSpan "ARCHIVE") - , para "boring" - ] + mconcat [ headerWith ("old", [], mempty) 1 + ("old" <> space <> tagSpan "ARCHIVE") + , para "boring" + ] , "include archive tree header only" =: unlines [ "#+OPTIONS: arch:headline" , "* old :ARCHIVE:" , " boring" ] =?> - let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty - in headerWith ("old", [], mempty) 1 ("old" <> tagSpan "ARCHIVE") + headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") , "limit headline depth" =: unlines [ "#+OPTIONS: H:2" @@ -791,6 +794,12 @@ tests = , "** DONE todo export" ] =?> headerWith ("todo-export", [], []) 2 "todo export" + + , "remove tags from headlines" =: + unlines [ "#+OPTIONS: tags:nil" + , "* Headline :hello:world:" + ] =?> + headerWith ("headline", [], mempty) 1 "Headline" ] ] @@ -898,17 +907,16 @@ tests = , "** Call Mom :@PHONE:" , "** Call John :@PHONE:JOHN: " ] =?> - let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty - in mconcat [ headerWith ("personal", [], []) - 1 - ("Personal" <> tagSpan "PERSONAL") - , headerWith ("call-mom", [], []) - 2 - ("Call Mom" <> tagSpan "@PHONE") - , headerWith ("call-john", [], []) - 2 - ("Call John" <> tagSpan "@PHONE" <> tagSpan "JOHN") - ] + mconcat [ headerWith ("personal", [], []) + 1 + ("Personal " <> tagSpan "PERSONAL") + , headerWith ("call-mom", [], []) + 2 + ("Call Mom " <> tagSpan "@PHONE") + , headerWith ("call-john", [], []) + 2 + ("Call John " <> tagSpan "@PHONE" <> "\160" <> tagSpan "JOHN") + ] , "Untagged header containing colons" =: "* This: is not: tagged" =?> diff --git a/test/command/3706.md b/test/command/3706.md new file mode 100644 index 000000000..00f53279e --- /dev/null +++ b/test/command/3706.md @@ -0,0 +1,44 @@ +Results marker can be hidden in block attributes (#3706) + +``` +pandoc -f org -t native +#+BEGIN_SRC R :exports results :colnames yes + data.frame(Id = 1:3, Desc = rep("La",3)) +#+END_SRC + +#+CAPTION: Lalelu. +#+LABEL: tab +#+RESULTS: +| Id | Desc | +|----+------| +| 1 | La | +| 2 | La | +| 3 | La | +^D +[Table [Str "Lalelu."] [AlignDefault,AlignDefault] [0.0,0.0] + [[Plain [Str "Id"]] + ,[Plain [Str "Desc"]]] + [[[Plain [Str "1"]] + ,[Plain [Str "La"]]] + ,[[Plain [Str "2"]] + ,[Plain [Str "La"]]] + ,[[Plain [Str "3"]] + ,[Plain [Str "La"]]]]] +``` + +``` +pandoc -f org -t native +#+BEGIN_SRC R :exports none :colnames yes + data.frame(Id = 1:2, Desc = rep("La",2)) +#+END_SRC + +#+CAPTION: Lalelu. +#+LABEL: tab +#+RESULTS: +| Id | Desc | +|----+------| +| 1 | La | +| 2 | La | +^D +[] +``` |