diff options
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Definition.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 1 |
9 files changed, 47 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs index 7ddd26625..fffca3b2e 100644 --- a/src/Text/Pandoc/Definition.hs +++ b/src/Text/Pandoc/Definition.hs @@ -52,6 +52,7 @@ type ListAttributes = (Int, ListNumberStyle, ListNumberDelim) -- | Style of list numbers. data ListNumberStyle = DefaultStyle + | Example | Decimal | LowerRoman | UpperRoman diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index cf46bf216..19338661d 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -320,6 +320,23 @@ decimal = do num <- many1 digit return (Decimal, read num) +-- | Parses a '@' and optional label and +-- returns (DefaultStyle, [next example number]). The next +-- example number is incremented in parser state, and the label +-- (if present) is added to the label table. +exampleNum :: GenParser Char ParserState (ListNumberStyle, Int) +exampleNum = do + char '@' + lab <- many (alphaNum <|> oneOf "_-") + st <- getState + let num = stateNextExample st + let newlabels = if null lab + then stateExamples st + else M.insert lab num $ stateExamples st + updateState $ \s -> s{ stateNextExample = num + 1 + , stateExamples = newlabels } + return (Example, num) + -- | Parses a '#' returns (DefaultStyle, 1). defaultNum :: GenParser Char st (ListNumberStyle, Int) defaultNum = do @@ -344,10 +361,10 @@ romanOne = (char 'i' >> return (LowerRoman, 1)) <|> (char 'I' >> return (UpperRoman, 1)) -- | Parses an ordered list marker and returns list attributes. -anyOrderedListMarker :: GenParser Char st ListAttributes +anyOrderedListMarker :: GenParser Char ParserState ListAttributes anyOrderedListMarker = choice $ [delimParser numParser | delimParser <- [inPeriod, inOneParen, inTwoParens], - numParser <- [decimal, defaultNum, romanOne, + numParser <- [decimal, exampleNum, defaultNum, romanOne, lowerAlpha, lowerRoman, upperAlpha, upperRoman]] -- | Parses a list number (num) followed by a period, returns list attributes. @@ -382,11 +399,12 @@ inTwoParens num = try $ do -- returns number. orderedListMarker :: ListNumberStyle -> ListNumberDelim - -> GenParser Char st Int + -> GenParser Char ParserState Int orderedListMarker style delim = do let num = defaultNum <|> -- # can continue any kind of list case style of DefaultStyle -> decimal + Example -> exampleNum Decimal -> decimal UpperRoman -> upperRoman LowerRoman -> lowerRoman @@ -581,7 +599,9 @@ data ParserState = ParserState stateLiterateHaskell :: Bool, -- ^ Treat input as literate haskell stateColumns :: Int, -- ^ Number of columns in terminal stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used - stateIndentedCodeClasses :: [String] -- ^ Classes to use for indented code blocks + stateIndentedCodeClasses :: [String], -- ^ Classes to use for indented code blocks + stateNextExample :: Int, -- ^ Number of next example + stateExamples :: M.Map String Int -- ^ Map from example labels to numbers } deriving Show @@ -606,7 +626,9 @@ defaultParserState = stateLiterateHaskell = False, stateColumns = 80, stateHeaderTable = [], - stateIndentedCodeClasses = [] } + stateIndentedCodeClasses = [], + stateNextExample = 1, + stateExamples = M.empty } data HeaderType = SingleHeader Char -- ^ Single line of characters underneath diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 0a46832a8..086f85bb4 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -69,7 +69,7 @@ setextHChars = "=-" -- treat these as potentially non-text when parsing inline: specialChars :: [Char] -specialChars = "\\[]*_~`<>$!^-.&'\";" +specialChars = "\\[]*_~`<>$!^-.&@'\";" -- -- auxiliary functions @@ -888,6 +888,7 @@ inlineParsers = [ str , rawHtmlInline' , rawLaTeXInline' , escapedChar + , exampleRef , symbol , ltSign ] @@ -923,6 +924,15 @@ ltSign = do specialCharsMinusLt :: [Char] specialCharsMinusLt = filter (/= '<') specialChars +exampleRef :: GenParser Char ParserState Inline +exampleRef = try $ do + char '@' + lab <- many1 (alphaNum <|> oneOf "-_") + examples <- liftM stateExamples getState + case M.lookup lab examples of + Just num -> return (Str $ show num) + Nothing -> pzero + symbol :: GenParser Char ParserState Inline symbol = do result <- oneOf specialCharsMinusLt diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 7b43ec626..13afe5053 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -425,7 +425,7 @@ bulletListStart = try $ do -- parses ordered list start and returns its length (inc following whitespace) orderedListStart :: ListNumberStyle -> ListNumberDelim - -> GenParser Char st Int + -> GenParser Char ParserState Int orderedListStart style delim = try $ do (_, markerLen) <- withHorizDisplacement (orderedListMarker style delim) white <- many1 spaceChar diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index babcf3423..025b54b93 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -304,6 +304,7 @@ orderedListMarkers (start, numstyle, numdelim) = let singleton c = [c] nums = case numstyle of DefaultStyle -> map show [start..] + Example -> map show [start..] Decimal -> map show [start..] UpperAlpha -> drop (start - 1) $ cycle $ map singleton ['A'..'Z'] diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 32948e292..73aadd771 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -153,6 +153,7 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do let style'' = case style' of DefaultStyle -> orderedListStyles !! level Decimal -> "[n]" + Example -> "[n]" LowerRoman -> "[r]" UpperRoman -> "[R]" LowerAlpha -> "[a]" diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 3abed1610..5223259eb 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -154,6 +154,7 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) = let attribs = case numstyle of DefaultStyle -> [] Decimal -> [("numeration", "arabic")] + Example -> [("numeration", "arabic")] UpperAlpha -> [("numeration", "upperalpha")] LowerAlpha -> [("numeration", "loweralpha")] UpperRoman -> [("numeration", "upperroman")] diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index d72fb5eb5..d6cd2a296 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Shared import Text.Pandoc.Parsing import Text.Pandoc.Blocks -import Text.ParserCombinators.Parsec ( parse, GenParser ) +import Text.ParserCombinators.Parsec ( runParser, GenParser ) import Data.List ( group, isPrefixOf, find, intersperse, transpose ) import Text.PrettyPrint.HughesPJ hiding ( Str ) import Control.Monad.State @@ -159,7 +159,7 @@ elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++ else [BulletList $ map elementToListItem subsecs] -- | Ordered list start parser for use in Para below. -olMarker :: GenParser Char st Char +olMarker :: GenParser Char ParserState Char olMarker = do (start, style', delim) <- anyOrderedListMarker if delim == Period && (style' == UpperAlpha || (style' == UpperRoman && @@ -170,7 +170,7 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker -- | True if string begins with an ordered list marker beginsWithOrderedListMarker :: String -> Bool beginsWithOrderedListMarker str = - case parse olMarker "para start" str of + case runParser olMarker defaultParserState "para start" str of Left _ -> False Right _ -> True diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 503222754..65e053827 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -144,6 +144,7 @@ blockToTexinfo (OrderedList (start, numstyle, _) lst) = do exemplar = case numstyle of DefaultStyle -> decimal Decimal -> decimal + Example -> decimal UpperRoman -> decimal -- Roman numerals not supported LowerRoman -> decimal UpperAlpha -> upperAlpha |