Implemented @ for sequentially numbered examples.
Also implemented (@label) for example labels and references.
This commit is contained in:
parent
db31e06693
commit
6972c0b5b0
9 changed files with 75 additions and 11 deletions
28
README
28
README
|
@ -667,12 +667,38 @@ So, the following yields a list numbered sequentially starting from 2:
|
|||
1. Four
|
||||
* Five
|
||||
|
||||
If default list markers are desired, use '`#.`':
|
||||
If default list markers are desired, use `#.`:
|
||||
|
||||
#. one
|
||||
#. two
|
||||
#. three
|
||||
|
||||
Numbered examples
|
||||
-----------------
|
||||
|
||||
The special list marker `@` can be used for sequentially numbered
|
||||
examples. The first list item with a `@` marker will be numbered '1',
|
||||
the next '2', and so on, throughout the document. The numbered examples
|
||||
need not occur in a single list; each new list using `@` will take up
|
||||
where the last stopped. So, for example:
|
||||
|
||||
(@) My first example will be numbered (1).
|
||||
(@) My second example will be numbered (2).
|
||||
|
||||
Explanation of examples.
|
||||
|
||||
(@) My third example will be numbered (3).
|
||||
|
||||
Numbered examples can be labeled and referred to later in the
|
||||
document:
|
||||
|
||||
(@good) This is a good example.
|
||||
|
||||
As (@good) illustrates, ...
|
||||
|
||||
The label can be any string of alphanumeric characters, underscores,
|
||||
or hyphens. The example must occur before the reference.
|
||||
|
||||
Definition lists
|
||||
----------------
|
||||
|
||||
|
|
|
@ -52,6 +52,7 @@ type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)
|
|||
|
||||
-- | Style of list numbers.
|
||||
data ListNumberStyle = DefaultStyle
|
||||
| Example
|
||||
| Decimal
|
||||
| LowerRoman
|
||||
| UpperRoman
|
||||
|
|
|
@ -35,6 +35,7 @@ import Data.List ( transpose, isSuffixOf, sortBy, findIndex, intercalate )
|
|||
import Data.Ord ( comparing )
|
||||
import Data.Char ( isAlphaNum )
|
||||
import Data.Maybe
|
||||
import qualified Data.Map as M
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXEnvironment' )
|
||||
|
@ -67,7 +68,7 @@ setextHChars = "=-"
|
|||
|
||||
-- treat these as potentially non-text when parsing inline:
|
||||
specialChars :: [Char]
|
||||
specialChars = "\\[]*_~`<>$!^-.&'\"\8216\8217\8220\8221;"
|
||||
specialChars = "\\[]*_~`<>$!^-.&@'\"\8216\8217\8220\8221;"
|
||||
|
||||
--
|
||||
-- auxiliary functions
|
||||
|
@ -915,6 +916,7 @@ inlineParsers = [ str
|
|||
, rawHtmlInline'
|
||||
, rawLaTeXInline'
|
||||
, escapedChar
|
||||
, exampleRef
|
||||
, symbol
|
||||
, ltSign ]
|
||||
|
||||
|
@ -950,6 +952,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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -576,6 +576,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
|
||||
|
@ -600,10 +617,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.
|
||||
|
@ -638,11 +655,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
|
||||
|
@ -700,7 +718,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
|
||||
|
||||
|
@ -725,7 +745,9 @@ defaultParserState =
|
|||
stateLiterateHaskell = False,
|
||||
stateColumns = 80,
|
||||
stateHeaderTable = [],
|
||||
stateIndentedCodeClasses = [] }
|
||||
stateIndentedCodeClasses = [],
|
||||
stateNextExample = 1,
|
||||
stateExamples = M.empty }
|
||||
|
||||
data HeaderType
|
||||
= SingleHeader Char -- ^ Single line of characters underneath
|
||||
|
@ -855,6 +877,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']
|
||||
|
|
|
@ -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]"
|
||||
|
|
|
@ -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")]
|
||||
|
|
|
@ -34,7 +34,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Shared
|
||||
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
|
||||
|
@ -158,7 +158,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 &&
|
||||
|
@ -169,7 +169,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
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
Loading…
Add table
Reference in a new issue