Skip to content

Commit

Permalink
Section reference labels
Browse files Browse the repository at this point in the history
  • Loading branch information
lierdakil committed Sep 29, 2015
1 parent c5e3c49 commit 34180d7
Show file tree
Hide file tree
Showing 10 changed files with 77 additions and 32 deletions.
24 changes: 24 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,30 @@ You can also reference sections of any level. Section labels use native pandoc s

You can also use `autoSectionLabels` variable to automatically prepend all section labels (automatically generated with pandoc included) with "sec:". Bear in mind that references can't contain periods, commas etc, so some auto-generated labels will still be unusable.

### Section reference labels

***Not currently supported with LaTeX output***

If you want to reference some section by a pre-defined label instead of by number, you can specify section attribute `label`, like this:

```markdown
# Section {label="Custom Label"}
```

This label will be used instead of section number in `chapters` output and when referencing section directly (with `@sec:section`).

Note that with `chapters` output with depth>1, only given section will be referenced by custom label, e.g. with

```markdown
# Chapter 1.

## Section with custom label {#sec:scl label="SCL"}

![](figure.png){#fig:figure}
```

`@sec:scl` will translate into `sec. 1.SCL`, and `@fig:figure` into `fig. 1.SCL.1`

### Code Block labels

There are a couple options to add code block labels. Those work only if code block id starts with `lst:`, e.g. `{#lst:label}`
Expand Down
4 changes: 3 additions & 1 deletion demo-chapters.native
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
,Para [Str "It's",Space,Str "possible",Space,Str "to",Space,Str "capitalize",Space,Str "reference",Space,Str "prefixes,",Space,Str "like",Space,Str "this:",Space,Str "Fig.\160\&1.1",Str "."]
,Para [Str "In",Space,Str "case",Space,Str "of",Space,Str "multiple",Space,Str "references,",Space,Str "capitalization",Space,Str "is",Space,Str "determined",Space,Str "by",Space,Str "first",Space,Str "reference.",Space,Str "Figs.\160\&1.1,",Space,Str "1.2",Space,Str "is",Space,Str "capitalized,",Space,Str "while",Space,Str "figs.\160\&1.1,",Space,Str "1.2",Space,Str "is",Space,Str "not."]
,Para [Str "It",Space,Str "is",Space,Str "also",Space,Str "possible",Space,Str "to",Space,Str "mix",Space,Str "different",Space,Str "references,",Space,Str "like",Space,Str "fig.\160\&1.1",Str ",",Space,Str "tbl.\160\&3.1",Str ",",Space,Str "lsts.\160\&4.1,",Space,Str "4.2",Str ",",Space,Str "figs.\160\&1.2,",Space,Str "1.3",Str ",",Space,Str "which",Space,Str "will",Space,Str "be",Space,Str "grouped",Space,Str "in",Space,Str "order",Space,Str "they",Space,Str "are",Space,Str "specified.",Space,Str "You",Space,Str "can",Space,Str "even",Space,Str "intermix",Space,Str "this",Space,Str "with",Space,Str "regular",Space,Str "citations,",Space,Str "although",Space,Str "it's",Space,Str "not",Space,Str "recommended:",Space,Str "fig.\160\&1.1",Str ",",Space,Str "tbl.\160\&3.1",Str ",",Space,Cite [Citation {citationId = "unprocessedCitation", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@unprocessedCitation]"]]
,Para [Str "You",Space,Str "can",Space,Str "also",Space,Str "have",Space,Str "custom",Space,Str "chapter",Space,Str "reference",Space,Str "labels,",Space,Str "like",Space,Str "sec.\160CustLabs"]
,Header 1 ("sec:sec1",[],[]) [Str "Chapter",Space,Str "1.",Space,Str "Figures"]
,Para [Image [Str "Figure",Space,Str "#",Space,Str "1.1:",Space,Str "First",Space,Str "figure"] ("img1.jpg","fig:")]
,Para [Image [Str "Figure",Space,Str "#",Space,Str "1.2:",Space,Str "Second",Space,Str "figure"] ("img2.jpg","fig:")]
Expand Down Expand Up @@ -50,4 +51,5 @@
,Header 2 ("list-of-tables",[],[]) [Str "List",Space,Str "of",Space,Str "Tables"]
,Div ("",["list"],[]) [Para [Str "3",Str ".",Str "1",Space,Str "Table",Space,Str "example"]]
,Header 1 ("",[],[]) [Str "List",Space,Str "of",Space,Str "Listings"]
,Div ("",["list"],[]) [Para [Str "4",Str ".",Str "1",Space,Str "Listing",Space,Str "caption"],Para [Str "4",Str ".",Str "2",Space,Str "Listing",Space,Str "caption"],Para [Str "4",Str ".",Str "3",Space,Str "Listing",Space,Str "caption"]]]
,Div ("",["list"],[]) [Para [Str "4",Str ".",Str "1",Space,Str "Listing",Space,Str "caption"],Para [Str "4",Str ".",Str "2",Space,Str "Listing",Space,Str "caption"],Para [Str "4",Str ".",Str "3",Space,Str "Listing",Space,Str "caption"]]
,Header 1 ("sec:custlabs",[],[("label","CustLabs")]) [Str "CustLabs.",Space,Str "Custom",Space,Str "labels"]]
6 changes: 6 additions & 0 deletions demo.md
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,8 @@ In case of multiple references, capitalization is determined by first reference.

