RST reader: handle code, literal, number-lines, class, name for include.

This commit is contained in:
John MacFarlane 2016-12-04 23:29:22 +01:00
parent d595702b17
commit 03ede3e312

View file

@ -41,7 +41,7 @@ import qualified Text.Pandoc.UTF8 as UTF8
import Control.Monad ( when, liftM, guard, mzero )
import Data.List ( findIndex, intercalate,
transpose, sort, deleteFirstsBy, isSuffixOf , nub, union)
import Data.Maybe (fromMaybe)
import Data.Maybe (fromMaybe, isJust)
import qualified Data.Map as M
import Text.Printf ( printf )
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
@ -402,28 +402,11 @@ blockQuote = do
return $ B.blockQuote contents
{-
From RST docs:
The following options are recognized:
[x] start-line : integer
[x] end-line : integer
[ ] start-after : text to find in the external data file
Only the content after the first occurrence of the specified text will be included.
[ ] end-before : text to find in the external data file
Only the content before the first occurrence of the specified text (but after any after text) will be included.
Combining start/end-line and start-after/end-before is possible. The text markers will be searched in the specified lines (further limiting the included content).
[ ] literal : flag (empty)
The entire included text is inserted into the document as a single literal block.
[ ] code : formal language (optional)
The argument and the content of the included file are passed to the code directive (useful for program listings). (New in Docutils 0.9)
[ ] number-lines : [start line number]
Precede every code line with a line number. The optional argument is the number of the first line (defaut 1). Works only with code or literal. (New in Docutils 0.9)
[ ] encoding : name of text encoding
The text encoding of the external data file. Defaults to the document's input_encoding.
[ ] tab-width : integer
Number of spaces for hard tab expansion. A negative value prevents expansion of hard tabs. Defaults to the tab_width configuration setting.
[ ] class (common option) - with code or literal
[ ] name (common option) - with code or literal
Unsupported options for include:
tab-width
encoding
start-after: text to find
end-before: text to find
-}
include :: PandocMonad m => RSTParser m Blocks
@ -461,13 +444,27 @@ include = try $ do
let contents' = unlines $ drop (startLine' - 1)
$ take (endLine' - 1)
$ contentLines
setPosition $ newPos f 1 1
setInput contents'
bs <- optional blanklines >> (mconcat <$> many block)
setInput oldInput
setPosition oldPos
updateState $ \s -> s{ stateContainers = tail $ stateContainers s }
return bs
case lookup "code" fields of
Just lang -> do
let numberLines = lookup "number-lines" fields
let classes = trimr lang : ["numberLines" | isJust numberLines] ++
maybe [] words (lookup "class" fields)
let kvs = maybe [] (\n -> [("startFrom", trimr n)]) numberLines
let ident = maybe "" trimr $ lookup "name" fields
let attribs = (ident, classes, kvs)
return $ B.codeBlockWith attribs contents'
Nothing -> case lookup "literal" fields of
Just _ -> return $ B.rawBlock "rst" contents'
Nothing -> do
setPosition $ newPos f 1 1
setInput contents'
bs <- optional blanklines >>
(mconcat <$> many block)
setInput oldInput
setPosition oldPos
updateState $ \s -> s{ stateContainers =
tail $ stateContainers s }
return bs
readFileLazy' :: PandocMonad m => FilePath -> m (Either PandocError String)
readFileLazy' f = catchError ((Right . UTF8.toStringLazy) <$> readFileLazy f) $