aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs39
-rw-r--r--tests/mediawiki-reader.native8
-rw-r--r--tests/mediawiki-reader.wiki25
3 files changed, 59 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 8805d528a..bb2889d00 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE RelaxedPolyRec #-} -- needed for inlinesBetween on GHC < 7
{-
-Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>
+ Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -33,8 +33,6 @@ TODO:
_ support HTML lists
_ support list style attributes and start values in ol lists, also
value attribute on li
-_ support preformatted text (lines starting with space)
-_ support preformatted text blocks
_ support internal links http://www.mediawiki.org/wiki/Help:Links
_ support external links (partially implemented)
_ support images http://www.mediawiki.org/wiki/Help:Images
@@ -50,13 +48,13 @@ import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines, (<>))
import Text.Pandoc.Options
-import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced,
- isInlineTag, isBlockTag, isTextTag, isCommentTag )
+import Text.Pandoc.Readers.HTML ( htmlTag, isInlineTag,
+ isBlockTag, isCommentTag )
import Text.Pandoc.XML ( fromEntities )
import Text.Pandoc.Parsing
+import Text.Pandoc.Generic ( bottomUp )
import Text.Pandoc.Shared ( stripTrailingNewlines )
import Data.Monoid (mconcat, mempty)
-import qualified Data.Foldable as F
import Control.Applicative ((<$>), (<*), (*>), (<$))
import Control.Monad
import Data.List (intersperse)
@@ -124,12 +122,13 @@ block = header
<|> bulletList
<|> orderedList
<|> definitionList
+ <|> mempty <$ try (spaces *> htmlComment)
+ <|> preformatted
<|> blockquote
<|> codeblock
<|> syntaxhighlight
<|> haskell
<|> mempty <$ skipMany1 blankline
- <|> mempty <$ try (spaces *> htmlComment)
<|> pTag
<|> blockHtml
<|> para
@@ -147,6 +146,22 @@ blockHtml = (B.rawBlock "html" . snd <$> htmlTag isBlockTag)
hrule :: MWParser Blocks
hrule = B.horizontalRule <$ try (string "----" *> many (char '-') *> newline)
+preformatted :: MWParser Blocks
+preformatted = do
+ char ' '
+ let endline' = B.linebreak <$ (try $ newline <* char ' ')
+ let whitespace' = B.str <$> many1 ('\160' <$ spaceChar)
+ let spToNbsp ' ' = '\160'
+ spToNbsp x = x
+ let nowiki' = mconcat . intersperse B.linebreak . map B.str .
+ lines . fromEntities . map spToNbsp <$> try
+ (htmlTag (~== TagOpen "nowiki" []) *>
+ manyTill anyChar (htmlTag (~== TagClose "nowiki")))
+ let inline' = whitespace' <|> endline' <|> nowiki' <|> inline
+ let strToCode (Str s) = Code ("",[],[]) s
+ strToCode x = x
+ B.para . bottomUp strToCode . mconcat <$> many1 inline'
+
blockquote :: MWParser Blocks
blockquote = B.blockQuote <$> blocksInTags "blockquote"
@@ -159,8 +174,8 @@ trimCode xs = stripTrailingNewlines xs
syntaxhighlight :: MWParser Blocks
syntaxhighlight = try $ do
- (tag@(TagOpen _ attrs), _) <- lookAhead
- $ htmlTag (~== TagOpen "syntaxhighlight" [])
+ (TagOpen _ attrs, _) <- lookAhead
+ $ htmlTag (~== TagOpen "syntaxhighlight" [])
let mblang = lookup "lang" attrs
let mbstart = lookup "start" attrs
let mbline = lookup "line" attrs
@@ -220,6 +235,7 @@ listItem c = try $ do
if null extras
then listItem' c
else do
+ skipMany spaceChar
first <- manyTill anyChar newline
rest <- many (try $ string extras *> manyTill anyChar newline)
contents <- parseFromString (many1 $ listItem' c)
@@ -233,14 +249,15 @@ listItem c = try $ do
listItem' :: Char -> MWParser Blocks
listItem' c = try $ do
listStart c
+ skipMany spaceChar
first <- manyTill anyChar newline
rest <- many (try $ char c *> lookAhead listStartChar *>
manyTill anyChar newline)
contents <- parseFromString (mconcat <$> many1 block)
$ unlines $ first : rest
case viewl (B.unMany contents) of
- (Para xs) :< rest -> return $ B.Many $ (Plain xs) <| rest
- _ -> return contents
+ (Para xs) :< ys -> return $ B.Many $ (Plain xs) <| ys
+ _ -> return contents
--
-- inline parsers
diff --git a/tests/mediawiki-reader.native b/tests/mediawiki-reader.native
index c823bafaf..6eac94b9d 100644
--- a/tests/mediawiki-reader.native
+++ b/tests/mediawiki-reader.native
@@ -6,7 +6,7 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
,Header 5 [Str "header",Space,Str "level",Space,Str "5"]
,Header 6 [Str "header",Space,Str "level",Space,Str "6"]
,Para [Str "=======",Space,Str "not",Space,Str "a",Space,Str "header",Space,Str "========"]
-,Para [Str "==",Space,Str "not",Space,Str "a",Space,Str "header",Space,Str "=="]
+,Para [Code ("",[],[]) "==\160not\160a\160header\160=="]
,Header 2 [Str "emph",Space,Str "and",Space,Str "strong"]
,Para [Emph [Str "emph"],Space,Strong [Str "strong"]]
,Para [Strong [Emph [Str "strong",Space,Str "and",Space,Str "emph"]]]
@@ -131,4 +131,8 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[[Plain [Str "five",Space,Str "sub",Space,Str "1",Space,Str "sub",Space,Str "1"]]]]
,[Plain [Str "five",Space,Str "sub",Space,Str "2"]]]]]
,Header 2 [Str "math"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Math InlineMath "x=\\frac{y^\\pi}{z}",Str "."]]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Math InlineMath "x=\\frac{y^\\pi}{z}",Str "."]
+,Header 2 [Str "preformatted",Space,Str "blocks"]
+,Para [Code ("",[],[]) "Start\160each\160line\160with\160a\160space.",LineBreak,Code ("",[],[]) "Text\160is\160",Strong [Code ("",[],[]) "preformatted"],Code ("",[],[]) "\160and",LineBreak,Emph [Code ("",[],[]) "markups"],Code ("",[],[]) "\160",Strong [Emph [Code ("",[],[]) "can"]],Code ("",[],[]) "\160be\160done."]
+,Para [Code ("",[],[]) "\160hell\160\160\160\160\160\160yeah"]
+,Para [Code ("",[],[]) "Start\160with\160a\160space\160in\160the\160first\160column,",LineBreak,Code ("",[],[]) "(before\160the\160<nowiki>).",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "Then\160your\160block\160format\160will\160be",LineBreak,Code ("",[],[]) "\160\160\160\160maintained.",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "This\160is\160good\160for\160copying\160in\160code\160blocks:",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "def\160function():",LineBreak,Code ("",[],[]) "\160\160\160\160\"\"\"documentation\160string\"\"\"",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "\160\160\160\160if\160True:",LineBreak,Code ("",[],[]) "\160\160\160\160\160\160\160\160print\160True",LineBreak,Code ("",[],[]) "\160\160\160\160else:",LineBreak,Code ("",[],[]) "\160\160\160\160\160\160\160\160print\160False"]]
diff --git a/tests/mediawiki-reader.wiki b/tests/mediawiki-reader.wiki
index b03c0f72d..7066b4a59 100644
--- a/tests/mediawiki-reader.wiki
+++ b/tests/mediawiki-reader.wiki
@@ -193,3 +193,28 @@ ends the list.
Here is some <math>x=\frac{y^\pi}{z}</math>.
+== preformatted blocks ==
+
+ Start each line with a space.
+ Text is '''preformatted''' and
+ ''markups'' '''''can''''' be done.
+
+ hell yeah
+
+ <nowiki>Start with a space in the first column,
+(before the <nowiki>).
+
+Then your block format will be
+ maintained.
+
+This is good for copying in code blocks:
+
+def function():
+ """documentation string"""
+
+ if True:
+ print True
+ else:
+ print False</nowiki>
+
+