MediaWiki reader: internal links.
This commit is contained in:
parent
fc2f7a4942
commit
a0d7b3f37b
3 changed files with 10 additions and 4 deletions
|
@ -30,8 +30,6 @@ Conversion of mediawiki text to 'Pandoc' document.
|
|||
-}
|
||||
{-
|
||||
TODO:
|
||||
_ support internal links http://www.mediawiki.org/wiki/Help:Links
|
||||
_ support external links (partially implemented)
|
||||
_ support images http://www.mediawiki.org/wiki/Help:Images
|
||||
_ support tables http://www.mediawiki.org/wiki/Help:Tables
|
||||
- footnotes?
|
||||
|
@ -51,7 +49,7 @@ import Text.Pandoc.Shared ( stripTrailingNewlines, safeRead )
|
|||
import Data.Monoid (mconcat, mempty)
|
||||
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
||||
import Control.Monad
|
||||
import Data.List (intersperse)
|
||||
import Data.List (intersperse, intercalate )
|
||||
import Text.HTML.TagSoup
|
||||
import Data.Sequence (viewl, ViewL(..), (<|))
|
||||
|
||||
|
@ -379,6 +377,8 @@ endline = () <$ try (newline <*
|
|||
internalLink :: MWParser Inlines
|
||||
internalLink = try $ do
|
||||
string "[["
|
||||
let addUnderscores x = let (pref,suff) = break (=='#') x
|
||||
in pref ++ intercalate "_" (words suff)
|
||||
pagename <- unwords . words <$> many (noneOf "|]")
|
||||
label <- option (B.text pagename) $ char '|' *>
|
||||
( (mconcat <$> many1 (notFollowedBy (char ']') *> inline))
|
||||
|
@ -387,7 +387,7 @@ internalLink = try $ do
|
|||
<|> (return $ B.text $ drop 1 $ dropWhile (/=':') pagename) )
|
||||
string "]]"
|
||||
linktrail <- B.text <$> many (char '\'' <|> letter)
|
||||
return $ B.link pagename "wikilink" (label <> linktrail)
|
||||
return $ B.link (addUnderscores pagename) "wikilink" (label <> linktrail)
|
||||
|
||||
externalLink :: MWParser Inlines
|
||||
externalLink = try $ do
|
||||
|
|
|
@ -80,6 +80,8 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Para [Link [Str "Helpers"] ("Help","wikilink")]
|
||||
,Para [Link [Str "Help"] ("Help","wikilink"),Str "ers"]
|
||||
,Para [Link [Str "Contents"] ("Help:Contents","wikilink")]
|
||||
,Para [Link [Str "#My",Space,Str "anchor"] ("#My_anchor","wikilink")]
|
||||
,Para [Link [Str "and",Space,Str "text"] ("Page#with_anchor","wikilink")]
|
||||
,Header 2 [Str "lists"]
|
||||
,BulletList
|
||||
[[Plain [Str "Start",Space,Str "each",Space,Str "line"]]
|
||||
|
|
|
@ -159,6 +159,10 @@ http://johnmacfarlane.net/pandoc/
|
|||
|
||||
[[Help:Contents|]]
|
||||
|
||||
[[#My anchor]]
|
||||
|
||||
[[Page#with anchor|and text]]
|
||||
|
||||
== lists ==
|
||||
|
||||
* Start each line
|
||||
|
|
Loading…
Add table
Reference in a new issue