Shared: introduce blocksToInlines function

This is a lossy function for converting `[Block] -> [Inline]`. Its main
use, at the moment, is for docx comments, which can contain arbitrary
blocks (except for footnotes), but which will be converted to spans.

This is, at the moment, pretty useless for everything but the basic
`Para` and `Plain` comments. It can be improved, but the docx reader
should probably emit a warning if the comment contains more than this.
This commit is contained in:
Jesse Rosenthal 2016-06-22 13:04:25 -04:00
parent 319a56aefc
commit 2b701f9389

View file

@ -89,6 +89,8 @@ module Text.Pandoc.Shared (
warn,
mapLeft,
hush,
-- * for squashing blocks
blocksToInlines,
-- * Safe read
safeRead,
-- * Temp directory
@ -1020,6 +1022,41 @@ collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
isSingleton _ = Nothing
checkPathSeperator = fmap isPathSeparator . isSingleton
---
--- Squash blocks into inlines
---
blockToInlines :: Block -> [Inline]
blockToInlines (Plain ils) = ils
blockToInlines (Para ils) = ils
blockToInlines (CodeBlock attr str) = [Code attr str]
blockToInlines (RawBlock fmt str) = [RawInline fmt str]
blockToInlines (OrderedList _ blkslst) =
concatMap blocksToInlines blkslst
blockToInlines (BulletList blkslst) =
concatMap blocksToInlines blkslst
blockToInlines (DefinitionList pairslst) =
concatMap f pairslst
where
f (ils, blkslst) = ils ++
[Str ":", Space] ++
(concatMap blocksToInlines blkslst)
blockToInlines (Header _ _ ils) = ils
blockToInlines (HorizontalRule) = []
blockToInlines (Table _ _ _ headers rows) =
intercalate [LineBreak] $ map (concatMap blocksToInlines) tbl
where
tbl = headers : rows
blockToInlines (Div _ blks) = blocksToInlines blks
blockToInlines Null = []
blocksToInlinesWithSep :: [Inline] -> [Block] -> [Inline]
blocksToInlinesWithSep sep blks = intercalate sep $ map blockToInlines blks
blocksToInlines :: [Block] -> [Inline]
blocksToInlines = blocksToInlinesWithSep [Space, Str "", Space]
--
-- Safe read
--