It is also possible to mix different references, like [@fig:figure1; @tbl:table1; @lst:captionAttr; @lst:tableCaption; @fig:figure2; @fig:figure3], which will be grouped in order they are specified. You can even intermix this with regular citations, although it's not recommended: [@fig:figure1; @tbl:table1; @unprocessedCitation]

You can also have custom chapter reference labels, like @sec:custlabs

# Chapter 1. Figures {#sec:sec1}

![First figure](img1.jpg){#fig:figure1}
Expand Down Expand Up @@ -107,3 +109,7 @@ It's also possible to show lists of figures and tables, like this:
\listoftables

\listoflistings

# Appendix A. Custom labels {label=AppA}

## This section will have custom label {#sec:custlabs label=CustLab}
4 changes: 3 additions & 1 deletion demo.native
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
,Para [Str "It's",Space,Str "possible",Space,Str "to",Space,Str "capitalize",Space,Str "reference",Space,Str "prefixes,",Space,Str "like",Space,Str "this:",Space,Str "Fig.\160\&2",Str "."]
,Para [Str "In",Space,Str "case",Space,Str "of",Space,Str "multiple",Space,Str "references,",Space,Str "capitalization",Space,Str "is",Space,Str "determined",Space,Str "by",Space,Str "first",Space,Str "reference.",Space,Str "Figs.\160\&2,",Space,Str "3",Space,Str "is",Space,Str "capitalized,",Space,Str "while",Space,Str "figs.\160\&2,",Space,Str "3",Space,Str "is",Space,Str "not."]
,Para [Str "It",Space,Str "is",Space,Str "also",Space,Str "possible",Space,Str "to",Space,Str "mix",Space,Str "different",Space,Str "references,",Space,Str "like",Space,Str "fig.\160\&2",Str ",",Space,Str "tbl.\160\&1",Str ",",Space,Str "lsts.\160\&1,",Space,Str "2",Str ",",Space,Str "figs.\160\&3,",Space,Str "4",Str ",",Space,Str "which",Space,Str "will",Space,Str "be",Space,Str "grouped",Space,Str "in",Space,Str "order",Space,Str "they",Space,Str "are",Space,Str "specified.",Space,Str "You",Space,Str "can",Space,Str "even",Space,Str "intermix",Space,Str "this",Space,Str "with",Space,Str "regular",Space,Str "citations,",Space,Str "although",Space,Str "it's",Space,Str "not",Space,Str "recommended:",Space,Str "fig.\160\&2",Str ",",Space,Str "tbl.\160\&1",Str ",",Space,Cite [Citation {citationId = "unprocessedCitation", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@unprocessedCitation]"]]
,Para [Str "You",Space,Str "can",Space,Str "also",Space,Str "have",Space,Str "custom",Space,Str "chapter",Space,Str "reference",Space,Str "labels,",Space,Str "like",Space,Str "sec.\160CustLabs"]
,Header 1 ("sec:sec1",[],[]) [Str "Chapter",Space,Str "1.",Space,Str "Figures"]
,Para [Image [Str "Figure",Space,Str "#",Space,Str "2:",Space,Str "First",Space,Str "figure"] ("img1.jpg","fig:")]
,Para [Image [Str "Figure",Space,Str "#",Space,Str "3:",Space,Str "Second",Space,Str "figure"] ("img2.jpg","fig:")]
Expand Down Expand Up @@ -58,4 +59,5 @@
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "Listing",Space,Str "caption"]]
,[Plain [Str "Listing",Space,Str "caption"]]
,[Plain [Str "Listing",Space,Str "caption"]]]]
,[Plain [Str "Listing",Space,Str "caption"]]]
,Header 1 ("sec:custlabs",[],[("label","CustLabs")]) [Str "CustLabs.",Space,Str "Custom",Space,Str "labels"]]
36 changes: 19 additions & 17 deletions src/Text/Pandoc/CrossRef/References/Blocks.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,37 +23,38 @@ replaceBlocks opts (Header n (label, cls, attrs) text')
unless ("unnumbered" `elem` cls) $ do
modify $ \r@References{curChap=cc} ->
let ln = length cc
inc l = init l ++ [last l + 1]
cl = lookup "label" attrs
inc l = init l ++ [(fst (last l) + 1, cl)]
cc' | ln > n = inc $ take n cc
| ln == n = inc cc
| otherwise = cc ++ take (n-ln) [1,1..]
| otherwise = cc ++ take (n-ln-1) (zip [1,1..] $ repeat Nothing) ++ [(1,cl)]
in r{curChap=cc'}
when ("sec:" `isPrefixOf` label') $ replaceAttrSec label' text' secRefs'
return $ Header n (label', cls, attrs) text'
replaceBlocks opts (Div (label,_,_) [Plain [Image alt img]])
replaceBlocks opts (Div (label,_,attrs) [Plain [Image alt img]])
| "fig:" `isPrefixOf` label
= do
idxStr <- replaceAttr opts label alt imgRefs'
idxStr <- replaceAttr opts label (lookup "label" attrs) alt imgRefs'
let alt' = case outFormat opts of
f | isFormat "latex" f ->
RawInline (Format "tex") ("\\label{"++label++"}") : alt
_ -> applyTemplate idxStr alt $ figureTemplate opts
return $ Para [Image alt' (fst img,"fig:")]
replaceBlocks opts (Div (label,_,_) [Plain [Math DisplayMath eq]])
replaceBlocks opts (Div (label,_,attrs) [Plain [Math DisplayMath eq]])
| "eq:" `isPrefixOf` label
= case outFormat opts of
f | isFormat "latex" f ->
let eqn = "\\begin{equation}"++eq++"\\label{"++label++"}\\end{equation}"
in return $ Para [RawInline (Format "tex") eqn]
_ -> do
idxStr <- replaceAttr opts label [] eqnRefs'
idxStr <- replaceAttr opts label (lookup "label" attrs) [] eqnRefs'
let eq' = eq++"\\qquad("++stringify idxStr++")"
return $ Para [Math DisplayMath eq']
replaceBlocks opts (Div (label,_,_) [Table title align widths header cells])
replaceBlocks opts (Div (label,_,attrs) [Table title align widths header cells])
| not $ null title
, "tbl:" `isPrefixOf` label
= do
idxStr <- replaceAttr opts label (init title) tblRefs'
idxStr <- replaceAttr opts label (lookup "label" attrs) (init title) tblRefs'
let title' =
case outFormat opts of
f | isFormat "latex" f ->
Expand All @@ -78,7 +79,7 @@ replaceBlocks opts cb@(CodeBlock (label, classes, attrs) code)
]
_ -> do
let cap = toList $ text caption
idxStr <- replaceAttr opts label cap lstRefs'
idxStr <- replaceAttr opts label (lookup "label" attrs) cap lstRefs'
let caption' = applyTemplate idxStr cap $ listingTemplate opts
return $ Div (label, "listing":classes, []) [
Para caption'
Expand All @@ -103,7 +104,7 @@ replaceBlocks opts
, RawBlock (Format "tex") "\\end{codelisting}"
]
_ -> do
idxStr <- replaceAttr opts label caption lstRefs'
idxStr <- replaceAttr opts label (lookup "label" attrs) caption lstRefs'
let caption' = applyTemplate idxStr caption $ listingTemplate opts
return $ Div (label, "listing":classes, []) [
Para caption'
Expand Down Expand Up @@ -134,23 +135,24 @@ getRefLabel tag ils
= init `fmap` stripPrefix "{#" attr
getRefLabel _ _ = Nothing

replaceAttr :: Options -> String -> [Inline] -> Accessor References RefMap -> WS [Inline]
replaceAttr o label title prop
replaceAttr :: Options -> String -> Maybe String -> [Inline] -> Accessor References RefMap -> WS [Inline]
replaceAttr o label refLabel title prop
= do
chap <- take (chapDepth o) `fmap` gets curChap
index <- (1+) `fmap` gets (M.size . M.filter ((==chap) . fst . refIndex) . getProp prop)
i <- (1+) `fmap` gets (M.size . M.filter ((==chap) . init . refIndex) . getProp prop)
let index = chap ++ [(i, refLabel)]
modify $ modifyProp prop $ M.insert label RefRec {
refIndex=(chap,index)
refIndex= index
, refTitle=normalizeSpaces title
}
return $ chapPrefix (chapDelim o) chap index
return $ chapPrefix (chapDelim o) index

replaceAttrSec :: String -> [Inline] -> Accessor References RefMap -> WS ()
replaceAttrSec label title prop
= do
chap <- gets curChap
index <- gets curChap
modify $ modifyProp prop $ M.insert label RefRec {
refIndex=(init chap,last chap)
refIndex=index
, refTitle=normalizeSpaces title
}
return ()
2 changes: 1 addition & 1 deletion src/Text/Pandoc/CrossRef/References/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,5 +33,5 @@ makeList opts titlef xs refs
compare' (_,RefRec{refIndex=i}) (_,RefRec{refIndex=j}) = compare i j
item = (:[]) . Plain . refTitle . snd
itemChap = Para . uncurry ((. (Space :)) . (++)) . (numWithChap . refIndex &&& refTitle) . snd
numWithChap = uncurry $ chapPrefix (chapDelim opts)
numWithChap = chapPrefix (chapDelim opts)
style = (1,DefaultStyle,DefaultDelim)
14 changes: 9 additions & 5 deletions src/Text/Pandoc/CrossRef/References/Refs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,31 +108,35 @@ replaceRefsOther :: String -> Options -> [Citation] -> WS [Inline]
replaceRefsOther prefix opts cits = do
indices <- mapM (getRefIndex prefix) cits
let
indices' = groupBy ((==) `on` (fmap fst . fst)) (sort indices)
indices' = groupBy ((==) `on` (fmap init . fst)) (sort indices)
cap = maybe False isFirstUpper $ getLabelPrefix . citationId . head $ cits
return $ normalizeInlines $ getRefPrefix opts prefix cap (length cits - 1) ++ intercalate [Str ",", Space] (makeIndices opts `map` indices')

getRefIndex :: String -> Citation -> WS (Maybe ([Int], Int), [Inline])
getRefIndex :: String -> Citation -> WS (Maybe Index, [Inline])
getRefIndex prefix Citation{citationId=cid,citationSuffix=suf}
= (\x -> (x,suf)) `fmap` gets (fmap refIndex . M.lookup lab . getProp prop)
where
prop = lookupUnsafe prefix accMap
lab = prefix ++ getLabelWithoutPrefix cid

makeIndices :: Options -> [(Maybe ([Int], Int), [Inline])] -> [Inline]
makeIndices :: Options -> [(Maybe Index, [Inline])] -> [Inline]
makeIndices _ s | any (isNothing . fst) s = [Strong [Str "??"]]
makeIndices o s = intercalate sep $ reverse $ map f $ foldl' f2 [] $ map (A.first fromJust) $ filter (isJust . fst) s
where
f2 :: [[(Index, [Inline])]] -> (Index, [Inline]) -> [[(Index, [Inline])]]
f2 [] (i,suf) = [[(i,suf)]]
f2 ([]:xs) (i,suf) = [(i,suf)]:xs
f2 l@(x@(((_,hx),sufp):_):xs) (i@(_,ni),suf)
f2 l@(x@((ix,sufp):_):xs) (i,suf)
| not (null suf) || not (null sufp) = [(i,suf)]:l
| ni-hx == 0 = l -- remove duplicates
| ni-hx == 1 = ((i,[]):x):xs -- group sequental
| otherwise = [(i,[])]:l -- new group
where
hx = fst $ last ix
ni = fst $ last i
f [] = [] -- drop empty lists
f [w] = show' w -- single value
f [w1,w2] = show' w2 ++ sep ++ show' w1 -- two values
f (x:xs) = show' (last xs) ++ rangeDelim o ++ show' x -- shorten more than two values
sep = [Str ",", Space]
show' ((c,n),suf) = chapPrefix (chapDelim o) c n ++ suf
show' (i,suf) = chapPrefix (chapDelim o) i ++ suf
7 changes: 5 additions & 2 deletions src/Text/Pandoc/CrossRef/References/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Text.Pandoc.CrossRef.References.Types ( References(..)
, WS
, RefRec(..)
, RefMap
, Index
, def
) where

Expand All @@ -10,7 +11,9 @@ import Text.Pandoc.Definition
import Control.Monad.State
import Data.Default

data RefRec = RefRec { refIndex :: ([Int], Int)
type Index = [(Int, Maybe String)]

data RefRec = RefRec { refIndex :: Index
, refTitle :: [Inline]
} deriving (Show, Eq)

Expand All @@ -22,7 +25,7 @@ data References = References { imgRefs :: RefMap
, tblRefs :: RefMap
, lstRefs :: RefMap
, secRefs :: RefMap
, curChap :: [Int]
, curChap :: Index
} deriving (Show, Eq)

--state monad
Expand Down
6 changes: 4 additions & 2 deletions src/Text/Pandoc/CrossRef/Util/Util.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
module Text.Pandoc.CrossRef.Util.Util where

import Text.Pandoc.CrossRef.References.Types
import Text.Pandoc.Definition
import Data.Char (toUpper, toLower, isUpper)
import Data.List (intercalate)
import Data.Maybe (fromMaybe)

isFormat :: String -> Maybe Format -> Bool
isFormat fmt (Just (Format f)) = takeWhile (`notElem` "+-") f == fmt
Expand All @@ -20,5 +22,5 @@ isFirstUpper :: String -> Bool
isFirstUpper (x:_) = isUpper x
isFirstUpper [] = False

chapPrefix :: [Inline] -> [Int] -> Int -> [Inline]
chapPrefix delim chap index = intercalate delim (map (return . Str . show) (chap++[index]))
chapPrefix :: [Inline] -> Index -> [Inline]
chapPrefix delim index = intercalate delim (map (return . Str . uncurry (fromMaybe . show)) index)
6 changes: 3 additions & 3 deletions test-pandoc-crossref.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ main = hspec $ do
testBlocks (section "Section Header" 1 "section")
(section "Section Header" 1 "section",
def{secRefs=M.fromList $ refRec' "sec:section" 1 "Section Header",
curChap=[1]})
curChap=[(1,Nothing)]})

describe "References.Refs.replaceRefs" $ do
it "References one image" $
Expand Down Expand Up @@ -147,13 +147,13 @@ refGen' :: String -> [Int] -> [(Int, Int)] -> M.Map String RefRec
refGen' p l1 l2 = M.fromList $ mconcat $ zipWith refRec''' (((uncapitalizeFirst p++) . show) `map` l1) l2

refRec' :: String -> Int -> String -> [(String, RefRec)]
refRec' ref i tit = [(ref, RefRec{refIndex=([],i),refTitle=toList $ text tit})]
refRec' ref i tit = [(ref, RefRec{refIndex=[(i,Nothing)],refTitle=toList $ text tit})]

refRec'' :: String -> Int -> [(String, RefRec)]
refRec'' ref i = refRec' ref i []

refRec''' :: String -> (Int, Int) -> [(String, RefRec)]
refRec''' ref (c,i) = [(ref, RefRec{refIndex=([c],i),refTitle=toList $ text []})]
refRec''' ref (c,i) = [(ref, RefRec{refIndex=[(c,Nothing), (i,Nothing)],refTitle=toList $ text []})]

testRefs' :: String -> [Int] -> [Int] -> Accessor References (M.Map String RefRec) -> String -> Expectation
testRefs' p l1 l2 prop res = testRefs (para $ citeGen p l1) (setProp prop (refGen p l1 l2) def) (para $ text res)
Expand Down

0 comments on commit 34180d7

Please sign in to comment.