Shared: rename compactify', compactify'DL -> compactify, compactifyDL.
This commit is contained in:
parent
56f74cb0ab
commit
5156a4fe3c
8 changed files with 29 additions and 29 deletions
|
@ -868,7 +868,7 @@ removeOneLeadingSpace xs =
|
||||||
startsWithSpace (y:_) = y == ' '
|
startsWithSpace (y:_) = y == ' '
|
||||||
|
|
||||||
compactifyCell :: Blocks -> Blocks
|
compactifyCell :: Blocks -> Blocks
|
||||||
compactifyCell bs = head $ compactify' [bs]
|
compactifyCell bs = head $ compactify [bs]
|
||||||
|
|
||||||
-- | Parse footer for a grid table.
|
-- | Parse footer for a grid table.
|
||||||
gridTableFooter :: Stream s m Char => ParserT s ParserState m [Char]
|
gridTableFooter :: Stream s m Char => ParserT s ParserState m [Char]
|
||||||
|
|
|
@ -909,12 +909,12 @@ orderedList = try $ do
|
||||||
atMostSpaces (tabStop - (endpos - startpos))
|
atMostSpaces (tabStop - (endpos - startpos))
|
||||||
return res )
|
return res )
|
||||||
start' <- option 1 $ guardEnabled Ext_startnum >> return start
|
start' <- option 1 $ guardEnabled Ext_startnum >> return start
|
||||||
return $ B.orderedListWith (start', style, delim) <$> fmap compactify' items
|
return $ B.orderedListWith (start', style, delim) <$> fmap compactify items
|
||||||
|
|
||||||
bulletList :: PandocMonad m => MarkdownParser m (F Blocks)
|
bulletList :: PandocMonad m => MarkdownParser m (F Blocks)
|
||||||
bulletList = do
|
bulletList = do
|
||||||
items <- fmap sequence $ many1 $ listItem bulletListStart
|
items <- fmap sequence $ many1 $ listItem bulletListStart
|
||||||
return $ B.bulletList <$> fmap compactify' items
|
return $ B.bulletList <$> fmap compactify items
|
||||||
|
|
||||||
-- definition lists
|
-- definition lists
|
||||||
|
|
||||||
|
@ -972,7 +972,7 @@ compactDefinitionList :: PandocMonad m => MarkdownParser m (F Blocks)
|
||||||
compactDefinitionList = do
|
compactDefinitionList = do
|
||||||
guardEnabled Ext_compact_definition_lists
|
guardEnabled Ext_compact_definition_lists
|
||||||
items <- fmap sequence $ many1 $ definitionListItem True
|
items <- fmap sequence $ many1 $ definitionListItem True
|
||||||
return $ B.definitionList <$> fmap compactify'DL items
|
return $ B.definitionList <$> fmap compactifyDL items
|
||||||
|
|
||||||
normalDefinitionList :: PandocMonad m => MarkdownParser m (F Blocks)
|
normalDefinitionList :: PandocMonad m => MarkdownParser m (F Blocks)
|
||||||
normalDefinitionList = do
|
normalDefinitionList = do
|
||||||
|
@ -1349,7 +1349,7 @@ gridTableRow indices = do
|
||||||
colLines <- many1 (gridTableRawLine indices)
|
colLines <- many1 (gridTableRawLine indices)
|
||||||
let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $
|
let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $
|
||||||
transpose colLines
|
transpose colLines
|
||||||
fmap compactify' <$> fmap sequence (mapM (parseFromString parseBlocks) cols)
|
fmap compactify <$> fmap sequence (mapM (parseFromString parseBlocks) cols)
|
||||||
|
|
||||||
removeOneLeadingSpace :: [String] -> [String]
|
removeOneLeadingSpace :: [String] -> [String]
|
||||||
removeOneLeadingSpace xs =
|
removeOneLeadingSpace xs =
|
||||||
|
|
|
@ -663,7 +663,7 @@ read_list = matchingElement NsText "list"
|
||||||
--
|
--
|
||||||
read_list_item :: ElementMatcher [Blocks]
|
read_list_item :: ElementMatcher [Blocks]
|
||||||
read_list_item = matchingElement NsText "list-item"
|
read_list_item = matchingElement NsText "list-item"
|
||||||
$ liftA (compactify'.(:[]))
|
$ liftA (compactify.(:[]))
|
||||||
( matchChildContent' [ read_paragraph
|
( matchChildContent' [ read_paragraph
|
||||||
, read_header
|
, read_header
|
||||||
, read_list
|
, read_list
|
||||||
|
@ -749,7 +749,7 @@ read_table_row = matchingElement NsTable "table-row"
|
||||||
--
|
--
|
||||||
read_table_cell :: ElementMatcher [Blocks]
|
read_table_cell :: ElementMatcher [Blocks]
|
||||||
read_table_cell = matchingElement NsTable "table-cell"
|
read_table_cell = matchingElement NsTable "table-cell"
|
||||||
$ liftA (compactify'.(:[]))
|
$ liftA (compactify.(:[]))
|
||||||
$ matchChildContent' [ read_paragraph
|
$ matchChildContent' [ read_paragraph
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
|
@ -47,7 +47,7 @@ import Text.Pandoc.Builder ( Inlines, Blocks )
|
||||||
import Text.Pandoc.Class (PandocMonad)
|
import Text.Pandoc.Class (PandocMonad)
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Options
|
import Text.Pandoc.Options
|
||||||
import Text.Pandoc.Shared ( compactify', compactify'DL, safeRead )
|
import Text.Pandoc.Shared ( compactify, compactifyDL, safeRead )
|
||||||
|
|
||||||
import Control.Monad ( foldM, guard, mzero, void )
|
import Control.Monad ( foldM, guard, mzero, void )
|
||||||
import Data.Char ( isSpace, toLower, toUpper)
|
import Data.Char ( isSpace, toLower, toUpper)
|
||||||
|
@ -898,16 +898,16 @@ list = choice [ definitionList, bulletList, orderedList ] <?> "list"
|
||||||
|
|
||||||
definitionList :: PandocMonad m => OrgParser m (F Blocks)
|
definitionList :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
definitionList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
definitionList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
||||||
fmap B.definitionList . fmap compactify'DL . sequence
|
fmap B.definitionList . fmap compactifyDL . sequence
|
||||||
<$> many1 (definitionListItem $ bulletListStart' (Just n))
|
<$> many1 (definitionListItem $ bulletListStart' (Just n))
|
||||||
|
|
||||||
bulletList :: PandocMonad m => OrgParser m (F Blocks)
|
bulletList :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
bulletList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
bulletList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
||||||
fmap B.bulletList . fmap compactify' . sequence
|
fmap B.bulletList . fmap compactify . sequence
|
||||||
<$> many1 (listItem (bulletListStart' $ Just n))
|
<$> many1 (listItem (bulletListStart' $ Just n))
|
||||||
|
|
||||||
orderedList :: PandocMonad m => OrgParser m (F Blocks)
|
orderedList :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
orderedList = fmap B.orderedList . fmap compactify' . sequence
|
orderedList = fmap B.orderedList . fmap compactify . sequence
|
||||||
<$> many1 (listItem orderedListStart)
|
<$> many1 (listItem orderedListStart)
|
||||||
|
|
||||||
bulletListStart' :: Monad m => Maybe Int -> OrgParser m Int
|
bulletListStart' :: Monad m => Maybe Int -> OrgParser m Int
|
||||||
|
|
|
@ -574,11 +574,11 @@ orderedList :: PandocMonad m => RSTParser m Blocks
|
||||||
orderedList = try $ do
|
orderedList = try $ do
|
||||||
(start, style, delim) <- lookAhead (anyOrderedListMarker <* spaceChar)
|
(start, style, delim) <- lookAhead (anyOrderedListMarker <* spaceChar)
|
||||||
items <- many1 (listItem (orderedListStart style delim))
|
items <- many1 (listItem (orderedListStart style delim))
|
||||||
let items' = compactify' items
|
let items' = compactify items
|
||||||
return $ B.orderedListWith (start, style, delim) items'
|
return $ B.orderedListWith (start, style, delim) items'
|
||||||
|
|
||||||
bulletList :: PandocMonad m => RSTParser m Blocks
|
bulletList :: PandocMonad m => RSTParser m Blocks
|
||||||
bulletList = B.bulletList . compactify' <$> many1 (listItem bulletListStart)
|
bulletList = B.bulletList . compactify <$> many1 (listItem bulletListStart)
|
||||||
|
|
||||||
--
|
--
|
||||||
-- directive (e.g. comment, container, compound-paragraph)
|
-- directive (e.g. comment, container, compound-paragraph)
|
||||||
|
|
|
@ -37,7 +37,7 @@ import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Options
|
import Text.Pandoc.Options
|
||||||
import Text.Pandoc.Shared (escapeURI,compactify', compactify'DL)
|
import Text.Pandoc.Shared (escapeURI,compactify, compactifyDL)
|
||||||
import Text.Pandoc.Parsing hiding (space, spaces, uri, macro)
|
import Text.Pandoc.Parsing hiding (space, spaces, uri, macro)
|
||||||
import Data.Char (toLower)
|
import Data.Char (toLower)
|
||||||
import Data.List (transpose, intersperse, intercalate)
|
import Data.List (transpose, intersperse, intercalate)
|
||||||
|
@ -225,16 +225,16 @@ list :: T2T Blocks
|
||||||
list = choice [bulletList, orderedList, definitionList]
|
list = choice [bulletList, orderedList, definitionList]
|
||||||
|
|
||||||
bulletList :: T2T Blocks
|
bulletList :: T2T Blocks
|
||||||
bulletList = B.bulletList . compactify'
|
bulletList = B.bulletList . compactify
|
||||||
<$> many1 (listItem bulletListStart parseBlocks)
|
<$> many1 (listItem bulletListStart parseBlocks)
|
||||||
|
|
||||||
orderedList :: T2T Blocks
|
orderedList :: T2T Blocks
|
||||||
orderedList = B.orderedList . compactify'
|
orderedList = B.orderedList . compactify
|
||||||
<$> many1 (listItem orderedListStart parseBlocks)
|
<$> many1 (listItem orderedListStart parseBlocks)
|
||||||
|
|
||||||
definitionList :: T2T Blocks
|
definitionList :: T2T Blocks
|
||||||
definitionList = try $ do
|
definitionList = try $ do
|
||||||
B.definitionList . compactify'DL <$>
|
B.definitionList . compactifyDL <$>
|
||||||
many1 (listItem definitionListStart definitionListEnd)
|
many1 (listItem definitionListStart definitionListEnd)
|
||||||
|
|
||||||
definitionListEnd :: T2T (Inlines, [Blocks])
|
definitionListEnd :: T2T (Inlines, [Blocks])
|
||||||
|
|
|
@ -59,8 +59,8 @@ module Text.Pandoc.Shared (
|
||||||
deNote,
|
deNote,
|
||||||
stringify,
|
stringify,
|
||||||
capitalize,
|
capitalize,
|
||||||
compactify',
|
compactify,
|
||||||
compactify'DL,
|
compactifyDL,
|
||||||
linesToPara,
|
linesToPara,
|
||||||
Element (..),
|
Element (..),
|
||||||
hierarchicalize,
|
hierarchicalize,
|
||||||
|
@ -434,10 +434,10 @@ capitalize = walk go
|
||||||
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
||||||
-- no other @Para@ blocks. Like compactify, but operates on @Blocks@ rather
|
-- no other @Para@ blocks. Like compactify, but operates on @Blocks@ rather
|
||||||
-- than @[Block]@.
|
-- than @[Block]@.
|
||||||
compactify' :: [Blocks] -- ^ List of list items (each a list of blocks)
|
compactify :: [Blocks] -- ^ List of list items (each a list of blocks)
|
||||||
-> [Blocks]
|
-> [Blocks]
|
||||||
compactify' [] = []
|
compactify [] = []
|
||||||
compactify' items =
|
compactify items =
|
||||||
let (others, final) = (init items, last items)
|
let (others, final) = (init items, last items)
|
||||||
in case reverse (B.toList final) of
|
in case reverse (B.toList final) of
|
||||||
(Para a:xs) -> case [Para x | Para x <- concatMap B.toList items] of
|
(Para a:xs) -> case [Para x | Para x <- concatMap B.toList items] of
|
||||||
|
@ -446,9 +446,9 @@ compactify' items =
|
||||||
_ -> items
|
_ -> items
|
||||||
_ -> items
|
_ -> items
|
||||||
|
|
||||||
-- | Like @compactify'@, but acts on items of definition lists.
|
-- | Like @compactify@, but acts on items of definition lists.
|
||||||
compactify'DL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
|
compactifyDL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
|
||||||
compactify'DL items =
|
compactifyDL items =
|
||||||
let defs = concatMap snd items
|
let defs = concatMap snd items
|
||||||
in case reverse (concatMap B.toList defs) of
|
in case reverse (concatMap B.toList defs) of
|
||||||
(Para x:xs)
|
(Para x:xs)
|
||||||
|
|
|
@ -9,11 +9,11 @@ import Text.Pandoc.Builder
|
||||||
import System.FilePath.Posix (joinPath)
|
import System.FilePath.Posix (joinPath)
|
||||||
|
|
||||||
tests :: [Test]
|
tests :: [Test]
|
||||||
tests = [ testGroup "compactify'DL"
|
tests = [ testGroup "compactifyDL"
|
||||||
[ testCase "compactify'DL with empty def" $
|
[ testCase "compactifyDL with empty def" $
|
||||||
assertBool "compactify'DL"
|
assertBool "compactifyDL"
|
||||||
(let x = [(str "word", [para (str "def"), mempty])]
|
(let x = [(str "word", [para (str "def"), mempty])]
|
||||||
in compactify'DL x == x)
|
in compactifyDL x == x)
|
||||||
]
|
]
|
||||||
, testGroup "collapseFilePath" testCollapse
|
, testGroup "collapseFilePath" testCollapse
|
||||||
]
|
]
|
||||||
|
|
Loading…
Reference in a new issue