Org reader: stop adding rundoc prefix to src params
Source block parameter names are no longer prefixed with *rundoc*. This was intended to simplify working with the rundoc project, a babel runner. However, the rundoc project is unmaintained, and adding those markers is not the reader's job anyway. The original language that is specified for a source element is now retained as the `data-org-language` attribute and only added if it differs from the translated language.
This commit is contained in:
parent
04658c491b
commit
2e43e27e5c
4 changed files with 50 additions and 72 deletions
|
@ -39,8 +39,7 @@ import Text.Pandoc.Readers.Org.Meta (metaExport, metaKey, metaLine)
|
|||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
import Text.Pandoc.Readers.Org.Shared (cleanLinkString, isImageFilename,
|
||||
rundocBlockClass, toRundocAttrib,
|
||||
translateLang)
|
||||
originalLang, translateLang)
|
||||
|
||||
import Text.Pandoc.Builder (Blocks, Inlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
|
@ -493,16 +492,14 @@ codeBlock blockAttrs blockType = do
|
|||
content <- rawBlockContent blockType
|
||||
resultsContent <- trailingResultsBlock
|
||||
let id' = fromMaybe mempty $ blockAttrName blockAttrs
|
||||
let includeCode = exportsCode kv
|
||||
let includeResults = exportsResults kv
|
||||
let codeBlck = B.codeBlockWith ( id', classes, kv ) content
|
||||
let labelledBlck = maybe (pure codeBlck)
|
||||
(labelDiv codeBlck)
|
||||
(blockAttrCaption blockAttrs)
|
||||
let resultBlck = fromMaybe mempty resultsContent
|
||||
return $
|
||||
(if includeCode then labelledBlck else mempty) <>
|
||||
(if includeResults then resultBlck else mempty)
|
||||
(if exportsCode kv then labelledBlck else mempty) <>
|
||||
(if exportsResults kv then resultBlck else mempty)
|
||||
where
|
||||
labelDiv :: Blocks -> F Inlines -> F Blocks
|
||||
labelDiv blk value =
|
||||
|
@ -511,13 +508,11 @@ codeBlock blockAttrs blockType = do
|
|||
labelledBlock :: F Inlines -> F Blocks
|
||||
labelledBlock = fmap (B.plain . B.spanWith ("", ["label"], []))
|
||||
|
||||
exportsCode :: [(String, String)] -> Bool
|
||||
exportsCode attrs = not (("rundoc-exports", "none") `elem` attrs
|
||||
|| ("rundoc-exports", "results") `elem` attrs)
|
||||
exportsCode :: [(String, String)] -> Bool
|
||||
exportsCode = maybe True (`elem` ["code", "both"]) . lookup "exports"
|
||||
|
||||
exportsResults :: [(String, String)] -> Bool
|
||||
exportsResults attrs = ("rundoc-exports", "results") `elem` attrs
|
||||
|| ("rundoc-exports", "both") `elem` attrs
|
||||
exportsResults :: [(String, String)] -> Bool
|
||||
exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports"
|
||||
|
||||
trailingResultsBlock :: PandocMonad m => OrgParser m (Maybe (F Blocks))
|
||||
trailingResultsBlock = optionMaybe . try $ do
|
||||
|
@ -532,16 +527,9 @@ codeHeaderArgs = try $ do
|
|||
language <- skipSpaces *> orgArgWord
|
||||
(switchClasses, switchKv) <- switchesAsAttributes
|
||||
parameters <- manyTill blockOption newline
|
||||
let pandocLang = translateLang language
|
||||
let classes = pandocLang : switchClasses
|
||||
return $
|
||||
if hasRundocParameters parameters
|
||||
then ( classes <> [ rundocBlockClass ]
|
||||
, switchKv <> map toRundocAttrib (("language", language) : parameters)
|
||||
)
|
||||
else (classes, switchKv <> parameters)
|
||||
where
|
||||
hasRundocParameters = not . null
|
||||
return $ ( translateLang language : switchClasses
|
||||
, originalLang language <> switchKv <> parameters
|
||||
)
|
||||
|
||||
switchesAsAttributes :: Monad m => OrgParser m ([String], [(String, String)])
|
||||
switchesAsAttributes = try $ do
|
||||
|
|
|
@ -37,8 +37,7 @@ import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker)
|
|||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
import Text.Pandoc.Readers.Org.Shared (cleanLinkString, isImageFilename,
|
||||
rundocBlockClass, toRundocAttrib,
|
||||
translateLang)
|
||||
originalLang, translateLang)
|
||||
|
||||
import Text.Pandoc.Builder (Inlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
|
@ -518,8 +517,8 @@ inlineCodeBlock = try $ do
|
|||
lang <- many1 orgArgWordChar
|
||||
opts <- option [] $ enclosedByPair '[' ']' inlineBlockOption
|
||||
inlineCode <- enclosedByPair '{' '}' (noneOf "\n\r")
|
||||
let attrClasses = [translateLang lang, rundocBlockClass]
|
||||
let attrKeyVal = map toRundocAttrib (("language", lang) : opts)
|
||||
let attrClasses = [translateLang lang]
|
||||
let attrKeyVal = originalLang lang <> opts
|
||||
returnF $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode
|
||||
where
|
||||
inlineBlockOption :: PandocMonad m => OrgParser m (String, String)
|
||||
|
|
|
@ -29,12 +29,10 @@ Utility functions used in other Pandoc Org modules.
|
|||
module Text.Pandoc.Readers.Org.Shared
|
||||
( cleanLinkString
|
||||
, isImageFilename
|
||||
, rundocBlockClass
|
||||
, toRundocAttrib
|
||||
, originalLang
|
||||
, translateLang
|
||||
) where
|
||||
|
||||
import Control.Arrow (first)
|
||||
import Data.Char (isAlphaNum)
|
||||
import Data.List (isPrefixOf, isSuffixOf)
|
||||
|
||||
|
@ -68,17 +66,17 @@ cleanLinkString s =
|
|||
in all (\c -> isAlphaNum c || c `elem` (".-"::String)) scheme
|
||||
&& not (null path)
|
||||
|
||||
-- | Prefix used for Rundoc classes and arguments.
|
||||
rundocPrefix :: String
|
||||
rundocPrefix = "rundoc-"
|
||||
-- | Creates an key-value pair marking the original language name specified for
|
||||
-- a piece of source code.
|
||||
|
||||
-- | The class-name used to mark rundoc blocks.
|
||||
rundocBlockClass :: String
|
||||
rundocBlockClass = rundocPrefix ++ "block"
|
||||
|
||||
-- | Prefix the name of a attribute, marking it as a code execution parameter.
|
||||
toRundocAttrib :: (String, String) -> (String, String)
|
||||
toRundocAttrib = first (rundocPrefix ++)
|
||||
-- | Creates an key-value attributes marking the original language name
|
||||
-- specified for a piece of source code.
|
||||
originalLang :: String -> [(String, String)]
|
||||
originalLang lang =
|
||||
let transLang = translateLang lang
|
||||
in if transLang == lang
|
||||
then []
|
||||
else [("data-org-language", lang)]
|
||||
|
||||
-- | Translate from Org-mode's programming language identifiers to those used
|
||||
-- by Pandoc. This is useful to allow for proper syntax highlighting in
|
||||
|
|
|
@ -275,17 +275,17 @@ tests =
|
|||
, "Inline code block" =:
|
||||
"src_emacs-lisp{(message \"Hello\")}" =?>
|
||||
(para $ codeWith ( ""
|
||||
, [ "commonlisp", "rundoc-block" ]
|
||||
, [ ("rundoc-language", "emacs-lisp") ])
|
||||
, [ "commonlisp" ]
|
||||
, [ ("data-org-language", "emacs-lisp") ])
|
||||
"(message \"Hello\")")
|
||||
|
||||
, "Inline code block with arguments" =:
|
||||
"src_sh[:export both :results output]{echo 'Hello, World'}" =?>
|
||||
(para $ codeWith ( ""
|
||||
, [ "bash", "rundoc-block" ]
|
||||
, [ ("rundoc-language", "sh")
|
||||
, ("rundoc-export", "both")
|
||||
, ("rundoc-results", "output")
|
||||
, [ "bash" ]
|
||||
, [ ("data-org-language", "sh")
|
||||
, ("export", "both")
|
||||
, ("results", "output")
|
||||
]
|
||||
)
|
||||
"echo 'Hello, World'")
|
||||
|
@ -293,9 +293,9 @@ tests =
|
|||
, "Inline code block with toggle" =:
|
||||
"src_sh[:toggle]{echo $HOME}" =?>
|
||||
(para $ codeWith ( ""
|
||||
, [ "bash", "rundoc-block" ]
|
||||
, [ ("rundoc-language", "sh")
|
||||
, ("rundoc-toggle", "yes")
|
||||
, [ "bash" ]
|
||||
, [ ("data-org-language", "sh")
|
||||
, ("toggle", "yes")
|
||||
]
|
||||
)
|
||||
"echo $HOME")
|
||||
|
@ -1472,16 +1472,14 @@ tests =
|
|||
in mconcat [ para $ spcSep [ "Low", "German", "greeting" ]
|
||||
, codeBlockWith attr' code'
|
||||
]
|
||||
, "Source block with rundoc/babel arguments" =:
|
||||
, "Source block with babel arguments" =:
|
||||
unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
|
||||
, "(progn (message \"Hello, World!\")"
|
||||
, " (+ 23 42))"
|
||||
, "#+END_SRC" ] =?>
|
||||
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
||||
, "rundoc-block"
|
||||
]
|
||||
params = [ ("rundoc-language", "emacs-lisp")
|
||||
, ("rundoc-exports", "both")
|
||||
let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax
|
||||
params = [ ("data-org-language", "emacs-lisp")
|
||||
, ("exports", "both")
|
||||
]
|
||||
code' = unlines [ "(progn (message \"Hello, World!\")"
|
||||
, " (+ 23 42))" ]
|
||||
|
@ -1495,11 +1493,9 @@ tests =
|
|||
, ""
|
||||
, "#+RESULTS:"
|
||||
, ": 65"] =?>
|
||||
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
||||
, "rundoc-block"
|
||||
]
|
||||
params = [ ("rundoc-language", "emacs-lisp")
|
||||
, ("rundoc-exports", "both")
|
||||
let classes = [ "commonlisp" ]
|
||||
params = [ ("data-org-language", "emacs-lisp")
|
||||
, ("exports", "both")
|
||||
]
|
||||
code' = unlines [ "(progn (message \"Hello, World!\")"
|
||||
, " (+ 23 42))" ]
|
||||
|
@ -1516,11 +1512,9 @@ tests =
|
|||
, ""
|
||||
, "#+RESULTS:"
|
||||
, ": 65" ] =?>
|
||||
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
||||
, "rundoc-block"
|
||||
]
|
||||
params = [ ("rundoc-language", "emacs-lisp")
|
||||
, ("rundoc-exports", "code")
|
||||
let classes = [ "commonlisp" ]
|
||||
params = [ ("data-org-language", "emacs-lisp")
|
||||
, ("exports", "code")
|
||||
]
|
||||
code' = unlines [ "(progn (message \"Hello, World!\")"
|
||||
, " (+ 23 42))" ]
|
||||
|
@ -1552,8 +1546,8 @@ tests =
|
|||
, "echo $HOME"
|
||||
, "#+END_SRC"
|
||||
] =?>
|
||||
let classes = [ "bash", "rundoc-block" ]
|
||||
params = [ ("rundoc-language", "sh"), ("rundoc-noeval", "yes") ]
|
||||
let classes = [ "bash" ]
|
||||
params = [ ("data-org-language", "sh"), ("noeval", "yes") ]
|
||||
in codeBlockWith ("", classes, params) "echo $HOME\n"
|
||||
|
||||
, "Source block with line number switch" =:
|
||||
|
@ -1562,7 +1556,7 @@ tests =
|
|||
, "#+END_SRC"
|
||||
] =?>
|
||||
let classes = [ "bash", "numberLines" ]
|
||||
params = [ ("startFrom", "10") ]
|
||||
params = [ ("data-org-language", "sh"), ("startFrom", "10") ]
|
||||
in codeBlockWith ("", classes, params) ":() { :|:& };:\n"
|
||||
|
||||
, "Example block" =:
|
||||
|
@ -1712,12 +1706,11 @@ tests =
|
|||
, "code body"
|
||||
, "#+END_SRC"
|
||||
] =?>
|
||||
let classes = [ "c", "rundoc-block" ]
|
||||
params = [ ("rundoc-language", "C")
|
||||
, ("rundoc-tangle", "xxxx.c")
|
||||
, ("rundoc-city", "Zürich")
|
||||
let params = [ ("data-org-language", "C")
|
||||
, ("tangle", "xxxx.c")
|
||||
, ("city", "Zürich")
|
||||
]
|
||||
in codeBlockWith ( "", classes, params) "code body\n"
|
||||
in codeBlockWith ( "", ["c"], params) "code body\n"
|
||||
]
|
||||
|
||||
, testGroup "Smart punctuation"
|
||||
|
|
Loading…
Reference in a new issue