commit
4b77def061
5 changed files with 162 additions and 116 deletions
22
INSTALL
22
INSTALL
|
@ -130,3 +130,25 @@ This is essentially what the binary installer does.
|
||||||
[blaze-html]: http://hackage.haskell.org/package/blaze-html
|
[blaze-html]: http://hackage.haskell.org/package/blaze-html
|
||||||
[Cabal User's Guide]: http://www.haskell.org/cabal/release/latest/doc/users-guide/builders.html#setup-configure-paths
|
[Cabal User's Guide]: http://www.haskell.org/cabal/release/latest/doc/users-guide/builders.html#setup-configure-paths
|
||||||
|
|
||||||
|
|
||||||
|
Running tests
|
||||||
|
-------------
|
||||||
|
|
||||||
|
Pandoc comes with an automated test suite integrated to cabal. Data
|
||||||
|
files are located under the 'tests' directory. If you implement a new
|
||||||
|
feature, please update them to improve covering, and make sure by any
|
||||||
|
necessary mean that the new reference native file is 100% correct.
|
||||||
|
|
||||||
|
Also, tests require templates that leave in a separate git repository,
|
||||||
|
tied into the main one as a git submodule. To populate 'template'
|
||||||
|
directory, you must therefore run first :
|
||||||
|
|
||||||
|
git submodule update --init templates
|
||||||
|
|
||||||
|
You are now ready to build tests :
|
||||||
|
|
||||||
|
cabal-dev install -ftests
|
||||||
|
|
||||||
|
And finally run them !
|
||||||
|
|
||||||
|
cabal-dev test
|
||||||
|
|
|
@ -52,6 +52,7 @@ module Text.Pandoc.Parsing ( (>>~),
|
||||||
failUnlessLHS,
|
failUnlessLHS,
|
||||||
escaped,
|
escaped,
|
||||||
characterReference,
|
characterReference,
|
||||||
|
updateLastStrPos,
|
||||||
anyOrderedListMarker,
|
anyOrderedListMarker,
|
||||||
orderedListMarker,
|
orderedListMarker,
|
||||||
charRef,
|
charRef,
|
||||||
|
@ -786,6 +787,10 @@ charOrRef cs =
|
||||||
guard (c `elem` cs)
|
guard (c `elem` cs)
|
||||||
return c)
|
return c)
|
||||||
|
|
||||||
|
updateLastStrPos :: GenParser Char ParserState ()
|
||||||
|
updateLastStrPos = getPosition >>= \p ->
|
||||||
|
updateState $ \s -> s{ stateLastStrPos = Just p }
|
||||||
|
|
||||||
singleQuoteStart :: GenParser Char ParserState ()
|
singleQuoteStart :: GenParser Char ParserState ()
|
||||||
singleQuoteStart = do
|
singleQuoteStart = do
|
||||||
failIfInQuoteContext InSingleQuote
|
failIfInQuoteContext InSingleQuote
|
||||||
|
|
|
@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||||
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Readers.Textile
|
Module : Text.Pandoc.Readers.Textile
|
||||||
Copyright : Copyright (C) 2010-2011 Paul Rivier and John MacFarlane
|
Copyright : Copyright (C) 2010-2012 Paul Rivier and John MacFarlane
|
||||||
License : GNU GPL, version 2 or above
|
License : GNU GPL, version 2 or above
|
||||||
|
|
||||||
Maintainer : Paul Rivier <paul*rivier#demotera*com>
|
Maintainer : Paul Rivier <paul*rivier#demotera*com>
|
||||||
|
@ -59,10 +59,12 @@ import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import Text.Pandoc.Parsing
|
import Text.Pandoc.Parsing
|
||||||
import Text.Pandoc.Readers.HTML ( htmlTag, isInlineTag, isBlockTag )
|
import Text.Pandoc.Readers.HTML ( htmlTag, isInlineTag, isBlockTag )
|
||||||
|
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
|
||||||
import Text.ParserCombinators.Parsec
|
import Text.ParserCombinators.Parsec
|
||||||
import Text.HTML.TagSoup.Match
|
import Text.HTML.TagSoup.Match
|
||||||
import Data.Char ( digitToInt, isLetter )
|
import Data.Char ( digitToInt, isUpper )
|
||||||
import Control.Monad ( guard, liftM )
|
import Control.Monad ( guard, liftM )
|
||||||
|
import Control.Applicative ((<$>), (*>), (<*))
|
||||||
|
|
||||||
-- | Parse a Textile text and return a Pandoc document.
|
-- | Parse a Textile text and return a Pandoc document.
|
||||||
readTextile :: ParserState -- ^ Parser state, including options for parser
|
readTextile :: ParserState -- ^ Parser state, including options for parser
|
||||||
|
@ -72,14 +74,6 @@ readTextile state s =
|
||||||
(readWith parseTextile) state{ stateOldDashes = True } (s ++ "\n\n")
|
(readWith parseTextile) state{ stateOldDashes = True } (s ++ "\n\n")
|
||||||
|
|
||||||
|
|
||||||
--
|
|
||||||
-- Constants and data structure definitions
|
|
||||||
--
|
|
||||||
|
|
||||||
-- | Special chars border strings parsing
|
|
||||||
specialChars :: [Char]
|
|
||||||
specialChars = "\\[]<>*#_@~-+^&,.;:!?|\"'%()="
|
|
||||||
|
|
||||||
-- | Generate a Pandoc ADT from a textile document
|
-- | Generate a Pandoc ADT from a textile document
|
||||||
parseTextile :: GenParser Char ParserState Pandoc
|
parseTextile :: GenParser Char ParserState Pandoc
|
||||||
parseTextile = do
|
parseTextile = do
|
||||||
|
@ -128,6 +122,7 @@ blockParsers = [ codeBlock
|
||||||
, hrule
|
, hrule
|
||||||
, anyList
|
, anyList
|
||||||
, rawHtmlBlock
|
, rawHtmlBlock
|
||||||
|
, rawLaTeXBlock'
|
||||||
, maybeExplicitBlock "table" table
|
, maybeExplicitBlock "table" table
|
||||||
, maybeExplicitBlock "p" para
|
, maybeExplicitBlock "p" para
|
||||||
, nullBlock ]
|
, nullBlock ]
|
||||||
|
@ -164,21 +159,16 @@ codeBlockPre = try $ do
|
||||||
header :: GenParser Char ParserState Block
|
header :: GenParser Char ParserState Block
|
||||||
header = try $ do
|
header = try $ do
|
||||||
char 'h'
|
char 'h'
|
||||||
level <- oneOf "123456" >>= return . digitToInt
|
level <- digitToInt <$> oneOf "123456"
|
||||||
optional attributes
|
optional attributes >> char '.' >> whitespace
|
||||||
char '.'
|
name <- normalizeSpaces <$> manyTill inline blockBreak
|
||||||
whitespace
|
return $ Header level name
|
||||||
name <- manyTill inline blockBreak
|
|
||||||
return $ Header level (normalizeSpaces name)
|
|
||||||
|
|
||||||
-- | Blockquote of the form "bq. content"
|
-- | Blockquote of the form "bq. content"
|
||||||
blockQuote :: GenParser Char ParserState Block
|
blockQuote :: GenParser Char ParserState Block
|
||||||
blockQuote = try $ do
|
blockQuote = try $ do
|
||||||
string "bq"
|
string "bq" >> optional attributes >> char '.' >> whitespace
|
||||||
optional attributes
|
BlockQuote . singleton <$> para
|
||||||
char '.'
|
|
||||||
whitespace
|
|
||||||
para >>= return . BlockQuote . (:[])
|
|
||||||
|
|
||||||
-- Horizontal rule
|
-- Horizontal rule
|
||||||
|
|
||||||
|
@ -198,10 +188,7 @@ hrule = try $ do
|
||||||
-- strict in the nesting, sublist must start at exactly "parent depth
|
-- strict in the nesting, sublist must start at exactly "parent depth
|
||||||
-- plus one"
|
-- plus one"
|
||||||
anyList :: GenParser Char ParserState Block
|
anyList :: GenParser Char ParserState Block
|
||||||
anyList = try $ do
|
anyList = try $ ( (anyListAtDepth 1) <* blanklines )
|
||||||
l <- anyListAtDepth 1
|
|
||||||
blanklines
|
|
||||||
return l
|
|
||||||
|
|
||||||
-- | This allow one type of list to be nested into an other type,
|
-- | This allow one type of list to be nested into an other type,
|
||||||
-- provided correct nesting
|
-- provided correct nesting
|
||||||
|
@ -212,20 +199,12 @@ anyListAtDepth depth = choice [ bulletListAtDepth depth,
|
||||||
|
|
||||||
-- | Bullet List of given depth, depth being the number of leading '*'
|
-- | Bullet List of given depth, depth being the number of leading '*'
|
||||||
bulletListAtDepth :: Int -> GenParser Char ParserState Block
|
bulletListAtDepth :: Int -> GenParser Char ParserState Block
|
||||||
bulletListAtDepth depth = try $ do
|
bulletListAtDepth depth = try $ BulletList <$> many1 (bulletListItemAtDepth depth)
|
||||||
items <- many1 (bulletListItemAtDepth depth)
|
|
||||||
return (BulletList items)
|
|
||||||
|
|
||||||
-- | Bullet List Item of given depth, depth being the number of
|
-- | Bullet List Item of given depth, depth being the number of
|
||||||
-- leading '*'
|
-- leading '*'
|
||||||
bulletListItemAtDepth :: Int -> GenParser Char ParserState [Block]
|
bulletListItemAtDepth :: Int -> GenParser Char ParserState [Block]
|
||||||
bulletListItemAtDepth depth = try $ do
|
bulletListItemAtDepth = genericListItemAtDepth '*'
|
||||||
count depth (char '*')
|
|
||||||
optional attributes
|
|
||||||
whitespace
|
|
||||||
p <- inlines >>= return . Plain
|
|
||||||
sublist <- option [] (anyListAtDepth (depth + 1) >>= return . (:[]))
|
|
||||||
return (p:sublist)
|
|
||||||
|
|
||||||
-- | Ordered List of given depth, depth being the number of
|
-- | Ordered List of given depth, depth being the number of
|
||||||
-- leading '#'
|
-- leading '#'
|
||||||
|
@ -237,19 +216,19 @@ orderedListAtDepth depth = try $ do
|
||||||
-- | Ordered List Item of given depth, depth being the number of
|
-- | Ordered List Item of given depth, depth being the number of
|
||||||
-- leading '#'
|
-- leading '#'
|
||||||
orderedListItemAtDepth :: Int -> GenParser Char ParserState [Block]
|
orderedListItemAtDepth :: Int -> GenParser Char ParserState [Block]
|
||||||
orderedListItemAtDepth depth = try $ do
|
orderedListItemAtDepth = genericListItemAtDepth '#'
|
||||||
count depth (char '#')
|
|
||||||
optional attributes
|
-- | Common implementation of list items
|
||||||
whitespace
|
genericListItemAtDepth :: Char -> Int -> GenParser Char ParserState [Block]
|
||||||
p <- inlines >>= return . Plain
|
genericListItemAtDepth c depth = try $ do
|
||||||
sublist <- option [] (anyListAtDepth (depth + 1) >>= return . (:[]))
|
count depth (char c) >> optional attributes >> whitespace
|
||||||
return (p:sublist)
|
p <- inlines
|
||||||
|
sublist <- option [] (singleton <$> anyListAtDepth (depth + 1))
|
||||||
|
return ((Plain p):sublist)
|
||||||
|
|
||||||
-- | A definition list is a set of consecutive definition items
|
-- | A definition list is a set of consecutive definition items
|
||||||
definitionList :: GenParser Char ParserState Block
|
definitionList :: GenParser Char ParserState Block
|
||||||
definitionList = try $ do
|
definitionList = try $ DefinitionList <$> many1 definitionListItem
|
||||||
items <- many1 definitionListItem
|
|
||||||
return $ DefinitionList items
|
|
||||||
|
|
||||||
-- | A definition list item in textile begins with '- ', followed by
|
-- | A definition list item in textile begins with '- ', followed by
|
||||||
-- the term defined, then spaces and ":=". The definition follows, on
|
-- the term defined, then spaces and ":=". The definition follows, on
|
||||||
|
@ -277,6 +256,8 @@ blockBreak :: GenParser Char ParserState ()
|
||||||
blockBreak = try (newline >> blanklines >> return ()) <|>
|
blockBreak = try (newline >> blanklines >> return ()) <|>
|
||||||
(lookAhead rawHtmlBlock >> return ())
|
(lookAhead rawHtmlBlock >> return ())
|
||||||
|
|
||||||
|
-- raw content
|
||||||
|
|
||||||
-- | A raw Html Block, optionally followed by blanklines
|
-- | A raw Html Block, optionally followed by blanklines
|
||||||
rawHtmlBlock :: GenParser Char ParserState Block
|
rawHtmlBlock :: GenParser Char ParserState Block
|
||||||
rawHtmlBlock = try $ do
|
rawHtmlBlock = try $ do
|
||||||
|
@ -284,11 +265,16 @@ rawHtmlBlock = try $ do
|
||||||
optional blanklines
|
optional blanklines
|
||||||
return $ RawBlock "html" b
|
return $ RawBlock "html" b
|
||||||
|
|
||||||
|
-- | Raw block of LaTeX content
|
||||||
|
rawLaTeXBlock' :: GenParser Char ParserState Block
|
||||||
|
rawLaTeXBlock' = do
|
||||||
|
failIfStrict
|
||||||
|
RawBlock "latex" <$> (rawLaTeXBlock <* spaces)
|
||||||
|
|
||||||
|
|
||||||
-- | In textile, paragraphs are separated by blank lines.
|
-- | In textile, paragraphs are separated by blank lines.
|
||||||
para :: GenParser Char ParserState Block
|
para :: GenParser Char ParserState Block
|
||||||
para = try $ do
|
para = try $ Para . normalizeSpaces <$> manyTill inline blockBreak
|
||||||
content <- manyTill inline blockBreak
|
|
||||||
return $ Para $ normalizeSpaces content
|
|
||||||
|
|
||||||
|
|
||||||
-- Tables
|
-- Tables
|
||||||
|
@ -302,11 +288,7 @@ tableCell = do
|
||||||
|
|
||||||
-- | A table row is made of many table cells
|
-- | A table row is made of many table cells
|
||||||
tableRow :: GenParser Char ParserState [TableCell]
|
tableRow :: GenParser Char ParserState [TableCell]
|
||||||
tableRow = try $ do
|
tableRow = try $ ( char '|' *> (endBy1 tableCell (char '|')) <* newline)
|
||||||
char '|'
|
|
||||||
cells <- endBy1 tableCell (char '|')
|
|
||||||
newline
|
|
||||||
return cells
|
|
||||||
|
|
||||||
-- | Many table rows
|
-- | Many table rows
|
||||||
tableRows :: GenParser Char ParserState [[TableCell]]
|
tableRows :: GenParser Char ParserState [[TableCell]]
|
||||||
|
@ -314,13 +296,8 @@ tableRows = many1 tableRow
|
||||||
|
|
||||||
-- | Table headers are made of cells separated by a tag "|_."
|
-- | Table headers are made of cells separated by a tag "|_."
|
||||||
tableHeaders :: GenParser Char ParserState [TableCell]
|
tableHeaders :: GenParser Char ParserState [TableCell]
|
||||||
tableHeaders = try $ do
|
tableHeaders = let separator = (try $ string "|_.") in
|
||||||
let separator = (try $ string "|_.")
|
try $ ( separator *> (sepBy1 tableCell separator) <* char '|' <* newline )
|
||||||
separator
|
|
||||||
headers <- sepBy1 tableCell separator
|
|
||||||
char '|'
|
|
||||||
newline
|
|
||||||
return headers
|
|
||||||
|
|
||||||
-- | A table with an optional header. Current implementation can
|
-- | A table with an optional header. Current implementation can
|
||||||
-- handle tables with and without header, but will parse cells
|
-- handle tables with and without header, but will parse cells
|
||||||
|
@ -373,15 +350,10 @@ inlineParsers = [ autoLink
|
||||||
, escapedInline
|
, escapedInline
|
||||||
, htmlSpan
|
, htmlSpan
|
||||||
, rawHtmlInline
|
, rawHtmlInline
|
||||||
|
, rawLaTeXInline'
|
||||||
, note
|
, note
|
||||||
, simpleInline (string "??") (Cite [])
|
, try $ (char '[' *> inlineMarkup <* char ']')
|
||||||
, simpleInline (string "**") Strong
|
, inlineMarkup
|
||||||
, simpleInline (string "__") Emph
|
|
||||||
, simpleInline (char '*') Strong
|
|
||||||
, simpleInline (char '_') Emph
|
|
||||||
, simpleInline (char '-') Strikeout
|
|
||||||
, simpleInline (char '^') Superscript
|
|
||||||
, simpleInline (char '~') Subscript
|
|
||||||
, link
|
, link
|
||||||
, image
|
, image
|
||||||
, mark
|
, mark
|
||||||
|
@ -389,6 +361,18 @@ inlineParsers = [ autoLink
|
||||||
, symbol
|
, symbol
|
||||||
]
|
]
|
||||||
|
|
||||||
|
-- | Inline markups
|
||||||
|
inlineMarkup :: GenParser Char ParserState Inline
|
||||||
|
inlineMarkup = choice [ simpleInline (string "??") (Cite [])
|
||||||
|
, simpleInline (string "**") Strong
|
||||||
|
, simpleInline (string "__") Emph
|
||||||
|
, simpleInline (char '*') Strong
|
||||||
|
, simpleInline (char '_') Emph
|
||||||
|
, simpleInline (char '-') Strikeout
|
||||||
|
, simpleInline (char '^') Superscript
|
||||||
|
, simpleInline (char '~') Subscript
|
||||||
|
]
|
||||||
|
|
||||||
-- | Trademark, registered, copyright
|
-- | Trademark, registered, copyright
|
||||||
mark :: GenParser Char st Inline
|
mark :: GenParser Char st Inline
|
||||||
mark = try $ char '(' >> (try tm <|> try reg <|> copy)
|
mark = try $ char '(' >> (try tm <|> try reg <|> copy)
|
||||||
|
@ -414,41 +398,53 @@ copy = do
|
||||||
|
|
||||||
note :: GenParser Char ParserState Inline
|
note :: GenParser Char ParserState Inline
|
||||||
note = try $ do
|
note = try $ do
|
||||||
char '['
|
ref <- (char '[' *> many1 digit <* char ']')
|
||||||
ref <- many1 digit
|
notes <- stateNotes <$> getState
|
||||||
char ']'
|
|
||||||
state <- getState
|
|
||||||
let notes = stateNotes state
|
|
||||||
case lookup ref notes of
|
case lookup ref notes of
|
||||||
Nothing -> fail "note not found"
|
Nothing -> fail "note not found"
|
||||||
Just raw -> liftM Note $ parseFromString parseBlocks raw
|
Just raw -> liftM Note $ parseFromString parseBlocks raw
|
||||||
|
|
||||||
|
-- | Special chars
|
||||||
|
markupChars :: [Char]
|
||||||
|
markupChars = "\\[]*#_@~-+^|%="
|
||||||
|
|
||||||
|
-- | Break strings on following chars. Space tab and newline break for
|
||||||
|
-- inlines breaking. Open paren breaks for mark. Quote, dash and dot
|
||||||
|
-- break for smart punctuation. Punctuation breaks for regular
|
||||||
|
-- punctuation. Double quote breaks for named links. > and < break
|
||||||
|
-- for inline html.
|
||||||
|
stringBreakers :: [Char]
|
||||||
|
stringBreakers = " \t\n('-.,:!?;\"<>"
|
||||||
|
|
||||||
|
wordBoundaries :: [Char]
|
||||||
|
wordBoundaries = markupChars ++ stringBreakers
|
||||||
|
|
||||||
|
-- | Parse a hyphened sequence of words
|
||||||
|
hyphenedWords :: GenParser Char ParserState String
|
||||||
|
hyphenedWords = try $ do
|
||||||
|
hd <- noneOf wordBoundaries
|
||||||
|
tl <- many ( (noneOf wordBoundaries) <|>
|
||||||
|
try (oneOf markupChars <* lookAhead (noneOf wordBoundaries) ) )
|
||||||
|
let wd = hd:tl
|
||||||
|
option wd $ try $
|
||||||
|
(\r -> concat [wd, "-", r]) <$> (char '-' *> hyphenedWords)
|
||||||
|
|
||||||
-- | Any string
|
-- | Any string
|
||||||
str :: GenParser Char ParserState Inline
|
str :: GenParser Char ParserState Inline
|
||||||
str = do
|
str = do
|
||||||
xs <- many1 (noneOf (specialChars ++ "\t\n "))
|
baseStr <- hyphenedWords
|
||||||
optional $ try $ do
|
-- RedCloth compliance : if parsed word is uppercase and immediatly
|
||||||
lookAhead (char '(')
|
-- followed by parens, parens content is unconditionally word acronym
|
||||||
notFollowedBy' mark
|
fullStr <- option baseStr $ try $ do
|
||||||
getInput >>= setInput . (' ':) -- add space before acronym explanation
|
guard $ all isUpper baseStr
|
||||||
-- parse a following hyphen if followed by a letter
|
acro <- enclosed (char '(') (char ')') anyChar
|
||||||
-- (this prevents unwanted interpretation as starting a strikeout section)
|
return $ concat [baseStr, " (", acro, ")"]
|
||||||
result <- option xs $ try $ do
|
updateLastStrPos
|
||||||
char '-'
|
return $ Str fullStr
|
||||||
next <- lookAhead letter
|
|
||||||
guard $ isLetter (last xs) || isLetter next
|
|
||||||
return $ xs ++ "-"
|
|
||||||
pos <- getPosition
|
|
||||||
updateState $ \s -> s{ stateLastStrPos = Just pos }
|
|
||||||
return $ Str result
|
|
||||||
|
|
||||||
-- | Textile allows HTML span infos, we discard them
|
-- | Textile allows HTML span infos, we discard them
|
||||||
htmlSpan :: GenParser Char ParserState Inline
|
htmlSpan :: GenParser Char ParserState Inline
|
||||||
htmlSpan = try $ do
|
htmlSpan = try $ Str <$> ( char '%' *> attributes *> manyTill anyChar (char '%') )
|
||||||
char '%'
|
|
||||||
_ <- attributes
|
|
||||||
content <- manyTill anyChar (char '%')
|
|
||||||
return $ Str content
|
|
||||||
|
|
||||||
-- | Some number of space chars
|
-- | Some number of space chars
|
||||||
whitespace :: GenParser Char ParserState Inline
|
whitespace :: GenParser Char ParserState Inline
|
||||||
|
@ -461,8 +457,13 @@ endline = try $ do
|
||||||
return LineBreak
|
return LineBreak
|
||||||
|
|
||||||
rawHtmlInline :: GenParser Char ParserState Inline
|
rawHtmlInline :: GenParser Char ParserState Inline
|
||||||
rawHtmlInline = liftM (RawInline "html" . snd)
|
rawHtmlInline = RawInline "html" . snd <$> htmlTag isInlineTag
|
||||||
$ htmlTag isInlineTag
|
|
||||||
|
-- | Raw LaTeX Inline
|
||||||
|
rawLaTeXInline' :: GenParser Char ParserState Inline
|
||||||
|
rawLaTeXInline' = try $ do
|
||||||
|
failIfStrict
|
||||||
|
rawLaTeXInline
|
||||||
|
|
||||||
-- | Textile standard link syntax is "label":target
|
-- | Textile standard link syntax is "label":target
|
||||||
link :: GenParser Char ParserState Inline
|
link :: GenParser Char ParserState Inline
|
||||||
|
@ -490,38 +491,36 @@ image = try $ do
|
||||||
escapedInline :: GenParser Char ParserState Inline
|
escapedInline :: GenParser Char ParserState Inline
|
||||||
escapedInline = escapedEqs <|> escapedTag
|
escapedInline = escapedEqs <|> escapedTag
|
||||||
|
|
||||||
-- | literal text escaped between == ... ==
|
|
||||||
escapedEqs :: GenParser Char ParserState Inline
|
escapedEqs :: GenParser Char ParserState Inline
|
||||||
escapedEqs = try $ do
|
escapedEqs = Str <$> (try $ surrounded (string "==") anyChar)
|
||||||
string "=="
|
|
||||||
contents <- manyTill anyChar (try $ string "==")
|
-- -- | literal text escaped between == ... ==
|
||||||
return $ Str contents
|
-- escapedEqs :: GenParser Char ParserState Inline
|
||||||
|
-- escapedEqs = try $ do
|
||||||
|
-- string "=="
|
||||||
|
-- contents <- manyTill anyChar (try $ string "==")
|
||||||
|
-- return $ Str contents
|
||||||
|
|
||||||
-- | literal text escaped btw <notextile> tags
|
-- | literal text escaped btw <notextile> tags
|
||||||
escapedTag :: GenParser Char ParserState Inline
|
escapedTag :: GenParser Char ParserState Inline
|
||||||
escapedTag = try $ do
|
escapedTag = try $ Str <$>
|
||||||
string "<notextile>"
|
enclosed (string "<notextile>") (string "</notextile>") anyChar
|
||||||
contents <- manyTill anyChar (try $ string "</notextile>")
|
|
||||||
return $ Str contents
|
|
||||||
|
|
||||||
-- | Any special symbol defined in specialChars
|
-- | Any special symbol defined in wordBoundaries
|
||||||
symbol :: GenParser Char ParserState Inline
|
symbol :: GenParser Char ParserState Inline
|
||||||
symbol = do
|
symbol = Str . singleton <$> oneOf wordBoundaries
|
||||||
result <- oneOf specialChars
|
|
||||||
return $ Str [result]
|
|
||||||
|
|
||||||
-- | Inline code
|
-- | Inline code
|
||||||
code :: GenParser Char ParserState Inline
|
code :: GenParser Char ParserState Inline
|
||||||
code = code1 <|> code2
|
code = code1 <|> code2
|
||||||
|
|
||||||
code1 :: GenParser Char ParserState Inline
|
code1 :: GenParser Char ParserState Inline
|
||||||
code1 = surrounded (char '@') anyChar >>= return . Code nullAttr
|
code1 = Code nullAttr <$> surrounded (char '@') anyChar
|
||||||
|
|
||||||
code2 :: GenParser Char ParserState Inline
|
code2 :: GenParser Char ParserState Inline
|
||||||
code2 = do
|
code2 = do
|
||||||
htmlTag (tagOpen (=="tt") null)
|
htmlTag (tagOpen (=="tt") null)
|
||||||
result' <- manyTill anyChar (try $ htmlTag $ tagClose (=="tt"))
|
Code nullAttr <$> manyTill anyChar (try $ htmlTag $ tagClose (=="tt"))
|
||||||
return $ Code nullAttr result'
|
|
||||||
|
|
||||||
-- | Html / CSS attributes
|
-- | Html / CSS attributes
|
||||||
attributes :: GenParser Char ParserState String
|
attributes :: GenParser Char ParserState String
|
||||||
|
@ -542,3 +541,7 @@ simpleInline :: GenParser Char ParserState t -- ^ surrounding parser
|
||||||
simpleInline border construct = surrounded border (inlineWithAttribute) >>=
|
simpleInline border construct = surrounded border (inlineWithAttribute) >>=
|
||||||
return . construct . normalizeSpaces
|
return . construct . normalizeSpaces
|
||||||
where inlineWithAttribute = (try $ optional attributes) >> inline
|
where inlineWithAttribute = (try $ optional attributes) >> inline
|
||||||
|
|
||||||
|
-- | Create a singleton list
|
||||||
|
singleton :: a -> [a]
|
||||||
|
singleton x = [x]
|
||||||
|
|
|
@ -67,9 +67,9 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
||||||
,([Str "beer"],
|
,([Str "beer"],
|
||||||
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
|
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
|
||||||
,Header 1 [Str "Inline",Space,Str "Markup"]
|
,Header 1 [Str "Inline",Space,Str "Markup"]
|
||||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
|
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation",Str ".",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
|
||||||
,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
|
,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
|
||||||
,Para [Str "Superscripts",Str ":",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts",Str ":",Space,Str "H",Subscript [Str "2"],Str "O",Str ",",Space,Str "H",Subscript [Str "23"],Str "O",Str ",",Space,Str "H",Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O",Str "."]
|
,Para [Str "Superscripts",Str ":",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts",Str ":",Space,Subscript [Str "here"],Space,Str "H",Subscript [Str "2"],Str "O",Str ",",Space,Str "H",Subscript [Str "23"],Str "O",Str ",",Space,Str "H",Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O",Str "."]
|
||||||
,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes",Str "."]
|
,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes",Str "."]
|
||||||
,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "\8230",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more",Str "."]
|
,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "\8230",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more",Str "."]
|
||||||
,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Quoted DoubleQuote [Str "I",Str "\8217",Str "d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example",Str "."]
|
,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Quoted DoubleQuote [Str "I",Str "\8217",Str "d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example",Str "."]
|
||||||
|
@ -139,8 +139,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
||||||
[[Plain [Str "this",Space,Str "<",Str "div",Str ">",Space,Str "won",Str "\8217",Str "t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "<",Str "/div",Str ">"]]
|
[[Plain [Str "this",Space,Str "<",Str "div",Str ">",Space,Str "won",Str "\8217",Str "t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "<",Str "/div",Str ">"]]
|
||||||
,[Plain [Str "but",Space,Str "this",Space,RawInline "html" "<strong>",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline "html" "</strong>"]]]
|
,[Plain [Str "but",Space,Str "this",Space,RawInline "html" "<strong>",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline "html" "</strong>"]]]
|
||||||
,Para [Str "Can",Space,Str "you",Space,Str "prove",Space,Str "that",Space,Str "2",Space,Str "<",Space,Str "3",Space,Str "?"]
|
,Para [Str "Can",Space,Str "you",Space,Str "prove",Space,Str "that",Space,Str "2",Space,Str "<",Space,Str "3",Space,Str "?"]
|
||||||
|
,Header 1 [Str "Raw",Space,Str "LaTeX"]
|
||||||
|
,Para [Str "This",Space,Str "Textile",Space,Str "reader",Space,Str "also",Space,Str "accepts",Space,Str "raw",Space,Str "LaTeX",Space,Str "for",Space,Str "blocks",Space,Str ":"]
|
||||||
|
,RawBlock "latex" "\\begin{itemize}\n \\item one\n \\item two\n\\end{itemize}"
|
||||||
|
,Para [Str "and",Space,Str "for",Space,RawInline "latex" "\\emph{inlines}",Str "."]
|
||||||
,Header 1 [Str "Acronyms",Space,Str "and",Space,Str "marks"]
|
,Header 1 [Str "Acronyms",Space,Str "and",Space,Str "marks"]
|
||||||
,Para [Str "PBS",Space,Str "(",Str "Public",Space,Str "Broadcasting",Space,Str "System",Str ")"]
|
,Para [Str "PBS (Public Broadcasting System)"]
|
||||||
,Para [Str "Hi",Str "\8482"]
|
,Para [Str "Hi",Str "\8482"]
|
||||||
,Para [Str "Hi",Space,Str "\8482"]
|
,Para [Str "Hi",Space,Str "\8482"]
|
||||||
,Para [Str "\174",Space,Str "Hi",Str "\174"]
|
,Para [Str "\174",Space,Str "Hi",Str "\174"]
|
||||||
|
|
|
@ -115,14 +115,15 @@ h1. Inline Markup
|
||||||
|
|
||||||
This is _emphasized_, and so __is this__.
|
This is _emphasized_, and so __is this__.
|
||||||
This is *strong*, and so **is this**.
|
This is *strong*, and so **is this**.
|
||||||
|
Hyphenated-words-are-ok, as well as strange_underscore_notation.
|
||||||
A "*strong link*":http://www.foobar.com.
|
A "*strong link*":http://www.foobar.com.
|
||||||
|
|
||||||
_*This is strong and em.*_
|
_*This is strong and em.*_
|
||||||
So is *_this_* word and __**that one**__.
|
So is *_this_* word and __**that one**__.
|
||||||
-This is strikeout and *strong*-
|
-This is strikeout and *strong*-
|
||||||
|
|
||||||
Superscripts: a^bc^d a^*hello*^ a^hello there^.
|
Superscripts: a[^bc^]d a^*hello*^ a[^hello there^].
|
||||||
Subscripts: H~2~O, H~23~O, H~many of them~O.
|
Subscripts: ~here~ H[~2~]O, H[~23~]O, H[~many of them~]O.
|
||||||
|
|
||||||
Dashes : How cool -- automatic dashes.
|
Dashes : How cool -- automatic dashes.
|
||||||
|
|
||||||
|
@ -198,6 +199,17 @@ Html blocks can be <div>inlined</div> as well.
|
||||||
|
|
||||||
Can you prove that 2 < 3 ?
|
Can you prove that 2 < 3 ?
|
||||||
|
|
||||||
|
h1. Raw LaTeX
|
||||||
|
|
||||||
|
This Textile reader also accepts raw LaTeX for blocks :
|
||||||
|
|
||||||
|
\begin{itemize}
|
||||||
|
\item one
|
||||||
|
\item two
|
||||||
|
\end{itemize}
|
||||||
|
|
||||||
|
and for \emph{inlines}.
|
||||||
|
|
||||||
h1. Acronyms and marks
|
h1. Acronyms and marks
|
||||||
|
|
||||||
PBS(Public Broadcasting System)
|
PBS(Public Broadcasting System)
|
||||||
|
|
Loading…
Add table
Reference in a new issue