2013-11-17 08:47:14 -08:00
|
|
|
{-# LANGUAGE RelaxedPolyRec, FlexibleInstances, TypeSynonymInstances #-}
|
|
|
|
-- RelaxedPolyRec needed for inlinesBetween on GHC < 7
|
2012-09-10 10:02:12 -07:00
|
|
|
{-
|
2014-05-08 21:50:20 +02:00
|
|
|
Copyright (C) 2012-2014 John MacFarlane <jgm@berkeley.edu>
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
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
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Readers.MediaWiki
|
2014-05-08 21:50:20 +02:00
|
|
|
Copyright : Copyright (C) 2012-2014 John MacFarlane
|
2012-09-10 10:02:12 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of mediawiki text to 'Pandoc' document.
|
|
|
|
-}
|
|
|
|
{-
|
|
|
|
TODO:
|
2012-09-15 21:06:55 -07:00
|
|
|
_ correctly handle tables within tables
|
2012-09-15 15:05:50 -04:00
|
|
|
_ parse templates?
|
2012-09-10 10:02:12 -07:00
|
|
|
-}
|
|
|
|
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where
|
|
|
|
|
|
|
|
import Text.Pandoc.Definition
|
|
|
|
import qualified Text.Pandoc.Builder as B
|
|
|
|
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines, (<>))
|
|
|
|
import Text.Pandoc.Options
|
2012-09-15 13:44:59 -04:00
|
|
|
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
|
2012-09-10 10:02:12 -07:00
|
|
|
import Text.Pandoc.XML ( fromEntities )
|
2012-09-13 15:10:40 -07:00
|
|
|
import Text.Pandoc.Parsing hiding ( nested )
|
2013-08-10 18:45:00 -07:00
|
|
|
import Text.Pandoc.Walk ( walk )
|
2013-10-18 17:50:43 -07:00
|
|
|
import Text.Pandoc.Shared ( stripTrailingNewlines, safeRead, stringify, trim )
|
2012-09-10 10:02:12 -07:00
|
|
|
import Data.Monoid (mconcat, mempty)
|
|
|
|
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
|
|
|
import Control.Monad
|
2012-09-15 13:44:59 -04:00
|
|
|
import Data.List (intersperse, intercalate, isPrefixOf )
|
2012-09-10 10:02:12 -07:00
|
|
|
import Text.HTML.TagSoup
|
2012-09-12 17:15:21 -07:00
|
|
|
import Data.Sequence (viewl, ViewL(..), (<|))
|
2013-03-28 10:47:27 -07:00
|
|
|
import qualified Data.Foldable as F
|
2013-11-17 08:47:14 -08:00
|
|
|
import qualified Data.Map as M
|
2013-03-28 10:47:27 -07:00
|
|
|
import Data.Char (isDigit, isSpace)
|
2013-12-19 21:07:09 -05:00
|
|
|
import Data.Maybe (fromMaybe)
|
2014-06-20 11:39:24 -07:00
|
|
|
import Text.Printf (printf)
|
|
|
|
import Debug.Trace (trace)
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
-- | Read mediawiki from an input string and return a Pandoc document.
|
|
|
|
readMediaWiki :: ReaderOptions -- ^ Reader options
|
2012-09-13 15:10:40 -07:00
|
|
|
-> String -- ^ String to parse (assuming @'\n'@ line endings)
|
|
|
|
-> Pandoc
|
2012-09-10 10:02:12 -07:00
|
|
|
readMediaWiki opts s =
|
2012-09-13 15:24:05 -07:00
|
|
|
case runParser parseMediaWiki MWState{ mwOptions = opts
|
|
|
|
, mwMaxNestingLevel = 4
|
2012-09-15 13:44:59 -04:00
|
|
|
, mwNextLinkNumber = 1
|
|
|
|
, mwCategoryLinks = []
|
2013-11-17 08:47:14 -08:00
|
|
|
, mwHeaderMap = M.empty
|
|
|
|
, mwIdentifierList = []
|
2012-09-15 13:44:59 -04:00
|
|
|
}
|
2012-09-13 15:10:40 -07:00
|
|
|
"source" (s ++ "\n") of
|
|
|
|
Left err' -> error $ "\nError:\n" ++ show err'
|
|
|
|
Right result -> result
|
2012-09-10 10:02:12 -07:00
|
|
|
|
2012-09-13 15:24:05 -07:00
|
|
|
data MWState = MWState { mwOptions :: ReaderOptions
|
2012-09-13 15:10:40 -07:00
|
|
|
, mwMaxNestingLevel :: Int
|
2012-09-13 15:24:05 -07:00
|
|
|
, mwNextLinkNumber :: Int
|
2012-09-15 13:44:59 -04:00
|
|
|
, mwCategoryLinks :: [Inlines]
|
2013-11-17 08:47:14 -08:00
|
|
|
, mwHeaderMap :: M.Map Inlines String
|
|
|
|
, mwIdentifierList :: [String]
|
2012-09-13 15:10:40 -07:00
|
|
|
}
|
|
|
|
|
|
|
|
type MWParser = Parser [Char] MWState
|
2012-09-10 10:02:12 -07:00
|
|
|
|
API changes to HasReaderOptions, HasHeaderMap, HasIdentifierList.
Previously these were typeclasses of monads. They've been changed
to be typeclasses of states. This ismplifies the instance definitions
and provides more flexibility.
This is an API change! However, it should be backwards compatible
unless you're defining instances of HasReaderOptions, HasHeaderMap,
or HasIdentifierList. The old getOption function should work as
before (albeit with a more general type).
The function askReaderOption has been removed.
extractReaderOptions has been added.
getOption has been given a default definition.
In HasHeaderMap, extractHeaderMap and updateHeaderMap have been added.
Default definitions have been given for getHeaderMap, putHeaderMap,
and modifyHeaderMap.
In HasIdentifierList, extractIdentifierList and updateIdentifierList
have been added. Default definitions have been given for
getIdentifierList, putIdentifierList, and modifyIdentifierList.
The ultimate goal here is to allow different parsers to use their
own, tailored parser states (instead of ParserState) while still
using shared functions.
2014-03-25 13:43:34 -07:00
|
|
|
instance HasReaderOptions MWState where
|
|
|
|
extractReaderOptions = mwOptions
|
2013-11-17 08:47:14 -08:00
|
|
|
|
API changes to HasReaderOptions, HasHeaderMap, HasIdentifierList.
Previously these were typeclasses of monads. They've been changed
to be typeclasses of states. This ismplifies the instance definitions
and provides more flexibility.
This is an API change! However, it should be backwards compatible
unless you're defining instances of HasReaderOptions, HasHeaderMap,
or HasIdentifierList. The old getOption function should work as
before (albeit with a more general type).
The function askReaderOption has been removed.
extractReaderOptions has been added.
getOption has been given a default definition.
In HasHeaderMap, extractHeaderMap and updateHeaderMap have been added.
Default definitions have been given for getHeaderMap, putHeaderMap,
and modifyHeaderMap.
In HasIdentifierList, extractIdentifierList and updateIdentifierList
have been added. Default definitions have been given for
getIdentifierList, putIdentifierList, and modifyIdentifierList.
The ultimate goal here is to allow different parsers to use their
own, tailored parser states (instead of ParserState) while still
using shared functions.
2014-03-25 13:43:34 -07:00
|
|
|
instance HasHeaderMap MWState where
|
|
|
|
extractHeaderMap = mwHeaderMap
|
2014-03-25 14:55:18 -07:00
|
|
|
updateHeaderMap f st = st{ mwHeaderMap = f $ mwHeaderMap st }
|
2013-11-17 08:47:14 -08:00
|
|
|
|
API changes to HasReaderOptions, HasHeaderMap, HasIdentifierList.
Previously these were typeclasses of monads. They've been changed
to be typeclasses of states. This ismplifies the instance definitions
and provides more flexibility.
This is an API change! However, it should be backwards compatible
unless you're defining instances of HasReaderOptions, HasHeaderMap,
or HasIdentifierList. The old getOption function should work as
before (albeit with a more general type).
The function askReaderOption has been removed.
extractReaderOptions has been added.
getOption has been given a default definition.
In HasHeaderMap, extractHeaderMap and updateHeaderMap have been added.
Default definitions have been given for getHeaderMap, putHeaderMap,
and modifyHeaderMap.
In HasIdentifierList, extractIdentifierList and updateIdentifierList
have been added. Default definitions have been given for
getIdentifierList, putIdentifierList, and modifyIdentifierList.
The ultimate goal here is to allow different parsers to use their
own, tailored parser states (instead of ParserState) while still
using shared functions.
2014-03-25 13:43:34 -07:00
|
|
|
instance HasIdentifierList MWState where
|
|
|
|
extractIdentifierList = mwIdentifierList
|
2014-03-25 14:55:18 -07:00
|
|
|
updateIdentifierList f st = st{ mwIdentifierList = f $ mwIdentifierList st }
|
2013-11-17 08:47:14 -08:00
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
--
|
|
|
|
-- auxiliary functions
|
|
|
|
--
|
|
|
|
|
2012-09-13 15:10:40 -07:00
|
|
|
-- This is used to prevent exponential blowups for things like:
|
|
|
|
-- ''a'''a''a'''a''a'''a''a'''a
|
|
|
|
nested :: MWParser a -> MWParser a
|
|
|
|
nested p = do
|
|
|
|
nestlevel <- mwMaxNestingLevel `fmap` getState
|
|
|
|
guard $ nestlevel > 0
|
|
|
|
updateState $ \st -> st{ mwMaxNestingLevel = mwMaxNestingLevel st - 1 }
|
|
|
|
res <- p
|
|
|
|
updateState $ \st -> st{ mwMaxNestingLevel = nestlevel }
|
|
|
|
return res
|
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
specialChars :: [Char]
|
2013-09-07 22:43:56 -07:00
|
|
|
specialChars = "'[]<=&*{}|\":\\"
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
spaceChars :: [Char]
|
|
|
|
spaceChars = " \n\t"
|
|
|
|
|
|
|
|
sym :: String -> MWParser ()
|
|
|
|
sym s = () <$ try (string s)
|
|
|
|
|
2012-09-13 14:55:33 -07:00
|
|
|
newBlockTags :: [String]
|
2012-09-15 15:05:50 -04:00
|
|
|
newBlockTags = ["haskell","syntaxhighlight","source","gallery","references"]
|
2012-09-13 14:55:33 -07:00
|
|
|
|
2012-09-13 11:18:59 -07:00
|
|
|
isBlockTag' :: Tag String -> Bool
|
2012-09-15 13:44:59 -04:00
|
|
|
isBlockTag' tag@(TagOpen t _) = (isBlockTag tag || t `elem` newBlockTags) &&
|
|
|
|
t `notElem` eitherBlockOrInline
|
|
|
|
isBlockTag' tag@(TagClose t) = (isBlockTag tag || t `elem` newBlockTags) &&
|
|
|
|
t `notElem` eitherBlockOrInline
|
2012-09-13 11:18:59 -07:00
|
|
|
isBlockTag' tag = isBlockTag tag
|
|
|
|
|
2012-09-15 13:44:59 -04:00
|
|
|
isInlineTag' :: Tag String -> Bool
|
|
|
|
isInlineTag' (TagComment _) = True
|
|
|
|
isInlineTag' t = not (isBlockTag' t)
|
|
|
|
|
|
|
|
eitherBlockOrInline :: [String]
|
|
|
|
eitherBlockOrInline = ["applet", "button", "del", "iframe", "ins",
|
|
|
|
"map", "area", "object"]
|
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
htmlComment :: MWParser ()
|
|
|
|
htmlComment = () <$ htmlTag isCommentTag
|
|
|
|
|
|
|
|
inlinesInTags :: String -> MWParser Inlines
|
2012-09-13 16:55:08 -07:00
|
|
|
inlinesInTags tag = try $ do
|
|
|
|
(_,raw) <- htmlTag (~== TagOpen tag [])
|
|
|
|
if '/' `elem` raw -- self-closing tag
|
|
|
|
then return mempty
|
|
|
|
else trimInlines . mconcat <$>
|
|
|
|
manyTill inline (htmlTag (~== TagClose tag))
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
blocksInTags :: String -> MWParser Blocks
|
2012-09-13 16:55:08 -07:00
|
|
|
blocksInTags tag = try $ do
|
|
|
|
(_,raw) <- htmlTag (~== TagOpen tag [])
|
2014-01-22 22:07:13 -08:00
|
|
|
let closer = if tag == "li"
|
|
|
|
then htmlTag (~== TagClose "li")
|
|
|
|
<|> lookAhead (
|
|
|
|
htmlTag (~== TagOpen "li" [])
|
|
|
|
<|> htmlTag (~== TagClose "ol")
|
|
|
|
<|> htmlTag (~== TagClose "ul"))
|
|
|
|
else htmlTag (~== TagClose tag)
|
2012-09-13 16:55:08 -07:00
|
|
|
if '/' `elem` raw -- self-closing tag
|
|
|
|
then return mempty
|
2014-01-22 22:07:13 -08:00
|
|
|
else mconcat <$> manyTill block closer
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
charsInTags :: String -> MWParser [Char]
|
2012-09-13 16:55:08 -07:00
|
|
|
charsInTags tag = try $ do
|
|
|
|
(_,raw) <- htmlTag (~== TagOpen tag [])
|
|
|
|
if '/' `elem` raw -- self-closing tag
|
|
|
|
then return ""
|
2013-01-06 19:35:40 -08:00
|
|
|
else manyTill anyChar (htmlTag (~== TagClose tag))
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
--
|
|
|
|
-- main parser
|
|
|
|
--
|
|
|
|
|
|
|
|
parseMediaWiki :: MWParser Pandoc
|
|
|
|
parseMediaWiki = do
|
|
|
|
bs <- mconcat <$> many block
|
|
|
|
spaces
|
|
|
|
eof
|
2012-09-15 13:44:59 -04:00
|
|
|
categoryLinks <- reverse . mwCategoryLinks <$> getState
|
|
|
|
let categories = if null categoryLinks
|
|
|
|
then mempty
|
|
|
|
else B.para $ mconcat $ intersperse B.space categoryLinks
|
|
|
|
return $ B.doc $ bs <> categories
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
--
|
|
|
|
-- block parsers
|
|
|
|
--
|
|
|
|
|
|
|
|
block :: MWParser Blocks
|
2014-06-20 11:39:24 -07:00
|
|
|
block = do
|
|
|
|
tr <- getOption readerTrace
|
|
|
|
pos <- getPosition
|
|
|
|
res <- mempty <$ skipMany1 blankline
|
2012-09-14 10:19:35 -04:00
|
|
|
<|> table
|
2012-09-13 11:18:59 -07:00
|
|
|
<|> header
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> hrule
|
|
|
|
<|> orderedList
|
2012-09-13 14:47:11 -07:00
|
|
|
<|> bulletList
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> definitionList
|
2012-09-12 22:44:11 -07:00
|
|
|
<|> mempty <$ try (spaces *> htmlComment)
|
|
|
|
<|> preformatted
|
2012-09-13 11:18:59 -07:00
|
|
|
<|> blockTag
|
2012-09-15 13:44:59 -04:00
|
|
|
<|> (B.rawBlock "mediawiki" <$> template)
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> para
|
2014-06-20 11:39:24 -07:00
|
|
|
when tr $
|
|
|
|
trace (printf "line %d: %s" (sourceLine pos)
|
|
|
|
(take 60 $ show $ B.toList res)) (return ())
|
|
|
|
return res
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
para :: MWParser Blocks
|
2013-03-28 10:47:27 -07:00
|
|
|
para = do
|
|
|
|
contents <- trimInlines . mconcat <$> many1 inline
|
|
|
|
if F.all (==Space) contents
|
|
|
|
then return mempty
|
|
|
|
else return $ B.para contents
|
2012-09-10 10:02:12 -07:00
|
|
|
|
2012-09-14 10:19:35 -04:00
|
|
|
table :: MWParser Blocks
|
|
|
|
table = do
|
|
|
|
tableStart
|
2013-03-28 11:26:22 -07:00
|
|
|
styles <- option [] parseAttrs <* blankline
|
|
|
|
let tableWidth = case lookup "width" styles of
|
2013-12-19 21:07:09 -05:00
|
|
|
Just w -> fromMaybe 1.0 $ parseWidth w
|
2012-09-15 15:04:11 -04:00
|
|
|
Nothing -> 1.0
|
2012-09-14 10:19:35 -04:00
|
|
|
caption <- option mempty tableCaption
|
|
|
|
optional rowsep
|
|
|
|
hasheader <- option False $ True <$ (lookAhead (char '!'))
|
2012-09-15 15:04:11 -04:00
|
|
|
(cellspecs',hdr) <- unzip <$> tableRow
|
|
|
|
let widths = map ((tableWidth *) . snd) cellspecs'
|
|
|
|
let restwidth = tableWidth - sum widths
|
|
|
|
let zerocols = length $ filter (==0.0) widths
|
|
|
|
let defaultwidth = if zerocols == 0 || zerocols == length widths
|
|
|
|
then 0.0
|
|
|
|
else restwidth / fromIntegral zerocols
|
|
|
|
let widths' = map (\w -> if w == 0 then defaultwidth else w) widths
|
|
|
|
let cellspecs = zip (map fst cellspecs') widths'
|
2012-09-15 14:20:50 -04:00
|
|
|
rows' <- many $ try $ rowsep *> (map snd <$> tableRow)
|
2014-04-10 16:52:30 -07:00
|
|
|
optional blanklines
|
2012-09-14 10:19:35 -04:00
|
|
|
tableEnd
|
2012-09-14 10:55:16 -04:00
|
|
|
let cols = length hdr
|
2012-09-14 10:19:35 -04:00
|
|
|
let (headers,rows) = if hasheader
|
|
|
|
then (hdr, rows')
|
|
|
|
else (replicate cols mempty, hdr:rows')
|
|
|
|
return $ B.table caption cellspecs headers rows
|
|
|
|
|
2013-03-28 11:26:22 -07:00
|
|
|
parseAttrs :: MWParser [(String,String)]
|
|
|
|
parseAttrs = many1 parseAttr
|
2012-09-15 00:23:24 -04:00
|
|
|
|
2013-03-28 11:26:22 -07:00
|
|
|
parseAttr :: MWParser (String, String)
|
2012-09-15 00:23:24 -04:00
|
|
|
parseAttr = try $ do
|
|
|
|
skipMany spaceChar
|
|
|
|
k <- many1 letter
|
|
|
|
char '='
|
|
|
|
char '"'
|
2013-03-28 11:26:22 -07:00
|
|
|
v <- many1Till (satisfy (/='\n')) (char '"')
|
2012-09-15 00:23:24 -04:00
|
|
|
return (k,v)
|
|
|
|
|
2012-09-14 10:19:35 -04:00
|
|
|
tableStart :: MWParser ()
|
2013-03-27 08:45:51 -07:00
|
|
|
tableStart = try $ guardColumnOne *> skipSpaces *> sym "{|"
|
2012-09-14 10:19:35 -04:00
|
|
|
|
|
|
|
tableEnd :: MWParser ()
|
2013-03-27 08:45:51 -07:00
|
|
|
tableEnd = try $ guardColumnOne *> skipSpaces *> sym "|}"
|
2012-09-14 10:19:35 -04:00
|
|
|
|
|
|
|
rowsep :: MWParser ()
|
2013-05-20 10:43:12 -07:00
|
|
|
rowsep = try $ guardColumnOne *> skipSpaces *> sym "|-" <*
|
2013-05-20 11:08:27 -07:00
|
|
|
optional parseAttr <* blanklines
|
2012-09-14 10:19:35 -04:00
|
|
|
|
|
|
|
cellsep :: MWParser ()
|
2012-09-15 15:04:11 -04:00
|
|
|
cellsep = try $
|
2013-03-27 08:45:51 -07:00
|
|
|
(guardColumnOne *> skipSpaces <*
|
2012-09-15 15:04:11 -04:00
|
|
|
( (char '|' <* notFollowedBy (oneOf "-}+"))
|
|
|
|
<|> (char '!')
|
|
|
|
)
|
|
|
|
)
|
|
|
|
<|> (() <$ try (string "||"))
|
|
|
|
<|> (() <$ try (string "!!"))
|
2012-09-14 10:19:35 -04:00
|
|
|
|
|
|
|
tableCaption :: MWParser Inlines
|
2012-09-14 23:29:06 -04:00
|
|
|
tableCaption = try $ do
|
|
|
|
guardColumnOne
|
2013-03-27 08:45:51 -07:00
|
|
|
skipSpaces
|
2012-09-14 23:29:06 -04:00
|
|
|
sym "|+"
|
2013-05-20 11:08:27 -07:00
|
|
|
optional (try $ parseAttr *> skipSpaces *> char '|' *> skipSpaces)
|
|
|
|
(trimInlines . mconcat) <$> many (notFollowedBy (cellsep <|> rowsep) *> inline)
|
2012-09-14 10:19:35 -04:00
|
|
|
|
2012-09-15 15:04:11 -04:00
|
|
|
tableRow :: MWParser [((Alignment, Double), Blocks)]
|
2014-04-10 16:52:30 -07:00
|
|
|
tableRow = try $ skipMany htmlComment *> many tableCell
|
2012-09-14 10:19:35 -04:00
|
|
|
|
2012-09-15 15:04:11 -04:00
|
|
|
tableCell :: MWParser ((Alignment, Double), Blocks)
|
2012-09-14 23:29:06 -04:00
|
|
|
tableCell = try $ do
|
|
|
|
cellsep
|
|
|
|
skipMany spaceChar
|
2013-03-28 11:26:22 -07:00
|
|
|
attrs <- option [] $ try $ parseAttrs <* skipSpaces <* char '|' <*
|
|
|
|
notFollowedBy (char '|')
|
2012-09-15 01:13:26 -04:00
|
|
|
skipMany spaceChar
|
2012-09-15 21:06:55 -07:00
|
|
|
ls <- concat <$> many (notFollowedBy (cellsep <|> rowsep <|> tableEnd) *>
|
|
|
|
((snd <$> withRaw table) <|> count 1 anyChar))
|
2012-09-15 14:20:50 -04:00
|
|
|
bs <- parseFromString (mconcat <$> many block) ls
|
|
|
|
let align = case lookup "align" attrs of
|
|
|
|
Just "left" -> AlignLeft
|
|
|
|
Just "right" -> AlignRight
|
|
|
|
Just "center" -> AlignCenter
|
|
|
|
_ -> AlignDefault
|
2012-09-15 15:04:11 -04:00
|
|
|
let width = case lookup "width" attrs of
|
2013-12-19 21:07:09 -05:00
|
|
|
Just xs -> fromMaybe 0.0 $ parseWidth xs
|
2012-09-15 15:04:11 -04:00
|
|
|
Nothing -> 0.0
|
|
|
|
return ((align, width), bs)
|
|
|
|
|
|
|
|
parseWidth :: String -> Maybe Double
|
|
|
|
parseWidth s =
|
|
|
|
case reverse s of
|
|
|
|
('%':ds) | all isDigit ds -> safeRead ('0':'.':reverse ds)
|
|
|
|
_ -> Nothing
|
2012-09-14 10:19:35 -04:00
|
|
|
|
2012-09-15 13:44:59 -04:00
|
|
|
template :: MWParser String
|
|
|
|
template = try $ do
|
|
|
|
string "{{"
|
|
|
|
notFollowedBy (char '{')
|
2014-06-20 12:00:26 -07:00
|
|
|
lookAhead $ letter <|> digit <|> char ':'
|
2012-09-15 15:22:18 -04:00
|
|
|
let chunk = template <|> variable <|> many1 (noneOf "{}") <|> count 1 anyChar
|
|
|
|
contents <- manyTill chunk (try $ string "}}")
|
|
|
|
return $ "{{" ++ concat contents ++ "}}"
|
2012-09-13 11:25:55 -07:00
|
|
|
|
2012-09-13 11:18:59 -07:00
|
|
|
blockTag :: MWParser Blocks
|
|
|
|
blockTag = do
|
2012-09-13 16:55:08 -07:00
|
|
|
(tag, _) <- lookAhead $ htmlTag isBlockTag'
|
|
|
|
case tag of
|
|
|
|
TagOpen "blockquote" _ -> B.blockQuote <$> blocksInTags "blockquote"
|
|
|
|
TagOpen "pre" _ -> B.codeBlock . trimCode <$> charsInTags "pre"
|
2012-09-15 01:47:57 -04:00
|
|
|
TagOpen "syntaxhighlight" attrs -> syntaxhighlight "syntaxhighlight" attrs
|
|
|
|
TagOpen "source" attrs -> syntaxhighlight "source" attrs
|
2012-09-13 16:55:08 -07:00
|
|
|
TagOpen "haskell" _ -> B.codeBlockWith ("",["haskell"],[]) . trimCode <$>
|
|
|
|
charsInTags "haskell"
|
|
|
|
TagOpen "gallery" _ -> blocksInTags "gallery"
|
|
|
|
TagOpen "p" _ -> mempty <$ htmlTag (~== tag)
|
|
|
|
TagClose "p" -> mempty <$ htmlTag (~== tag)
|
|
|
|
_ -> B.rawBlock "html" . snd <$> htmlTag (~== tag)
|
2012-09-13 11:18:59 -07:00
|
|
|
|
|
|
|
trimCode :: String -> String
|
|
|
|
trimCode ('\n':xs) = stripTrailingNewlines xs
|
|
|
|
trimCode xs = stripTrailingNewlines xs
|
|
|
|
|
2012-09-15 01:47:57 -04:00
|
|
|
syntaxhighlight :: String -> [Attribute String] -> MWParser Blocks
|
|
|
|
syntaxhighlight tag attrs = try $ do
|
2012-09-13 11:18:59 -07:00
|
|
|
let mblang = lookup "lang" attrs
|
|
|
|
let mbstart = lookup "start" attrs
|
|
|
|
let mbline = lookup "line" attrs
|
|
|
|
let classes = maybe [] (:[]) mblang ++ maybe [] (const ["numberLines"]) mbline
|
|
|
|
let kvs = maybe [] (\x -> [("startFrom",x)]) mbstart
|
2012-09-15 01:47:57 -04:00
|
|
|
contents <- charsInTags tag
|
2012-09-13 11:18:59 -07:00
|
|
|
return $ B.codeBlockWith ("",classes,kvs) $ trimCode contents
|
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
hrule :: MWParser Blocks
|
|
|
|
hrule = B.horizontalRule <$ try (string "----" *> many (char '-') *> newline)
|
|
|
|
|
2012-09-14 10:19:35 -04:00
|
|
|
guardColumnOne :: MWParser ()
|
|
|
|
guardColumnOne = getPosition >>= \pos -> guard (sourceColumn pos == 1)
|
|
|
|
|
2012-09-12 22:44:11 -07:00
|
|
|
preformatted :: MWParser Blocks
|
2012-09-13 12:03:54 -07:00
|
|
|
preformatted = try $ do
|
2012-09-14 10:19:35 -04:00
|
|
|
guardColumnOne
|
2012-09-12 22:44:11 -07:00
|
|
|
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")))
|
2013-03-28 10:47:27 -07:00
|
|
|
let inline' = whitespace' <|> endline' <|> nowiki'
|
2013-03-28 10:51:14 -07:00
|
|
|
<|> (try $ notFollowedBy newline *> inline)
|
2012-09-12 22:44:11 -07:00
|
|
|
let strToCode (Str s) = Code ("",[],[]) s
|
|
|
|
strToCode x = x
|
2013-03-28 10:47:27 -07:00
|
|
|
contents <- mconcat <$> many1 inline'
|
|
|
|
let spacesStr (Str xs) = all isSpace xs
|
|
|
|
spacesStr _ = False
|
|
|
|
if F.all spacesStr contents
|
|
|
|
then return mempty
|
2013-08-10 18:45:00 -07:00
|
|
|
else return $ B.para $ walk strToCode contents
|
2012-09-12 22:44:11 -07:00
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
header :: MWParser Blocks
|
|
|
|
header = try $ do
|
2012-09-14 10:19:35 -04:00
|
|
|
guardColumnOne
|
2012-09-10 10:02:12 -07:00
|
|
|
eqs <- many1 (char '=')
|
|
|
|
let lev = length eqs
|
|
|
|
guard $ lev <= 6
|
|
|
|
contents <- trimInlines . mconcat <$> manyTill inline (count lev $ char '=')
|
2013-11-17 08:47:14 -08:00
|
|
|
attr <- registerHeader nullAttr contents
|
|
|
|
return $ B.headerWith attr lev contents
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
bulletList :: MWParser Blocks
|
2012-09-13 14:47:11 -07:00
|
|
|
bulletList = B.bulletList <$>
|
|
|
|
( many1 (listItem '*')
|
|
|
|
<|> (htmlTag (~== TagOpen "ul" []) *> spaces *> many (listItem '*' <|> li) <*
|
|
|
|
optional (htmlTag (~== TagClose "ul"))) )
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
orderedList :: MWParser Blocks
|
2012-09-13 14:47:11 -07:00
|
|
|
orderedList =
|
|
|
|
(B.orderedList <$> many1 (listItem '#'))
|
2014-01-22 22:07:13 -08:00
|
|
|
<|> try
|
|
|
|
(do (tag,_) <- htmlTag (~== TagOpen "ol" [])
|
|
|
|
spaces
|
|
|
|
items <- many (listItem '#' <|> li)
|
|
|
|
optional (htmlTag (~== TagClose "ol"))
|
|
|
|
let start = fromMaybe 1 $ safeRead $ fromAttrib "start" tag
|
|
|
|
return $ B.orderedListWith (start, DefaultStyle, DefaultDelim) items)
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
definitionList :: MWParser Blocks
|
|
|
|
definitionList = B.definitionList <$> many1 defListItem
|
|
|
|
|
|
|
|
defListItem :: MWParser (Inlines, [Blocks])
|
|
|
|
defListItem = try $ do
|
2012-09-12 17:29:51 -07:00
|
|
|
terms <- mconcat . intersperse B.linebreak <$> many defListTerm
|
2012-09-15 16:24:55 -04:00
|
|
|
-- we allow dd with no dt, or dt with no dd
|
|
|
|
defs <- if B.isNull terms
|
2013-09-07 22:43:56 -07:00
|
|
|
then notFollowedBy (try $ string ":<math>") *>
|
|
|
|
many1 (listItem ':')
|
|
|
|
else many (listItem ':')
|
2012-09-10 10:02:12 -07:00
|
|
|
return (terms, defs)
|
|
|
|
|
|
|
|
defListTerm :: MWParser Inlines
|
2013-01-25 18:32:15 -08:00
|
|
|
defListTerm = char ';' >> skipMany spaceChar >> anyLine >>=
|
2012-09-10 10:02:12 -07:00
|
|
|
parseFromString (trimInlines . mconcat <$> many inline)
|
|
|
|
|
|
|
|
listStart :: Char -> MWParser ()
|
|
|
|
listStart c = char c *> notFollowedBy listStartChar
|
|
|
|
|
|
|
|
listStartChar :: MWParser Char
|
|
|
|
listStartChar = oneOf "*#;:"
|
|
|
|
|
2012-09-12 17:40:15 -07:00
|
|
|
anyListStart :: MWParser Char
|
|
|
|
anyListStart = char '*'
|
|
|
|
<|> char '#'
|
|
|
|
<|> char ':'
|
|
|
|
<|> char ';'
|
2012-09-10 10:02:12 -07:00
|
|
|
|
2012-09-13 14:47:11 -07:00
|
|
|
li :: MWParser Blocks
|
2012-09-13 16:55:08 -07:00
|
|
|
li = lookAhead (htmlTag (~== TagOpen "li" [])) *>
|
2012-09-13 14:47:11 -07:00
|
|
|
(firstParaToPlain <$> blocksInTags "li") <* spaces
|
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
listItem :: Char -> MWParser Blocks
|
|
|
|
listItem c = try $ do
|
2012-09-12 16:47:30 -07:00
|
|
|
extras <- many (try $ char c <* lookAhead listStartChar)
|
|
|
|
if null extras
|
|
|
|
then listItem' c
|
|
|
|
else do
|
2012-09-12 22:44:11 -07:00
|
|
|
skipMany spaceChar
|
2012-09-15 16:17:52 -04:00
|
|
|
first <- concat <$> manyTill listChunk newline
|
|
|
|
rest <- many
|
2014-04-01 10:36:23 -07:00
|
|
|
(try $ string extras *> lookAhead listStartChar *>
|
|
|
|
(concat <$> manyTill listChunk newline))
|
2012-09-12 16:47:30 -07:00
|
|
|
contents <- parseFromString (many1 $ listItem' c)
|
|
|
|
(unlines (first : rest))
|
|
|
|
case c of
|
|
|
|
'*' -> return $ B.bulletList contents
|
|
|
|
'#' -> return $ B.orderedList contents
|
2012-09-12 17:40:15 -07:00
|
|
|
':' -> return $ B.definitionList [(mempty, contents)]
|
2012-09-12 16:47:30 -07:00
|
|
|
_ -> mzero
|
|
|
|
|
2012-09-15 16:17:52 -04:00
|
|
|
-- The point of this is to handle stuff like
|
|
|
|
-- * {{cite book
|
|
|
|
-- | blah
|
|
|
|
-- | blah
|
|
|
|
-- }}
|
|
|
|
-- * next list item
|
|
|
|
-- which seems to be valid mediawiki.
|
|
|
|
listChunk :: MWParser String
|
|
|
|
listChunk = template <|> count 1 anyChar
|
|
|
|
|
2012-09-12 16:47:30 -07:00
|
|
|
listItem' :: Char -> MWParser Blocks
|
|
|
|
listItem' c = try $ do
|
2012-09-10 10:02:12 -07:00
|
|
|
listStart c
|
2012-09-12 22:44:11 -07:00
|
|
|
skipMany spaceChar
|
2012-09-15 16:17:52 -04:00
|
|
|
first <- concat <$> manyTill listChunk newline
|
2012-09-10 10:02:12 -07:00
|
|
|
rest <- many (try $ char c *> lookAhead listStartChar *>
|
2012-09-15 16:17:52 -04:00
|
|
|
(concat <$> manyTill listChunk newline))
|
2012-09-13 14:47:11 -07:00
|
|
|
parseFromString (firstParaToPlain . mconcat <$> many1 block)
|
|
|
|
$ unlines $ first : rest
|
|
|
|
|
|
|
|
firstParaToPlain :: Blocks -> Blocks
|
|
|
|
firstParaToPlain contents =
|
2012-09-12 17:15:21 -07:00
|
|
|
case viewl (B.unMany contents) of
|
2012-09-13 14:47:11 -07:00
|
|
|
(Para xs) :< ys -> B.Many $ (Plain xs) <| ys
|
|
|
|
_ -> contents
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
--
|
|
|
|
-- inline parsers
|
|
|
|
--
|
|
|
|
|
|
|
|
inline :: MWParser Inlines
|
|
|
|
inline = whitespace
|
|
|
|
<|> url
|
|
|
|
<|> str
|
2012-09-15 16:55:42 -04:00
|
|
|
<|> doubleQuotes
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> strong
|
|
|
|
<|> emph
|
2012-09-13 18:16:25 -07:00
|
|
|
<|> image
|
2012-09-13 16:55:08 -07:00
|
|
|
<|> internalLink
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> externalLink
|
2013-09-07 22:43:56 -07:00
|
|
|
<|> math
|
2012-09-13 11:18:59 -07:00
|
|
|
<|> inlineTag
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> B.singleton <$> charRef
|
|
|
|
<|> inlineHtml
|
2012-09-15 15:22:18 -04:00
|
|
|
<|> (B.rawInline "mediawiki" <$> variable)
|
2012-09-15 13:44:59 -04:00
|
|
|
<|> (B.rawInline "mediawiki" <$> template)
|
2012-09-10 10:02:12 -07:00
|
|
|
<|> special
|
|
|
|
|
|
|
|
str :: MWParser Inlines
|
|
|
|
str = B.str <$> many1 (noneOf $ specialChars ++ spaceChars)
|
|
|
|
|
2013-09-07 22:43:56 -07:00
|
|
|
math :: MWParser Inlines
|
2013-10-18 17:50:43 -07:00
|
|
|
math = (B.displayMath . trim <$> try (char ':' >> charsInTags "math"))
|
|
|
|
<|> (B.math . trim <$> charsInTags "math")
|
|
|
|
<|> (B.displayMath . trim <$> try (dmStart *> manyTill anyChar dmEnd))
|
|
|
|
<|> (B.math . trim <$> try (mStart *> manyTill (satisfy (/='\n')) mEnd))
|
2013-09-07 22:43:56 -07:00
|
|
|
where dmStart = string "\\["
|
|
|
|
dmEnd = try (string "\\]")
|
|
|
|
mStart = string "\\("
|
|
|
|
mEnd = try (string "\\)")
|
|
|
|
|
2012-09-15 15:22:18 -04:00
|
|
|
variable :: MWParser String
|
|
|
|
variable = try $ do
|
|
|
|
string "{{{"
|
|
|
|
contents <- manyTill anyChar (try $ string "}}}")
|
|
|
|
return $ "{{{" ++ contents ++ "}}}"
|
2012-09-13 12:03:54 -07:00
|
|
|
|
2012-09-13 11:18:59 -07:00
|
|
|
inlineTag :: MWParser Inlines
|
|
|
|
inlineTag = do
|
2012-09-15 13:44:59 -04:00
|
|
|
(tag, _) <- lookAhead $ htmlTag isInlineTag'
|
2012-09-13 16:55:08 -07:00
|
|
|
case tag of
|
2012-09-15 15:33:48 -04:00
|
|
|
TagOpen "ref" _ -> B.note . B.plain <$> inlinesInTags "ref"
|
2012-09-13 16:55:08 -07:00
|
|
|
TagOpen "nowiki" _ -> try $ do
|
|
|
|
(_,raw) <- htmlTag (~== tag)
|
|
|
|
if '/' `elem` raw
|
|
|
|
then return mempty
|
|
|
|
else B.text . fromEntities <$>
|
|
|
|
manyTill anyChar (htmlTag (~== TagClose "nowiki"))
|
|
|
|
TagOpen "br" _ -> B.linebreak <$ (htmlTag (~== TagOpen "br" []) -- will get /> too
|
|
|
|
*> optional blankline)
|
|
|
|
TagOpen "strike" _ -> B.strikeout <$> inlinesInTags "strike"
|
|
|
|
TagOpen "del" _ -> B.strikeout <$> inlinesInTags "del"
|
|
|
|
TagOpen "sub" _ -> B.subscript <$> inlinesInTags "sub"
|
|
|
|
TagOpen "sup" _ -> B.superscript <$> inlinesInTags "sup"
|
|
|
|
TagOpen "code" _ -> B.code <$> charsInTags "code"
|
|
|
|
TagOpen "tt" _ -> B.code <$> charsInTags "tt"
|
|
|
|
TagOpen "hask" _ -> B.codeWith ("",["haskell"],[]) <$> charsInTags "hask"
|
|
|
|
_ -> B.rawInline "html" . snd <$> htmlTag (~== tag)
|
2012-09-13 11:18:59 -07:00
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
special :: MWParser Inlines
|
2012-09-13 11:18:59 -07:00
|
|
|
special = B.str <$> count 1 (notFollowedBy' (htmlTag isBlockTag') *>
|
2012-09-14 10:55:16 -04:00
|
|
|
oneOf specialChars)
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
inlineHtml :: MWParser Inlines
|
2012-09-15 13:44:59 -04:00
|
|
|
inlineHtml = B.rawInline "html" . snd <$> htmlTag isInlineTag'
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
whitespace :: MWParser Inlines
|
|
|
|
whitespace = B.space <$ (skipMany1 spaceChar <|> endline <|> htmlComment)
|
|
|
|
|
|
|
|
endline :: MWParser ()
|
|
|
|
endline = () <$ try (newline <*
|
2013-03-28 10:47:27 -07:00
|
|
|
notFollowedBy spaceChar <*
|
|
|
|
notFollowedBy newline <*
|
2012-09-10 10:02:12 -07:00
|
|
|
notFollowedBy' hrule <*
|
2012-09-14 10:19:35 -04:00
|
|
|
notFollowedBy tableStart <*
|
2012-09-15 15:22:18 -04:00
|
|
|
notFollowedBy' header <*
|
2012-09-10 10:02:12 -07:00
|
|
|
notFollowedBy anyListStart)
|
|
|
|
|
2013-11-24 12:51:41 +01:00
|
|
|
imageIdentifiers :: [MWParser ()]
|
|
|
|
imageIdentifiers = [sym (identifier ++ ":") | identifier <- identifiers]
|
2014-08-06 00:47:23 +02:00
|
|
|
where identifiers = ["File", "Image", "Archivo", "Datei", "Fichier",
|
|
|
|
"Bild"]
|
2013-11-24 12:51:41 +01:00
|
|
|
|
2012-09-13 18:16:25 -07:00
|
|
|
image :: MWParser Inlines
|
|
|
|
image = try $ do
|
|
|
|
sym "[["
|
2013-11-24 12:51:41 +01:00
|
|
|
choice imageIdentifiers
|
2012-09-13 18:16:25 -07:00
|
|
|
fname <- many1 (noneOf "|]")
|
|
|
|
_ <- many (try $ char '|' *> imageOption)
|
|
|
|
caption <- (B.str fname <$ sym "]]")
|
|
|
|
<|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]")))
|
2013-09-11 09:31:41 -07:00
|
|
|
return $ B.image fname ("fig:" ++ stringify caption) caption
|
2012-09-13 18:16:25 -07:00
|
|
|
|
|
|
|
imageOption :: MWParser String
|
|
|
|
imageOption =
|
|
|
|
try (oneOfStrings [ "border", "thumbnail", "frameless"
|
|
|
|
, "thumb", "upright", "left", "right"
|
|
|
|
, "center", "none", "baseline", "sub"
|
|
|
|
, "super", "top", "text-top", "middle"
|
|
|
|
, "bottom", "text-bottom" ])
|
|
|
|
<|> try (string "frame")
|
|
|
|
<|> try (many1 (oneOf "x0123456789") <* string "px")
|
|
|
|
<|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]"))
|
|
|
|
|
2012-09-13 16:55:08 -07:00
|
|
|
internalLink :: MWParser Inlines
|
|
|
|
internalLink = try $ do
|
2012-09-13 18:16:25 -07:00
|
|
|
sym "[["
|
2012-09-13 17:06:09 -07:00
|
|
|
let addUnderscores x = let (pref,suff) = break (=='#') x
|
|
|
|
in pref ++ intercalate "_" (words suff)
|
2012-09-13 16:55:08 -07:00
|
|
|
pagename <- unwords . words <$> many (noneOf "|]")
|
|
|
|
label <- option (B.text pagename) $ char '|' *>
|
|
|
|
( (mconcat <$> many1 (notFollowedBy (char ']') *> inline))
|
|
|
|
-- the "pipe trick"
|
|
|
|
-- [[Help:Contents|] -> "Contents"
|
|
|
|
<|> (return $ B.text $ drop 1 $ dropWhile (/=':') pagename) )
|
2012-09-13 18:16:25 -07:00
|
|
|
sym "]]"
|
2012-09-15 16:55:42 -04:00
|
|
|
linktrail <- B.text <$> many letter
|
2012-09-15 13:44:59 -04:00
|
|
|
let link = B.link (addUnderscores pagename) "wikilink" (label <> linktrail)
|
|
|
|
if "Category:" `isPrefixOf` pagename
|
|
|
|
then do
|
|
|
|
updateState $ \st -> st{ mwCategoryLinks = link : mwCategoryLinks st }
|
|
|
|
return mempty
|
|
|
|
else return link
|
2012-09-13 16:55:08 -07:00
|
|
|
|
2012-09-10 10:02:12 -07:00
|
|
|
externalLink :: MWParser Inlines
|
|
|
|
externalLink = try $ do
|
|
|
|
char '['
|
2012-09-12 09:29:00 -07:00
|
|
|
(_, src) <- uri
|
2012-09-13 15:24:05 -07:00
|
|
|
lab <- try (trimInlines . mconcat <$>
|
|
|
|
(skipMany1 spaceChar *> manyTill inline (char ']')))
|
|
|
|
<|> do char ']'
|
|
|
|
num <- mwNextLinkNumber <$> getState
|
|
|
|
updateState $ \st -> st{ mwNextLinkNumber = num + 1 }
|
|
|
|
return $ B.str $ show num
|
|
|
|
return $ B.link src "" lab
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
url :: MWParser Inlines
|
|
|
|
url = do
|
2012-09-12 09:29:00 -07:00
|
|
|
(orig, src) <- uri
|
2012-09-10 10:02:12 -07:00
|
|
|
return $ B.link src "" (B.str orig)
|
|
|
|
|
|
|
|
-- | Parses a list of inlines between start and end delimiters.
|
|
|
|
inlinesBetween :: (Show b) => MWParser a -> MWParser b -> MWParser Inlines
|
|
|
|
inlinesBetween start end =
|
|
|
|
(trimInlines . mconcat) <$> try (start >> many1Till inner end)
|
|
|
|
where inner = innerSpace <|> (notFollowedBy' (() <$ whitespace) >> inline)
|
2014-07-11 12:51:26 +01:00
|
|
|
innerSpace = try $ whitespace <* notFollowedBy' end
|
2012-09-10 10:02:12 -07:00
|
|
|
|
|
|
|
emph :: MWParser Inlines
|
|
|
|
emph = B.emph <$> nested (inlinesBetween start end)
|
|
|
|
where start = sym "''" >> lookAhead nonspaceChar
|
|
|
|
end = try $ notFollowedBy' (() <$ strong) >> sym "''"
|
|
|
|
|
|
|
|
strong :: MWParser Inlines
|
|
|
|
strong = B.strong <$> nested (inlinesBetween start end)
|
|
|
|
where start = sym "'''" >> lookAhead nonspaceChar
|
|
|
|
end = try $ sym "'''"
|
|
|
|
|
2012-09-15 16:55:42 -04:00
|
|
|
doubleQuotes :: MWParser Inlines
|
|
|
|
doubleQuotes = B.doubleQuoted . trimInlines . mconcat <$> try
|
|
|
|
((getState >>= guard . readerSmart . mwOptions) *>
|
|
|
|
openDoubleQuote *> manyTill inline closeDoubleQuote )
|
|
|
|
where openDoubleQuote = char '"' <* lookAhead alphaNum
|
|
|
|
closeDoubleQuote = char '"' <* notFollowedBy alphaNum
|
|
|
|
|