1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
|
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.LaTeX.Citation
( citationCommands
, cites
)
where
import Text.Pandoc.Class
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Builder as B
import qualified Data.Map as M
import Data.Text (Text)
import Control.Applicative ((<|>), optional, many)
import Control.Monad (mzero)
import Control.Monad.Trans (lift)
import Control.Monad.Except (throwError)
import Text.Pandoc.Error (PandocError(PandocParsecError))
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
optional, space, spaces, withRaw, (<|>))
citationCommands :: PandocMonad m => LP m Inlines -> M.Map Text (LP m Inlines)
citationCommands inline =
let citation = citationWith inline
tok = spaces *> grouped inline
in M.fromList
[ ("cite", citation "cite" NormalCitation False)
, ("Cite", citation "Cite" NormalCitation False)
, ("citep", citation "citep" NormalCitation False)
, ("citep*", citation "citep*" NormalCitation False)
, ("citeal", citation "citeal" NormalCitation False)
, ("citealp", citation "citealp" NormalCitation False)
, ("citealp*", citation "citealp*" NormalCitation False)
, ("autocite", citation "autocite" NormalCitation False)
, ("smartcite", citation "smartcite" NormalCitation False)
, ("footcite", inNote <$> citation "footcite" NormalCitation False)
, ("parencite", citation "parencite" NormalCitation False)
, ("supercite", citation "supercite" NormalCitation False)
, ("footcitetext", inNote <$> citation "footcitetext" NormalCitation False)
, ("citeyearpar", citation "citeyearpar" SuppressAuthor False)
, ("citeyear", citation "citeyear" SuppressAuthor False)
, ("autocite*", citation "autocite*" SuppressAuthor False)
, ("cite*", citation "cite*" SuppressAuthor False)
, ("parencite*", citation "parencite*" SuppressAuthor False)
, ("textcite", citation "textcite" AuthorInText False)
, ("citet", citation "citet" AuthorInText False)
, ("citet*", citation "citet*" AuthorInText False)
, ("citealt", citation "citealt" AuthorInText False)
, ("citealt*", citation "citealt*" AuthorInText False)
, ("textcites", citation "textcites" AuthorInText True)
, ("cites", citation "cites" NormalCitation True)
, ("autocites", citation "autocites" NormalCitation True)
, ("footcites", inNote <$> citation "footcites" NormalCitation True)
, ("parencites", citation "parencites" NormalCitation True)
, ("supercites", citation "supercites" NormalCitation True)
, ("footcitetexts", inNote <$> citation "footcitetexts" NormalCitation True)
, ("Autocite", citation "Autocite" NormalCitation False)
, ("Smartcite", citation "Smartcite" NormalCitation False)
, ("Footcite", inNote <$> citation "Footcite" NormalCitation False)
, ("Parencite", citation "Parencite" NormalCitation False)
, ("Supercite", citation "Supercite" NormalCitation False)
, ("Footcitetext", inNote <$> citation "Footcitetext" NormalCitation False)
, ("Citeyearpar", citation "Citeyearpar" SuppressAuthor False)
, ("Citeyear", citation "Citeyear" SuppressAuthor False)
, ("Autocite*", citation "Autocite*" SuppressAuthor False)
, ("Cite*", citation "Cite*" SuppressAuthor False)
, ("Parencite*", citation "Parencite*" SuppressAuthor False)
, ("Textcite", citation "Textcite" AuthorInText False)
, ("Textcites", citation "Textcites" AuthorInText True)
, ("Cites", citation "Cites" NormalCitation True)
, ("Autocites", citation "Autocites" NormalCitation True)
, ("Footcites", inNote <$> citation "Footcites" NormalCitation True)
, ("Parencites", citation "Parencites" NormalCitation True)
, ("Supercites", citation "Supercites" NormalCitation True)
, ("Footcitetexts", inNote <$> citation "Footcitetexts" NormalCitation True)
, ("citetext", complexNatbibCitation inline NormalCitation)
, ("citeauthor", (try (tok *> sp *> controlSeq "citetext") *>
complexNatbibCitation inline AuthorInText)
<|> citation "citeauthor" AuthorInText False)
, ("nocite", mempty <$ (citation "nocite" NormalCitation False >>=
addMeta "nocite"))
]
-- citations
addPrefix :: [Inline] -> [Citation] -> [Citation]
addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
addPrefix _ _ = []
addSuffix :: [Inline] -> [Citation] -> [Citation]
addSuffix s ks@(_:_) =
let k = last ks
in init ks ++ [k {citationSuffix = citationSuffix k ++ s}]
addSuffix _ _ = []
simpleCiteArgs :: forall m . PandocMonad m => LP m Inlines -> LP m [Citation]
simpleCiteArgs inline = try $ do
first <- optionMaybe $ toList <$> opt
second <- optionMaybe $ toList <$> opt
keys <- try $ bgroup *> manyTill citationLabel egroup
let (pre, suf) = case (first , second ) of
(Just s , Nothing) -> (mempty, s )
(Just s , Just t ) -> (s , t )
_ -> (mempty, mempty)
conv k = Citation { citationId = k
, citationPrefix = []
, citationSuffix = []
, citationMode = NormalCitation
, citationHash = 0
, citationNoteNum = 0
}
return $ addPrefix pre $ addSuffix suf $ map conv keys
where
opt :: PandocMonad m => LP m Inlines
opt = do
toks <- try (sp *> bracketedToks <* sp)
-- now parse the toks as inlines
st <- getState
parsed <- lift $
runParserT (mconcat <$> many inline) st "bracketed option" toks
case parsed of
Right result -> return result
Left e -> throwError $ PandocParsecError (toSources toks) e
citationLabel :: PandocMonad m => LP m Text
citationLabel = do
sp
untokenize <$>
(many1 (satisfyTok isWordTok <|> symbolIn bibtexKeyChar)
<* sp
<* optional (symbol ',')
<* sp)
where bibtexKeyChar = ".:;?!`'()/*@_+=-&[]" :: [Char]
cites :: PandocMonad m
=> LP m Inlines -> CitationMode -> Bool -> LP m [Citation]
cites inline mode multi = try $ do
let paropt = parenWrapped inline
cits <- if multi
then do
multiprenote <- optionMaybe $ toList <$> paropt
multipostnote <- optionMaybe $ toList <$> paropt
let (pre, suf) = case (multiprenote, multipostnote) of
(Just s , Nothing) -> (mempty, s)
(Nothing , Just t) -> (mempty, t)
(Just s , Just t ) -> (s, t)
_ -> (mempty, mempty)
tempCits <- many1 $ simpleCiteArgs inline
case tempCits of
(k:ks) -> case ks of
(_:_) -> return $ (addMprenote pre k : init ks) ++
[addMpostnote suf (last ks)]
_ -> return [addMprenote pre (addMpostnote suf k)]
_ -> return [[]]
else count 1 $ simpleCiteArgs inline
let cs = concat cits
return $ case mode of
AuthorInText -> case cs of
(c:rest) -> c {citationMode = mode} : rest
[] -> []
_ -> map (\a -> a {citationMode = mode}) cs
where mprenote (k:ks) = (k:ks) ++ [Space]
mprenote _ = mempty
mpostnote (k:ks) = [Str ",", Space] ++ (k:ks)
mpostnote _ = mempty
addMprenote mpn (k:ks) =
let mpnfinal = case citationPrefix k of
(_:_) -> mprenote mpn
_ -> mpn
in addPrefix mpnfinal (k:ks)
addMprenote _ _ = []
addMpostnote = addSuffix . mpostnote
citationWith :: PandocMonad m
=> LP m Inlines -> Text -> CitationMode -> Bool -> LP m Inlines
citationWith inline name mode multi = do
(c,raw) <- withRaw $ cites inline mode multi
return $ cite c (rawInline "latex" $ "\\" <> name <> untokenize raw)
handleCitationPart :: Inlines -> [Citation]
handleCitationPart ils =
let isCite Cite{} = True
isCite _ = False
(pref, rest) = break isCite (toList ils)
in case rest of
(Cite cs _:suff) -> addPrefix pref $ addSuffix suff cs
_ -> []
complexNatbibCitation :: PandocMonad m
=> LP m Inlines -> CitationMode -> LP m Inlines
complexNatbibCitation inline mode = try $ do
(cs, raw) <-
withRaw $ concat <$> do
bgroup
items <- mconcat <$>
many1 (notFollowedBy (symbol ';') >> inline)
`sepBy1` symbol ';'
egroup
return $ map handleCitationPart items
case cs of
[] -> mzero
(c:cits) -> return $ cite (c{ citationMode = mode }:cits)
(rawInline "latex" $ "\\citetext" <> untokenize raw)
inNote :: Inlines -> Inlines
inNote ils =
note $ para $ ils <> str "."
|