Org reader: recognize babel result blocks with attributes

Babel result blocks can have block attributes like captions and names.
Result blocks with attributes were not recognized and were parsed as
normal blocks without attributes.

Fixes: 
This commit is contained in:
Albert Krewinkel 2017-05-31 20:01:04 +02:00
parent 4b98d0459a
commit 7852cd5603
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
3 changed files with 66 additions and 22 deletions
src/Text/Pandoc/Readers/Org
test/command

View file

@ -122,18 +122,18 @@ attrFromBlockAttributes (BlockAttributes{..}) =
kv = filter ((`notElem` ["id", "class"]) . fst) blockAttrKeyValues kv = filter ((`notElem` ["id", "class"]) . fst) blockAttrKeyValues
in (ident, classes, kv) in (ident, classes, kv)
stringyMetaAttribute :: Monad m => (String -> Bool) -> OrgParser m (String, String) stringyMetaAttribute :: Monad m => OrgParser m (String, String)
stringyMetaAttribute attrCheck = try $ do stringyMetaAttribute = try $ do
metaLineStart metaLineStart
attrName <- map toUpper <$> many1Till nonspaceChar (char ':') attrName <- map toUpper <$> many1Till nonspaceChar (char ':')
guard $ attrCheck attrName
skipSpaces skipSpaces
attrValue <- anyLine attrValue <- anyLine <|> ("" <$ newline)
return (attrName, attrValue) return (attrName, attrValue)
blockAttributes :: PandocMonad m => OrgParser m BlockAttributes blockAttributes :: PandocMonad m => OrgParser m BlockAttributes
blockAttributes = try $ do blockAttributes = try $ do
kv <- many (stringyMetaAttribute attrCheck) kv <- many stringyMetaAttribute
guard $ all (attrCheck . fst) kv
let caption = foldl' (appendValues "CAPTION") Nothing kv let caption = foldl' (appendValues "CAPTION") Nothing kv
let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv
let name = lookup "NAME" kv let name = lookup "NAME" kv
@ -150,13 +150,7 @@ blockAttributes = try $ do
} }
where where
attrCheck :: String -> Bool attrCheck :: String -> Bool
attrCheck attr = attrCheck x = x `elem` ["NAME", "LABEL", "CAPTION", "ATTR_HTML", "RESULTS"]
case attr of
"NAME" -> True
"LABEL" -> True
"CAPTION" -> True
"ATTR_HTML" -> True
_ -> False
appendValues :: String -> Maybe String -> (String, String) -> Maybe String appendValues :: String -> Maybe String -> (String, String) -> Maybe String
appendValues attrName accValue (key, value) = appendValues attrName accValue (key, value) =
@ -166,6 +160,7 @@ blockAttributes = try $ do
Just acc -> Just $ acc ++ ' ':value Just acc -> Just $ acc ++ ' ':value
Nothing -> Just value Nothing -> Just value
-- | Parse key-value pairs for HTML attributes
keyValues :: Monad m => OrgParser m [(String, String)] keyValues :: Monad m => OrgParser m [(String, String)]
keyValues = try $ keyValues = try $
manyTill ((,) <$> key <*> value) newline manyTill ((,) <$> key <*> value) newline
@ -301,16 +296,15 @@ codeBlock blockAttrs blockType = do
skipSpaces skipSpaces
(classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders) (classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders)
content <- rawBlockContent blockType content <- rawBlockContent blockType
resultsContent <- trailingResultsBlock resultsContent <- option mempty babelResultsBlock
let id' = fromMaybe mempty $ blockAttrName blockAttrs let id' = fromMaybe mempty $ blockAttrName blockAttrs
let codeBlck = B.codeBlockWith ( id', classes, kv ) content let codeBlck = B.codeBlockWith ( id', classes, kv ) content
let labelledBlck = maybe (pure codeBlck) let labelledBlck = maybe (pure codeBlck)
(labelDiv codeBlck) (labelDiv codeBlck)
(blockAttrCaption blockAttrs) (blockAttrCaption blockAttrs)
let resultBlck = fromMaybe mempty resultsContent
return $ return $
(if exportsCode kv then labelledBlck else mempty) <> (if exportsCode kv then labelledBlck else mempty) <>
(if exportsResults kv then resultBlck else mempty) (if exportsResults kv then resultsContent else mempty)
where where
labelDiv :: Blocks -> F Inlines -> F Blocks labelDiv :: Blocks -> F Inlines -> F Blocks
labelDiv blk value = labelDiv blk value =
@ -325,12 +319,16 @@ codeBlock blockAttrs blockType = do
exportsResults :: [(String, String)] -> Bool exportsResults :: [(String, String)] -> Bool
exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports" exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports"
trailingResultsBlock :: PandocMonad m => OrgParser m (Maybe (F Blocks)) -- | Parse the result of an evaluated babel code block.
trailingResultsBlock = optionMaybe . try $ do babelResultsBlock :: PandocMonad m => OrgParser m (F Blocks)
babelResultsBlock = try $ do
blanklines blanklines
stringAnyCase "#+RESULTS:" resultsMarker <|>
blankline (lookAhead . void . try $
manyTill (metaLineStart *> anyLineNewline) resultsMarker)
block block
where
resultsMarker = try . void $ stringAnyCase "#+RESULTS:" *> blankline
-- | Parse code block arguments -- | Parse code block arguments
codeHeaderArgs :: Monad m => OrgParser m ([String], [(String, String)]) codeHeaderArgs :: Monad m => OrgParser m ([String], [(String, String)])

View file

@ -44,7 +44,7 @@ import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Control.Monad (mzero, void) import Control.Monad (mzero, void, when)
import Data.Char (toLower) import Data.Char (toLower)
import Data.List (intersperse) import Data.List (intersperse)
import qualified Data.Map as M import qualified Data.Map as M
@ -75,7 +75,9 @@ declarationLine :: PandocMonad m => OrgParser m ()
declarationLine = try $ do declarationLine = try $ do
key <- map toLower <$> metaKey key <- map toLower <$> metaKey
(key', value) <- metaValue key (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 :: Monad m => OrgParser m String
metaKey = map toLower <$> many1 (noneOf ": \n\r") metaKey = map toLower <$> many1 (noneOf ": \n\r")

44
test/command/3706.md Normal file
View file

@ -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
[]
```