diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 14 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 7 | 
2 files changed, 11 insertions, 10 deletions
| diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index b374acfe2..ef9c99cad 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -116,7 +116,7 @@ blockAttributes = try $ do    let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv    let name    = lookup "NAME" kv    caption' <- maybe (return Nothing) -                    (fmap Just . parseFromString parseInlines) +                    (fmap Just . parseFromString inlines)                      caption    kvAttrs' <- parseFromString keyValues . (++ "\n") $ fromMaybe mempty kvAttrs    return $ BlockAttributes @@ -217,7 +217,7 @@ verseBlock blkProp = try $ do    ignHeaders    content <- rawBlockContent blkProp    fmap B.para . mconcat . intersperse (pure B.linebreak) -    <$> mapM (parseFromString parseInlines) (map (++ "\n") . lines $ content) +    <$> mapM (parseFromString inlines) (map (++ "\n") . lines $ content)  exportsCode :: [(String, String)] -> Bool  exportsCode attrs = not (("rundoc-exports", "none") `elem` attrs @@ -618,10 +618,10 @@ header = try $ do    title    <- manyTill inline (lookAhead $ optional headerTags <* newline)    tags     <- option [] headerTags    newline +  let text = tagTitle title tags    propAttr <- option nullAttr (keyValuesToAttr <$> propertiesDrawer) -  inlines  <- runF (tagTitle title tags) <$> getState -  attr     <- registerHeader propAttr inlines -  return $ pure (B.headerWith attr level inlines) +  attr     <- registerHeader propAttr (runF text def) +  return (B.headerWith attr level <$> text)   where     tagTitle :: [F Inlines] -> [String] -> F Inlines     tagTitle title tags = trimInlinesF . mconcat $ title <> map tagToInlineF tags @@ -799,7 +799,7 @@ noteBlock = try $ do  -- Paragraphs or Plain text  paraOrPlain :: OrgParser (F Blocks)  paraOrPlain = try $ do -  ils <- parseInlines +  ils <- inlines    nl <- option False (newline *> return True)    -- Read block as paragraph, except if we are in a list context and the block    -- is directly followed by a list item, in which case the block is read as @@ -858,7 +858,7 @@ definitionListItem parseMarkerGetLength = try $ do    line1 <- anyLineNewline    blank <- option "" ("\n" <$ blankline)    cont <- concat <$> many (listContinuation markerLength) -  term' <- parseFromString parseInlines term +  term' <- parseFromString inlines term    contents' <- parseFromString blocks $ line1 ++ blank ++ cont    return $ (,) <$> term' <*> fmap (:[]) contents'   where diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 0c3840979..a122c334a 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -28,8 +28,8 @@ Parsers for Org-mode inline elements.  -}  module Text.Pandoc.Readers.Org.Inlines    ( inline +  , inlines    , addToNotesTable -  , parseInlines    , isImageFilename    , linkTarget    ) where @@ -145,8 +145,9 @@ inline =           ] <* (guard =<< newlinesCountWithinLimits)    <?> "inline" -parseInlines :: OrgParser (F Inlines) -parseInlines = trimInlinesF . mconcat <$> many1 inline +-- | Read the rest of the input as inlines. +inlines :: OrgParser (F Inlines) +inlines = trimInlinesF . mconcat <$> many1 inline  -- treat these as potentially non-text when parsing inline:  specialChars :: [Char] | 
