Org reader: Read inline code blocks
Org's inline code blocks take forms like `src_haskell(print "hi")` and are frequently used to include results from computations called from within the document. The blocks are read as inline code and marked with the special class `rundoc-block`. Proper handling and execution of these blocks is the subject of a separate library, rundoc, which is work in progress. This closes #1278.
This commit is contained in:
parent
7524e8e1f0
commit
71bd4fb2b3
2 changed files with 58 additions and 3 deletions
|
@ -43,6 +43,7 @@ import Text.Pandoc.Shared (compactify', compactify'DL)
|
||||||
|
|
||||||
import Control.Applicative ( Applicative, pure
|
import Control.Applicative ( Applicative, pure
|
||||||
, (<$>), (<$), (<*>), (<*), (*>), (<**>) )
|
, (<$>), (<$), (<*>), (<*), (*>), (<**>) )
|
||||||
|
import Control.Arrow (first)
|
||||||
import Control.Monad (foldM, guard, liftM, liftM2, mzero, when)
|
import Control.Monad (foldM, guard, liftM, liftM2, mzero, when)
|
||||||
import Control.Monad.Reader (Reader, runReader, ask, asks)
|
import Control.Monad.Reader (Reader, runReader, ask, asks)
|
||||||
import Data.Char (isAlphaNum, toLower)
|
import Data.Char (isAlphaNum, toLower)
|
||||||
|
@ -721,7 +722,6 @@ bulletList = fmap B.bulletList . fmap compactify' . sequence
|
||||||
<$> many1 (listItem bulletListStart)
|
<$> many1 (listItem bulletListStart)
|
||||||
|
|
||||||
orderedList :: OrgParser (F Blocks)
|
orderedList :: OrgParser (F Blocks)
|
||||||
-- orderedList = B.orderedList . compactify' <$> many1 (listItem orderedListStart)
|
|
||||||
orderedList = fmap B.orderedList . fmap compactify' . sequence
|
orderedList = fmap B.orderedList . fmap compactify' . sequence
|
||||||
<$> many1 (listItem orderedListStart)
|
<$> many1 (listItem orderedListStart)
|
||||||
|
|
||||||
|
@ -746,11 +746,11 @@ definitionListItem :: OrgParser Int
|
||||||
definitionListItem parseMarkerGetLength = try $ do
|
definitionListItem parseMarkerGetLength = try $ do
|
||||||
markerLength <- parseMarkerGetLength
|
markerLength <- parseMarkerGetLength
|
||||||
term <- manyTill (noneOf "\n\r") (try $ string "::")
|
term <- manyTill (noneOf "\n\r") (try $ string "::")
|
||||||
first <- anyLineNewline
|
line1 <- anyLineNewline
|
||||||
blank <- option "" ("\n" <$ blankline)
|
blank <- option "" ("\n" <$ blankline)
|
||||||
cont <- concat <$> many (listContinuation markerLength)
|
cont <- concat <$> many (listContinuation markerLength)
|
||||||
term' <- parseFromString inline term
|
term' <- parseFromString inline term
|
||||||
contents' <- parseFromString parseBlocks $ first ++ blank ++ cont
|
contents' <- parseFromString parseBlocks $ line1 ++ blank ++ cont
|
||||||
return $ (,) <$> term' <*> fmap (:[]) contents'
|
return $ (,) <$> term' <*> fmap (:[]) contents'
|
||||||
|
|
||||||
|
|
||||||
|
@ -789,6 +789,7 @@ inline =
|
||||||
, footnote
|
, footnote
|
||||||
, linkOrImage
|
, linkOrImage
|
||||||
, anchor
|
, anchor
|
||||||
|
, inlineCodeBlock
|
||||||
, str
|
, str
|
||||||
, endline
|
, endline
|
||||||
, emph
|
, emph
|
||||||
|
@ -989,6 +990,42 @@ solidify = map replaceSpecialChar
|
||||||
| c `elem` "_.-:" = c
|
| c `elem` "_.-:" = c
|
||||||
| otherwise = '-'
|
| otherwise = '-'
|
||||||
|
|
||||||
|
-- | Parses an inline code block and marks it as an babel block.
|
||||||
|
inlineCodeBlock :: OrgParser (F Inlines)
|
||||||
|
inlineCodeBlock = try $ do
|
||||||
|
string "src_"
|
||||||
|
lang <- many1 orgArgWordChar
|
||||||
|
opts <- option [] $ enclosedByPair '[' ']' blockOption
|
||||||
|
inlineCode <- enclosedByPair '{' '}' (noneOf "\n\r")
|
||||||
|
let attrClasses = [translateLang lang, rundocBlockClass]
|
||||||
|
let attrKeyVal = map toRundocAttrib (("language", lang) : opts)
|
||||||
|
returnF $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode
|
||||||
|
where enclosedByPair s e p = char s *> many1Till p (char e)
|
||||||
|
|
||||||
|
-- | The class-name used to mark rundoc blocks.
|
||||||
|
rundocBlockClass :: String
|
||||||
|
rundocBlockClass = "rundoc-block"
|
||||||
|
|
||||||
|
blockOption :: OrgParser (String, String)
|
||||||
|
blockOption = try $ (,) <$> orgArgKey <*> orgArgValue
|
||||||
|
|
||||||
|
orgArgKey :: OrgParser String
|
||||||
|
orgArgKey = try $
|
||||||
|
skipSpaces *> char ':'
|
||||||
|
*> many1 orgArgWordChar
|
||||||
|
<* many1 spaceChar
|
||||||
|
|
||||||
|
orgArgValue :: OrgParser String
|
||||||
|
orgArgValue = try $
|
||||||
|
skipSpaces *> many1 orgArgWordChar
|
||||||
|
<* skipSpaces
|
||||||
|
|
||||||
|
orgArgWordChar :: OrgParser Char
|
||||||
|
orgArgWordChar = alphaNum <|> oneOf "-_"
|
||||||
|
|
||||||
|
toRundocAttrib :: (String, String) -> (String, String)
|
||||||
|
toRundocAttrib = first ("rundoc-" ++)
|
||||||
|
|
||||||
emph :: OrgParser (F Inlines)
|
emph :: OrgParser (F Inlines)
|
||||||
emph = fmap B.emph <$> emphasisBetween '/'
|
emph = fmap B.emph <$> emphasisBetween '/'
|
||||||
|
|
||||||
|
|
|
@ -207,6 +207,24 @@ tests =
|
||||||
"<<anchor>> Link here later." =?>
|
"<<anchor>> Link here later." =?>
|
||||||
(para $ spanWith ("anchor", [], []) mempty <>
|
(para $ spanWith ("anchor", [], []) mempty <>
|
||||||
"Link" <> space <> "here" <> space <> "later.")
|
"Link" <> space <> "here" <> space <> "later.")
|
||||||
|
|
||||||
|
, "Inline code block" =:
|
||||||
|
"src_emacs-lisp{(message \"Hello\")}" =?>
|
||||||
|
(para $ codeWith ( ""
|
||||||
|
, [ "commonlisp", "rundoc-block" ]
|
||||||
|
, [ ("rundoc-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")
|
||||||
|
]
|
||||||
|
)
|
||||||
|
"echo 'Hello, World'")
|
||||||
]
|
]
|
||||||
|
|
||||||
, testGroup "Meta Information" $
|
, testGroup "Meta Information" $
|
||||||
|
|
Loading…
Reference in a new issue