Parse line-oriented markup as LineBlock
Markup-features focusing on lines as distinctive part of the markup are read into `LineBlock` elements. This currently means line blocks in reStructuredText and Markdown (the latter only if the `line_block` extension is enabled), the `linegroup`/`line` combination from the Docbook 5.1 working draft, and Org-mode `VERSE` blocks.
This commit is contained in:
parent
22cb9e3327
commit
c9460e7013
8 changed files with 34 additions and 26 deletions
|
@ -592,8 +592,6 @@ checkInMeta p = do
|
|||
when accepts p
|
||||
return mempty
|
||||
|
||||
|
||||
|
||||
addMeta :: ToMetaValue a => String -> a -> DB ()
|
||||
addMeta field val = modify (setMeta field val)
|
||||
|
||||
|
@ -612,7 +610,7 @@ isBlockElement (Elem e) = qName (elName e) `elem` blocktags
|
|||
"important","caution","note","tip","warning","qandadiv",
|
||||
"question","answer","abstract","itemizedlist","orderedlist",
|
||||
"variablelist","article","book","table","informaltable",
|
||||
"informalexample",
|
||||
"informalexample", "linegroup",
|
||||
"screen","programlisting","example","calloutlist"]
|
||||
isBlockElement _ = False
|
||||
|
||||
|
@ -779,6 +777,7 @@ parseBlock (Elem e) =
|
|||
"informaltable" -> parseTable
|
||||
"informalexample" -> divWith ("", ["informalexample"], []) <$>
|
||||
getBlocks e
|
||||
"linegroup" -> lineBlock <$> lineItems
|
||||
"literallayout" -> codeBlockWithLang
|
||||
"screen" -> codeBlockWithLang
|
||||
"programlisting" -> codeBlockWithLang
|
||||
|
@ -900,6 +899,7 @@ parseBlock (Elem e) =
|
|||
let ident = attrValue "id" e
|
||||
modify $ \st -> st{ dbSectionLevel = n - 1 }
|
||||
return $ headerWith (ident,[],[]) n' headerText <> b
|
||||
lineItems = mapM getInlines $ filterChildren (named "line") e
|
||||
metaBlock = acceptingMetadata (getBlocks e) >> return mempty
|
||||
|
||||
getInlines :: Element -> DB Inlines
|
||||
|
|
|
@ -32,7 +32,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
|
|||
module Text.Pandoc.Readers.Markdown ( readMarkdown,
|
||||
readMarkdownWithWarnings ) where
|
||||
|
||||
import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
|
||||
import Data.List ( transpose, sortBy, findIndex, intercalate )
|
||||
import qualified Data.Map as M
|
||||
import Data.Scientific (coefficient, base10Exponent)
|
||||
import Data.Ord ( comparing )
|
||||
|
@ -1106,7 +1106,7 @@ lineBlock = try $ do
|
|||
guardEnabled Ext_line_blocks
|
||||
lines' <- lineBlockLines >>=
|
||||
mapM (parseFromString (trimInlinesF . mconcat <$> many inline))
|
||||
return $ B.para <$> (mconcat $ intersperse (return B.linebreak) lines')
|
||||
return $ B.lineBlock <$> sequence lines'
|
||||
|
||||
--
|
||||
-- Tables
|
||||
|
|
|
@ -50,7 +50,7 @@ import Text.Pandoc.Shared ( compactify', compactify'DL )
|
|||
|
||||
import Control.Monad ( foldM, guard, mzero, void )
|
||||
import Data.Char ( isSpace, toLower, toUpper)
|
||||
import Data.List ( foldl', intersperse, isPrefixOf )
|
||||
import Data.List ( foldl', isPrefixOf )
|
||||
import Data.Maybe ( fromMaybe, isNothing )
|
||||
import Data.Monoid ((<>))
|
||||
|
||||
|
@ -427,7 +427,7 @@ verseBlock :: String -> OrgParser (F Blocks)
|
|||
verseBlock blockType = try $ do
|
||||
ignHeaders
|
||||
content <- rawBlockContent blockType
|
||||
fmap B.para . mconcat . intersperse (pure B.linebreak)
|
||||
fmap B.lineBlock . sequence
|
||||
<$> mapM parseVerseLine (lines content)
|
||||
where
|
||||
-- replace initial spaces with nonbreaking spaces to preserve
|
||||
|
|
|
@ -39,7 +39,7 @@ import Text.Pandoc.Shared
|
|||
import Text.Pandoc.Parsing
|
||||
import Text.Pandoc.Options
|
||||
import Control.Monad ( when, liftM, guard, mzero )
|
||||
import Data.List ( findIndex, intersperse, intercalate,
|
||||
import Data.List ( findIndex, intercalate,
|
||||
transpose, sort, deleteFirstsBy, isSuffixOf , nub, union)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import qualified Data.Map as M
|
||||
|
@ -228,7 +228,7 @@ lineBlock :: RSTParser Blocks
|
|||
lineBlock = try $ do
|
||||
lines' <- lineBlockLines
|
||||
lines'' <- mapM parseInlineFromString lines'
|
||||
return $ B.para (mconcat $ intersperse B.linebreak lines'')
|
||||
return $ B.lineBlock lines''
|
||||
|
||||
--
|
||||
-- paragraph block
|
||||
|
|
|
@ -1490,14 +1490,11 @@ tests =
|
|||
mconcat
|
||||
[ para $ spcSep [ "The", "first", "lines", "of"
|
||||
, "Goethe's", emph "Faust" <> ":"]
|
||||
, para $ mconcat
|
||||
[ spcSep [ "Habe", "nun,", "ach!", "Philosophie," ]
|
||||
, linebreak
|
||||
, spcSep [ "Juristerei", "und", "Medizin," ]
|
||||
, linebreak
|
||||
, spcSep [ "Und", "leider", "auch", "Theologie!" ]
|
||||
, linebreak
|
||||
, spcSep [ "Durchaus", "studiert,", "mit", "heißem", "Bemühn." ]
|
||||
, lineBlock
|
||||
[ "Habe nun, ach! Philosophie,"
|
||||
, "Juristerei und Medizin,"
|
||||
, "Und leider auch Theologie!"
|
||||
, "Durchaus studiert, mit heißem Bemühn."
|
||||
]
|
||||
]
|
||||
|
||||
|
@ -1508,7 +1505,7 @@ tests =
|
|||
, "bar"
|
||||
, "#+END_VERSE"
|
||||
] =?>
|
||||
para ("foo" <> linebreak <> linebreak <> "bar")
|
||||
lineBlock [ "foo", mempty, "bar" ]
|
||||
|
||||
, "Verse block with varying indentation" =:
|
||||
unlines [ "#+BEGIN_VERSE"
|
||||
|
@ -1516,7 +1513,7 @@ tests =
|
|||
, "my old friend"
|
||||
, "#+END_VERSE"
|
||||
] =?>
|
||||
para ("\160\160hello darkness" <> linebreak <> "my old friend")
|
||||
lineBlock [ "\160\160hello darkness", "my old friend" ]
|
||||
|
||||
, "Raw block LaTeX" =:
|
||||
unlines [ "#+BEGIN_LaTeX"
|
||||
|
|
|
@ -19,8 +19,7 @@ infix 4 =:
|
|||
|
||||
tests :: [Test]
|
||||
tests = [ "line block with blank line" =:
|
||||
"| a\n|\n| b" =?> para (str "a") <>
|
||||
para (str "\160b")
|
||||
"| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ]
|
||||
, testGroup "field list"
|
||||
[ "general" =: unlines
|
||||
[ "para"
|
||||
|
@ -135,7 +134,7 @@ tests = [ "line block with blank line" =:
|
|||
codeBlock "block quotes\n\ncan go on for many lines" <>
|
||||
para "but must stop here")
|
||||
, "line block with 3 lines" =: "| a\n| b\n| c"
|
||||
=?> para ("a" <> linebreak <> "b" <> linebreak <> "c")
|
||||
=?> lineBlock ["a", "b", "c"]
|
||||
, "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph"
|
||||
=?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph"
|
||||
, "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph"
|
||||
|
|
|
@ -84,8 +84,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
|
|||
,BlockQuote
|
||||
[Header 2 ("foobar",["baz"],[("key","val")]) [Str "Header",Space,Str "attributes",Space,Str "inside",Space,Str "block",Space,Str "quote"]]
|
||||
,Header 2 ("line-blocks",[],[]) [Str "Line",Space,Str "blocks"]
|
||||
,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,Para [Str "Continuation",Space,Str "line",LineBreak,Str "\160\160and",Space,Str "another"]
|
||||
,LineBlock
|
||||
[[Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be"]
|
||||
,[Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,"]
|
||||
,[Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,"]
|
||||
,[Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,[]
|
||||
,[Str "Continuation",Space,Str "line"]
|
||||
,[Str "\160\160and",Space,Str "another"]]
|
||||
,Header 2 ("grid-tables",[],[]) [Str "Grid",Space,Str "Tables"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
|
|
|
@ -230,8 +230,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Str "Another",Space,Str "paragraph"]
|
||||
,Para [Str "A",Space,Str "third",Space,Str "paragraph"]
|
||||
,Header 1 ("line-blocks",[],[]) [Str "Line",Space,Str "blocks"]
|
||||
,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,Para [Str "Continuation",Space,Str "line",LineBreak,Str "\160\160and",Space,Str "another"]
|
||||
,LineBlock
|
||||
[[Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be"]
|
||||
,[Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,"]
|
||||
,[Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,"]
|
||||
,[Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,[]
|
||||
,[Str "Continuation",Space,Str "line"]
|
||||
,[Str "\160\160and",Space,Str "another"]]
|
||||
,Header 1 ("simple-tables",[],[]) [Str "Simple",Space,Str "Tables"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
|
|
Loading…
Reference in a new issue