diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
| -rw-r--r-- | src/Text/Pandoc/Readers/DocBook.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Odt/ContentReader.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Odt/StyleReader.hs | 32 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 10 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 9 |
6 files changed, 36 insertions, 27 deletions
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 336b40933..4d8d5ab94 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 2e95c518d..68bc936b1 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 1aaff62e5..11d39498c 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -418,7 +418,7 @@ getListConstructor ListLevelStyle{..} = LltNumbered -> let listNumberStyle = toListNumberStyle listItemFormat listNumberDelim = toListNumberDelim listItemPrefix listItemSuffix - in orderedListWith (1, listNumberStyle, listNumberDelim) + in orderedListWith (listItemStart, listNumberStyle, listNumberDelim) where toListNumberStyle LinfNone = DefaultStyle toListNumberStyle LinfNumber = Decimal diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs index 96cfed0b3..26ba6df82 100644 --- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs +++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs @@ -76,8 +76,9 @@ import Control.Applicative hiding ( liftA, liftA2, liftA3 ) import qualified Data.Foldable as F import qualified Data.Map as M import qualified Data.Set as S -import Data.List ( unfoldr ) +import Data.Char ( isDigit ) import Data.Default +import Data.List ( unfoldr ) import Data.Maybe import qualified Text.XML.Light as XML @@ -390,6 +391,7 @@ data ListLevelStyle = ListLevelStyle { listLevelType :: ListLevelType , listItemPrefix :: Maybe String , listItemSuffix :: Maybe String , listItemFormat :: ListItemNumberFormat + , listItemStart :: Int } deriving ( Eq, Ord ) @@ -578,25 +580,31 @@ readListLevelStyles namespace elementName levelType = readListLevelStyle :: ListLevelType -> StyleReader _x (Int, ListLevelStyle) readListLevelStyle levelType = readAttr NsText "level" >>?! keepingTheValue - ( liftA4 toListLevelStyle - ( returnV levelType ) - ( findAttr' NsStyle "num-prefix" ) - ( findAttr' NsStyle "num-suffix" ) - ( getAttr NsStyle "num-format" ) + ( liftA5 toListLevelStyle + ( returnV levelType ) + ( findAttr' NsStyle "num-prefix" ) + ( findAttr' NsStyle "num-suffix" ) + ( getAttr NsStyle "num-format" ) + ( findAttr' NsText "start-value" ) ) where - toListLevelStyle _ p s LinfNone = ListLevelStyle LltBullet p s LinfNone - toListLevelStyle _ p s f@(LinfString _) = ListLevelStyle LltBullet p s f - toListLevelStyle t p s f = ListLevelStyle t p s f + toListLevelStyle _ p s LinfNone b = ListLevelStyle LltBullet p s LinfNone (startValue b) + toListLevelStyle _ p s f@(LinfString _) b = ListLevelStyle LltBullet p s f (startValue b) + toListLevelStyle t p s f b = ListLevelStyle t p s f (startValue b) + startValue (Just "") = 1 + startValue (Just v) = if all isDigit v + then read v + else 1 + startValue Nothing = 1 -- chooseMostSpecificListLevelStyle :: S.Set ListLevelStyle -> Maybe ListLevelStyle chooseMostSpecificListLevelStyle ls | ls == mempty = Nothing | otherwise = Just ( F.foldr1 select ls ) where - select ( ListLevelStyle t1 p1 s1 f1 ) - ( ListLevelStyle t2 p2 s2 f2 ) - = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2) + select ( ListLevelStyle t1 p1 s1 f1 b1 ) + ( ListLevelStyle t2 p2 s2 f2 _ ) + = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2) b1 select' LltNumbered _ = LltNumbered select' _ LltNumbered = LltNumbered select' _ _ = LltBullet diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 82c3a6cbe..61978f79f 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -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 ((<>)) @@ -288,9 +288,9 @@ blockAttributes = try $ do let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv let name = lookup "NAME" kv let label = lookup "LABEL" kv - caption' <- maybe (return Nothing) - (fmap Just . parseFromString inlines) - caption + caption' <- case caption of + Nothing -> return Nothing + Just s -> Just <$> parseFromString inlines (s ++ "\n") kvAttrs' <- parseFromString keyValues . (++ "\n") $ fromMaybe mempty kvAttrs return $ BlockAttributes { blockAttrName = name @@ -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 diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index f181d523a..1b06c6f23 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -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 @@ -949,7 +949,8 @@ table = gridTable False <|> simpleTable False <|> -- inline :: RSTParser Inlines -inline = choice [ whitespace +inline = choice [ note -- can start with whitespace, so try before ws + , whitespace , link , str , endline @@ -958,7 +959,6 @@ inline = choice [ whitespace , code , subst , interpretedRole - , note , smart , hyphens , escapedChar @@ -1174,6 +1174,7 @@ subst = try $ do note :: RSTParser Inlines note = try $ do + optional whitespace ref <- noteMarker char '_' state <- getState |
