diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/CommonMark.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Creole.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 36 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Arrows/State.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/ContentReader.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TikiWiki.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Txt2Tags.hs | 2 |
10 files changed, 64 insertions, 49 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index 6b864521f..47f4c4088 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -59,7 +59,7 @@ readCommonMark opts s = return $ -- | Returns True if the given extension is enabled. enabled :: Extension -> ReaderOptions -> Bool -enabled ext opts = ext `extensionEnabled` (readerExtensions opts) +enabled ext opts = ext `extensionEnabled` readerExtensions opts convertEmojis :: String -> String convertEmojis (':':xs) = diff --git a/src/Text/Pandoc/Readers/Creole.hs b/src/Text/Pandoc/Readers/Creole.hs index 4da259c0e..b4eb6eaef 100644 --- a/src/Text/Pandoc/Readers/Creole.hs +++ b/src/Text/Pandoc/Readers/Creole.hs @@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA License : GNU GPL, version 2 or above Maintainer : Sascha Wilde <wilde@sha-bang.de> - Stability : WIP + Stability : alpha Portability : portable Conversion of creole text to 'Pandoc' document. @@ -64,7 +64,7 @@ readCreole opts s = do type CRLParser = ParserT [Char] ParserState -- --- Utility funcitons +-- Utility functions -- (<+>) :: (Monad m, Monoid a) => m a -> m a -> m a @@ -111,7 +111,8 @@ block = do return res nowiki :: PandocMonad m => CRLParser m B.Blocks -nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart >> manyTill content nowikiEnd) +nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart + >> manyTill content nowikiEnd) where content = brackets <|> line brackets = try $ option "" ((:[]) <$> newline) @@ -154,7 +155,8 @@ listItem :: PandocMonad m => Char -> Int -> CRLParser m B.Blocks listItem c n = fmap (B.plain . B.trimInlines .mconcat) (listStart >> many1Till inline itemEnd) where - listStart = try $ optional newline >> skipSpaces >> count n (char c) + listStart = try $ skipSpaces >> optional newline >> skipSpaces + >> count n (char c) >> lookAhead (noneOf [c]) >> skipSpaces itemEnd = endOfParaElement <|> nextItem n <|> if n < 3 then nextItem (n+1) @@ -193,7 +195,7 @@ endOfParaElement = lookAhead $ endOfInput <|> endOfPara startOf :: PandocMonad m => CRLParser m a -> CRLParser m () startOf p = try $ blankline >> p >> return mempty startOfList = startOf $ anyList 1 - startOfTable =startOf table + startOfTable = startOf table startOfHeader = startOf header startOfNowiki = startOf nowiki hr = startOf horizontalRule diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 8d37deb26..2b667c63c 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -141,7 +141,7 @@ type TagParser m = HTMLParser m [Tag Text] pHtml :: PandocMonad m => TagParser m Blocks pHtml = try $ do - (TagOpen "html" attr) <- lookAhead $ pAnyTag + (TagOpen "html" attr) <- lookAhead pAnyTag for_ (lookup "lang" attr) $ updateState . B.setMeta "lang" . B.text . T.unpack pInTags "html" block @@ -152,7 +152,7 @@ pBody = pInTags "body" block pHead :: PandocMonad m => TagParser m Blocks pHead = pInTags "head" $ pTitle <|> pMetaTag <|> pBaseTag <|> (mempty <$ pAnyTag) where pTitle = pInTags "title" inline >>= setTitle . trimInlines - setTitle t = mempty <$ (updateState $ B.setMeta "title" t) + setTitle t = mempty <$ updateState (B.setMeta "title" t) pMetaTag = do mt <- pSatisfy (matchTagOpen "meta" []) let name = T.unpack $ fromAttrib "name" mt @@ -233,7 +233,7 @@ eFootnote :: PandocMonad m => TagParser m () eFootnote = try $ do let notes = ["footnote", "rearnote"] guardEnabled Ext_epub_html_exts - (TagOpen tag attr') <- lookAhead $ pAnyTag + (TagOpen tag attr') <- lookAhead pAnyTag let attr = toStringAttr attr' guard (maybe False (flip elem notes) (lookup "type" attr)) let ident = fromMaybe "" (lookup "id" attr) @@ -478,7 +478,7 @@ pTable = try $ do let pTh = option [] $ pInTags "tr" (pCell "th") pTr = try $ skipMany pBlank >> pInTags "tr" (pCell "td" <|> pCell "th") - pTBody = do pOptInTag "tbody" $ many1 pTr + pTBody = pOptInTag "tbody" $ many1 pTr head'' <- pOptInTag "thead" pTh head' <- map snd <$> (pOptInTag "tbody" $ @@ -1133,6 +1133,7 @@ htmlTag :: (HasReaderOptions st, Monad m) -> ParserT [Char] st m (Tag String, String) htmlTag f = try $ do lookAhead (char '<') + startpos <- getPosition inp <- getInput let ts = canonicalizeTags $ parseTagsOptions parseOptions{ optTagWarning = False @@ -1153,11 +1154,17 @@ htmlTag f = try $ do [] -> False (c:cs) -> isLetter c && all isNameChar cs - let endAngle = try $ do char '>' - pos <- getPosition - guard $ (sourceLine pos == ln && - sourceColumn pos >= col) || - sourceLine pos > ln + let endpos = if ln == 1 + then setSourceColumn startpos + (sourceColumn startpos + (col - 1)) + else setSourceColumn (setSourceLine startpos + (sourceLine startpos + (ln - 1))) + col + let endAngle = try $ + do char '>' + pos <- getPosition + guard $ pos >= endpos + let handleTag tagname = do -- basic sanity check, since the parser is very forgiving -- and finds tags in stuff like x<y) @@ -1172,8 +1179,9 @@ htmlTag f = try $ do case next of TagComment s | "<!--" `isPrefixOf` inp -> do - char '<' - manyTill anyChar endAngle + string "<!--" + count (length s) anyChar + string "-->" stripComments <- getOption readerStripComments if stripComments then return (next, "") @@ -1255,7 +1263,7 @@ renderTags' = renderTagsOptions renderOptions{ optMinimize = matchTags ["hr", "br", "img", "meta", "link"] , optRawTag = matchTags ["script", "style"] } - where matchTags = \tags -> flip elem tags . T.toLower + where matchTags tags = flip elem tags . T.toLower -- EPUB Specific diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index a982029af..9bac3d3a7 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1132,7 +1132,7 @@ inlineCommand' = try $ do lookupListDefault raw names inlineCommands tok :: PandocMonad m => LP m Inlines -tok = grouped inline <|> inlineCommand' <|> singleChar' +tok = try $ spaces >> grouped inline <|> inlineCommand' <|> singleChar' where singleChar' = do Tok _ _ t <- singleChar return (str (T.unpack t)) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 2a88b39ec..8fc92f7e8 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -846,6 +846,7 @@ listLine continuationIndent = try $ do skipMany spaceChar listStart) notFollowedByHtmlCloser + notFollowedByDivCloser optional (() <$ gobbleSpaces continuationIndent) listLineCommon @@ -883,16 +884,24 @@ listContinuation continuationIndent = try $ do x <- try $ do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser gobbleSpaces continuationIndent anyLineNewline xs <- many $ try $ do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser gobbleSpaces continuationIndent <|> notFollowedBy' listStart anyLineNewline blanks <- many blankline return $ concat (x:xs) ++ blanks +notFollowedByDivCloser :: PandocMonad m => MarkdownParser m () +notFollowedByDivCloser = do + guardDisabled Ext_fenced_divs <|> + do divLevel <- stateFencedDivLevel <$> getState + guard (divLevel < 1) <|> notFollowedBy divFenceEnd + notFollowedByHtmlCloser :: PandocMonad m => MarkdownParser m () notFollowedByHtmlCloser = do inHtmlBlock <- stateInHtmlBlock <$> getState @@ -965,6 +974,7 @@ defRawBlock compact = try $ do let dline = try ( do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser if compact -- laziness not compatible with compact then () <$ indentSpaces else (() <$ indentSpaces) @@ -1409,7 +1419,7 @@ tableWith headerParser rowParser lineParser footerParser = try $ do lines' <- fmap sequence $ rowParser indices `sepEndBy1` lineParser footerParser numColumns <- getOption readerColumns - let widths = if indices == [] + let widths = if null indices then replicate (length aligns) 0.0 else widthsFromIndices numColumns indices return (aligns, widths, heads, lines') @@ -1688,10 +1698,8 @@ endline = try $ do guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header guardDisabled Ext_backtick_code_blocks <|> notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced)) - guardDisabled Ext_fenced_divs <|> - do divLevel <- stateFencedDivLevel <$> getState - guard (divLevel < 1) <|> notFollowedBy divFenceEnd notFollowedByHtmlCloser + notFollowedByDivCloser (eof >> return mempty) <|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak)) <|> (guardEnabled Ext_ignore_line_breaks >> return mempty) @@ -1998,7 +2006,7 @@ cite = do guardEnabled Ext_citations textualCite <|> do (cs, raw) <- withRaw normalCite - return $ (flip B.cite (B.text raw)) <$> cs + return $ flip B.cite (B.text raw) <$> cs textualCite :: PandocMonad m => MarkdownParser m (F Inlines) textualCite = try $ do @@ -2085,15 +2093,15 @@ citation = try $ do return $ do x <- pref y <- suff - return $ Citation{ citationId = key - , citationPrefix = B.toList x - , citationSuffix = B.toList y - , citationMode = if suppress_author - then SuppressAuthor - else NormalCitation - , citationNoteNum = 0 - , citationHash = 0 - } + return Citation{ citationId = key + , citationPrefix = B.toList x + , citationSuffix = B.toList y + , citationMode = if suppress_author + then SuppressAuthor + else NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } smart :: PandocMonad m => MarkdownParser m (F Inlines) smart = do diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs index 06b2dcaaa..73bed545e 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs @@ -82,7 +82,7 @@ tryModifyState f = ArrowState $ \(state,a) instance Cat.Category (ArrowState s) where id = ArrowState id - arrow2 . arrow1 = ArrowState $ (runArrowState arrow2).(runArrowState arrow1) + arrow2 . arrow1 = ArrowState $ runArrowState arrow2 . runArrowState arrow1 instance Arrow (ArrowState state) where arr = ignoringState diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 44bd89278..4189d5aaa 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -293,7 +293,7 @@ withNewStyle a = proc x -> do modifier <- arr modifierFromStyleDiff -< triple fShouldTrace <- isStyleToTrace -< style case fShouldTrace of - Right shouldTrace -> do + Right shouldTrace -> if shouldTrace then do pushStyle -< style @@ -357,7 +357,7 @@ modifierFromStyleDiff propertyTriple = hasChangedM property triple@(_, textProps,_) = fromMaybe False $ (/=) <$> property textProps <*> lookupPreviousValueM property triple - lookupPreviousValue f = lookupPreviousStyleValue ((fmap f).textProperties) + lookupPreviousValue f = lookupPreviousStyleValue (fmap f . textProperties) lookupPreviousValueM f = lookupPreviousStyleValue ((f =<<).textProperties) @@ -803,9 +803,9 @@ read_frame_text_box = matchingElement NsDraw "text-box" arr read_img_with_caption -< toList paragraphs read_img_with_caption :: [Block] -> Inlines -read_img_with_caption ((Para ((Image attr alt (src,title)) : [])) : _) = +read_img_with_caption ((Para [Image attr alt (src,title)]) : _) = singleton (Image attr alt (src, 'f':'i':'g':':':title)) -- no text, default caption -read_img_with_caption ((Para ((Image attr _ (src,title)) : txt)) : _) = +read_img_with_caption (Para (Image attr _ (src,title) : txt) : _) = singleton (Image attr txt (src, 'f':'i':'g':':':title) ) -- override caption with the text that follows read_img_with_caption ( (Para (_ : xs)) : ys) = read_img_with_caption ((Para xs) : ys) diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index f8c2b8cb7..a3b4f2ff1 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -387,7 +387,7 @@ table = try $ do char '.' rawcapt <- trim <$> anyLine parseFromString' (mconcat <$> many inline) rawcapt - rawrows <- many1 $ (skipMany ignorableRow) >> tableRow + rawrows <- many1 $ skipMany ignorableRow >> tableRow skipMany ignorableRow blanklines let (headers, rows) = case rawrows of @@ -438,8 +438,7 @@ maybeExplicitBlock name blk = try $ do -- | Any inline element inline :: PandocMonad m => ParserT [Char] ParserState m Inlines -inline = do - choice inlineParsers <?> "inline" +inline = choice inlineParsers <?> "inline" -- | Inline parsers tried in order inlineParsers :: PandocMonad m => [ParserT [Char] ParserState m Inlines] @@ -610,7 +609,7 @@ escapedInline = escapedEqs <|> escapedTag escapedEqs :: PandocMonad m => ParserT [Char] ParserState m Inlines escapedEqs = B.str <$> - (try $ string "==" *> manyTill anyChar' (try $ string "==")) + try (string "==" *> manyTill anyChar' (try $ string "==")) -- | literal text escaped btw <notextile> tags escapedTag :: PandocMonad m => ParserT [Char] ParserState m Inlines @@ -643,7 +642,7 @@ code2 = do -- | Html / CSS attributes attributes :: PandocMonad m => ParserT [Char] ParserState m Attr -attributes = (foldl (flip ($)) ("",[],[])) <$> +attributes = foldl (flip ($)) ("",[],[]) <$> try (do special <- option id specialAttribute attrs <- many attribute return (special : attrs)) diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs index ad35a6935..4a66cc13d 100644 --- a/src/Text/Pandoc/Readers/TikiWiki.hs +++ b/src/Text/Pandoc/Readers/TikiWiki.hs @@ -501,7 +501,7 @@ escapedChar = try $ do string "~" inner <- many1 $ oneOf "0123456789" string "~" - return $B.str [(toEnum ((read inner) :: Int)) :: Char] + return $B.str [(toEnum (read inner :: Int)) :: Char] -- UNSUPPORTED, as there doesn't seem to be any facility in calibre -- for this @@ -587,8 +587,7 @@ macroAttr = try $ do return (key, value) macroAttrs :: PandocMonad m => TikiWikiParser m [(String, String)] -macroAttrs = try $ do - sepEndBy macroAttr spaces +macroAttrs = try $ sepEndBy macroAttr spaces -- ~np~ __not bold__ ~/np~ noparse :: PandocMonad m => TikiWikiParser m B.Inlines @@ -641,8 +640,7 @@ wikiLinkText start middle end = do where linkContent = do char '|' - mystr <- many (noneOf middle) - return mystr + many (noneOf middle) externalLink :: PandocMonad m => TikiWikiParser m B.Inlines externalLink = makeLink "[" "]|" "]" diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index fdf7a827a..3fc54aaab 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -560,7 +560,7 @@ endline = try $ do notFollowedBy quote notFollowedBy list notFollowedBy table - return $ B.softbreak + return B.softbreak str :: T2T Inlines str = try $ do |