diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 32 |
3 files changed, 42 insertions, 17 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 8100a6823..10e2b9833 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -232,7 +232,7 @@ inline = (mempty <$ comment) <|> (guardEnabled Ext_literate_haskell *> char '|' *> doLHSverb) <|> (str . (:[]) <$> tildeEscape) <|> (str . (:[]) <$> oneOf "[]") - <|> (str . (:[]) <$> oneOf "#&") -- TODO print warning? + <|> (str . (:[]) <$> oneOf "#&~^'`\"[]") -- TODO print warning? -- <|> (str <$> count 1 (satisfy (\c -> c /= '\\' && c /='\n' && c /='}' && c /='{'))) -- eat random leftover characters inlines :: LP Inlines @@ -859,8 +859,14 @@ tok = try $ grouped inline <|> inlineCommand <|> str <$> count 1 inlineChar opt :: LP Inlines opt = bracketed inline +rawopt :: LP String +rawopt = do + contents <- bracketed (many1 (noneOf "]") <|> try (string "\\]")) + optional sp + return $ "[" ++ contents ++ "]" + skipopts :: LP () -skipopts = skipMany (opt *> optional sp) +skipopts = skipMany rawopt inlineText :: LP Inlines inlineText = str <$> many1 inlineChar @@ -883,8 +889,9 @@ inlineEnvironment = try $ do rawEnv :: String -> LP Blocks rawEnv name = do - let addBegin x = "\\begin{" ++ name ++ "}" ++ x parseRaw <- getOption readerParseRaw + rawOptions <- mconcat <$> many rawopt + let addBegin x = "\\begin{" ++ name ++ "}" ++ rawOptions ++ x if parseRaw then (rawBlock "latex" . addBegin) <$> (withRaw (env name blocks) >>= applyMacros' . snd) diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 60d69638b..46f082ccd 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -562,13 +562,11 @@ directive' = do "rubric" -> B.para . B.strong <$> parseInlineFromString top _ | label `elem` ["attention","caution","danger","error","hint", "important","note","tip","warning"] -> - do let tit = B.para $ B.strong $ B.str label - bod <- parseFromString parseBlocks $ top ++ "\n\n" ++ body' - return $ B.blockQuote $ tit <> bod + do bod <- parseFromString parseBlocks $ top ++ "\n\n" ++ body' + return $ B.divWith ("",["admonition", label],[]) bod "admonition" -> - do tit <- B.para . B.strong <$> parseInlineFromString top - bod <- parseFromString parseBlocks body' - return $ B.blockQuote $ tit <> bod + do bod <- parseFromString parseBlocks $ top ++ "\n\n" ++ body' + return $ B.divWith ("",["admonition"],[]) bod "sidebar" -> do let subtit = maybe "" trim $ lookup "subtitle" fields tit <- B.para . B.strong <$> parseInlineFromString @@ -576,11 +574,11 @@ directive' = do then "" else (": " ++ subtit)) bod <- parseFromString parseBlocks body' - return $ B.blockQuote $ tit <> bod + return $ B.divWith ("",["sidebar"],[]) $ tit <> bod "topic" -> do tit <- B.para . B.strong <$> parseInlineFromString top bod <- parseFromString parseBlocks body' - return $ tit <> bod + return $ B.divWith ("",["topic"],[]) $ tit <> bod "default-role" -> mempty <$ updateState (\s -> s { stateRstDefaultRole = case trim top of diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 13fe29ca2..4ab0243fe 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -161,9 +161,22 @@ codeBlock = codeBlockBc <|> codeBlockPre codeBlockBc :: Parser [Char] ParserState Blocks codeBlockBc = try $ do - string "bc. " - contents <- manyTill anyLine blanklines - return $ B.codeBlock (unlines contents) + string "bc." + extended <- option False (True <$ char '.') + char ' ' + let starts = ["p", "table", "bq", "bc", "h1", "h2", "h3", + "h4", "h5", "h6", "pre", "###", "notextile"] + let ender = choice $ map explicitBlockStart starts + contents <- if extended + then do + f <- anyLine + rest <- many (notFollowedBy ender *> anyLine) + return (f:rest) + else manyTill anyLine blanklines + return $ B.codeBlock (trimTrailingNewlines (unlines contents)) + +trimTrailingNewlines :: String -> String +trimTrailingNewlines = reverse . dropWhile (=='\n') . reverse -- | Code Blocks in Textile are between <pre> and </pre> codeBlockPre :: Parser [Char] ParserState Blocks @@ -408,14 +421,21 @@ ignorableRow = try $ do _ <- anyLine return () +explicitBlockStart :: String -> Parser [Char] ParserState () +explicitBlockStart name = try $ do + string name + attributes + char '.' + optional whitespace + optional endline + -- | Blocks like 'p' and 'table' do not need explicit block tag. -- However, they can be used to set HTML/CSS attributes when needed. maybeExplicitBlock :: String -- ^ block tag name -> Parser [Char] ParserState Blocks -- ^ implicit block -> Parser [Char] ParserState Blocks maybeExplicitBlock name blk = try $ do - optional $ try $ string name >> attributes >> char '.' >> - optional whitespace >> optional endline + optional $ explicitBlockStart name blk @@ -574,7 +594,7 @@ link = try $ do then char ']' else lookAhead $ space <|> try (oneOf "!.,;:" *> (space <|> newline)) - url <- manyTill nonspaceChar stop + url <- many1Till nonspaceChar stop let name' = if B.toList name == [Str "$"] then B.str url else name return $ if attr == nullAttr then B.link url "" name' |