{-# 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.Parsing hiding (blankline, many, mathDisplay, mathInline,
optional, space, spaces, withRaw, (<|>))
citationCommands :: PandocMonad m => LP m Inlines -> M.Map Text (LP m Inlines)
citationCommands :: forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
citationCommands LP m Inlines
inline =
let citation :: Text -> CitationMode -> Bool -> LP m Inlines
citation = forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Text -> CitationMode -> Bool -> LP m Inlines
citationWith LP m Inlines
inline
tok :: LP m Inlines
tok = forall (m :: * -> *). PandocMonad m => LP m ()
spaces forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Inlines
inline
in forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"cite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"cite" CitationMode
NormalCitation Bool
False)
, (Text
"Cite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Cite" CitationMode
NormalCitation Bool
False)
, (Text
"citep", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citep" CitationMode
NormalCitation Bool
False)
, (Text
"citep*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citep*" CitationMode
NormalCitation Bool
False)
, (Text
"citeal", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citeal" CitationMode
NormalCitation Bool
False)
, (Text
"citealp", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citealp" CitationMode
NormalCitation Bool
False)
, (Text
"citealp*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citealp*" CitationMode
NormalCitation Bool
False)
, (Text
"autocite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"autocite" CitationMode
NormalCitation Bool
False)
, (Text
"smartcite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"smartcite" CitationMode
NormalCitation Bool
False)
, (Text
"footcite", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"footcite" CitationMode
NormalCitation Bool
False)
, (Text
"parencite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"parencite" CitationMode
NormalCitation Bool
False)
, (Text
"supercite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"supercite" CitationMode
NormalCitation Bool
False)
, (Text
"footcitetext", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"footcitetext" CitationMode
NormalCitation Bool
False)
, (Text
"citeyearpar", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citeyearpar" CitationMode
SuppressAuthor Bool
False)
, (Text
"citeyear", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citeyear" CitationMode
SuppressAuthor Bool
False)
, (Text
"autocite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"autocite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"cite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"cite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"parencite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"parencite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"textcite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"textcite" CitationMode
AuthorInText Bool
False)
, (Text
"citet", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citet" CitationMode
AuthorInText Bool
False)
, (Text
"citet*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citet*" CitationMode
AuthorInText Bool
False)
, (Text
"citealt", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citealt" CitationMode
AuthorInText Bool
False)
, (Text
"citealt*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citealt*" CitationMode
AuthorInText Bool
False)
, (Text
"textcites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"textcites" CitationMode
AuthorInText Bool
True)
, (Text
"cites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"cites" CitationMode
NormalCitation Bool
True)
, (Text
"autocites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"autocites" CitationMode
NormalCitation Bool
True)
, (Text
"footcites", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"footcites" CitationMode
NormalCitation Bool
True)
, (Text
"parencites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"parencites" CitationMode
NormalCitation Bool
True)
, (Text
"supercites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"supercites" CitationMode
NormalCitation Bool
True)
, (Text
"footcitetexts", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"footcitetexts" CitationMode
NormalCitation Bool
True)
, (Text
"Autocite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Autocite" CitationMode
NormalCitation Bool
False)
, (Text
"Smartcite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Smartcite" CitationMode
NormalCitation Bool
False)
, (Text
"Footcite", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Footcite" CitationMode
NormalCitation Bool
False)
, (Text
"Parencite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Parencite" CitationMode
NormalCitation Bool
False)
, (Text
"Supercite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Supercite" CitationMode
NormalCitation Bool
False)
, (Text
"Footcitetext", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Footcitetext" CitationMode
NormalCitation Bool
False)
, (Text
"Citeyearpar", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Citeyearpar" CitationMode
SuppressAuthor Bool
False)
, (Text
"Citeyear", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Citeyear" CitationMode
SuppressAuthor Bool
False)
, (Text
"Autocite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Autocite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"Cite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Cite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"Parencite*", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Parencite*" CitationMode
SuppressAuthor Bool
False)
, (Text
"Textcite", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Textcite" CitationMode
AuthorInText Bool
False)
, (Text
"Textcites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Textcites" CitationMode
AuthorInText Bool
True)
, (Text
"Cites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Cites" CitationMode
NormalCitation Bool
True)
, (Text
"Autocites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Autocites" CitationMode
NormalCitation Bool
True)
, (Text
"Footcites", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Footcites" CitationMode
NormalCitation Bool
True)
, (Text
"Parencites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Parencites" CitationMode
NormalCitation Bool
True)
, (Text
"Supercites", Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Supercites" CitationMode
NormalCitation Bool
True)
, (Text
"Footcitetexts", Inlines -> Inlines
inNote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"Footcitetexts" CitationMode
NormalCitation Bool
True)
, (Text
"citetext", forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> LP m Inlines
complexNatbibCitation LP m Inlines
inline CitationMode
NormalCitation)
, (Text
"citeauthor", (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Inlines
tok forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *). PandocMonad m => LP m ()
sp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"citetext") forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> LP m Inlines
complexNatbibCitation LP m Inlines
inline CitationMode
AuthorInText)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"citeauthor" CitationMode
AuthorInText Bool
False)
, (Text
"nocite", forall a. Monoid a => a
mempty forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> CitationMode -> Bool -> LP m Inlines
citation Text
"nocite" CitationMode
NormalCitation Bool
False forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"nocite"))
]
addPrefix :: [Inline] -> [Citation] -> [Citation]
addPrefix :: [Inline] -> [Citation] -> [Citation]
addPrefix [Inline]
p (Citation
k:[Citation]
ks) = Citation
k {citationPrefix :: [Inline]
citationPrefix = [Inline]
p forall a. [a] -> [a] -> [a]
++ Citation -> [Inline]
citationPrefix Citation
k} forall a. a -> [a] -> [a]
: [Citation]
ks
addPrefix [Inline]
_ [Citation]
_ = []
addSuffix :: [Inline] -> [Citation] -> [Citation]
addSuffix :: [Inline] -> [Citation] -> [Citation]
addSuffix [Inline]
s ks :: [Citation]
ks@(Citation
_:[Citation]
_) =
let k :: Citation
k = forall a. [a] -> a
last [Citation]
ks
in forall a. [a] -> [a]
init [Citation]
ks forall a. [a] -> [a] -> [a]
++ [Citation
k {citationSuffix :: [Inline]
citationSuffix = Citation -> [Inline]
citationSuffix Citation
k forall a. [a] -> [a] -> [a]
++ [Inline]
s}]
addSuffix [Inline]
_ [Citation]
_ = []
simpleCiteArgs :: forall m . PandocMonad m => LP m Inlines -> LP m [Citation]
simpleCiteArgs :: forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> LP m [Citation]
simpleCiteArgs LP m Inlines
inline = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
Maybe [Inline]
first <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PandocMonad m => LP m Inlines
opt
Maybe [Inline]
second <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PandocMonad m => LP m Inlines
opt
[Text]
keys <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill forall (m :: * -> *). PandocMonad m => LP m Text
citationLabel forall (m :: * -> *). PandocMonad m => LP m Tok
egroup
let ([Inline]
pre, [Inline]
suf) = case (Maybe [Inline]
first , Maybe [Inline]
second ) of
(Just [Inline]
s , Maybe [Inline]
Nothing) -> (forall a. Monoid a => a
mempty, [Inline]
s )
(Just [Inline]
s , Just [Inline]
t ) -> ([Inline]
s , [Inline]
t )
(Maybe [Inline], Maybe [Inline])
_ -> (forall a. Monoid a => a
mempty, forall a. Monoid a => a
mempty)
conv :: Text -> Citation
conv Text
k = Citation { citationId :: Text
citationId = Text
k
, citationPrefix :: [Inline]
citationPrefix = []
, citationSuffix :: [Inline]
citationSuffix = []
, citationMode :: CitationMode
citationMode = CitationMode
NormalCitation
, citationHash :: Int
citationHash = Int
0
, citationNoteNum :: Int
citationNoteNum = Int
0
}
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Inline] -> [Citation] -> [Citation]
addPrefix [Inline]
pre forall a b. (a -> b) -> a -> b
$ [Inline] -> [Citation] -> [Citation]
addSuffix [Inline]
suf forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Text -> Citation
conv [Text]
keys
where
opt :: PandocMonad m => LP m Inlines
opt :: PandocMonad m => LP m Inlines
opt = do
[Tok]
toks <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (forall (m :: * -> *). PandocMonad m => LP m ()
sp forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracketedToks forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (m :: * -> *). PandocMonad m => LP m ()
sp)
LaTeXState
st <- forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Either ParseError Inlines
parsed <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a)
runParserT (forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Inlines
inline) LaTeXState
st SourceName
"bracketed option"
(Bool -> [Tok] -> TokStream
TokStream Bool
False [Tok]
toks)
case Either ParseError Inlines
parsed of
Right Inlines
result -> forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
result
Left ParseError
e -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError (forall a. ToSources a => a -> Sources
toSources [Tok]
toks) ParseError
e
citationLabel :: PandocMonad m => LP m Text
citationLabel :: forall (m :: * -> *). PandocMonad m => LP m Text
citationLabel = do
forall (m :: * -> *). PandocMonad m => LP m ()
sp
[Tok] -> Text
untokenize forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
isWordTok forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (m :: * -> *). PandocMonad m => SourceName -> LP m Tok
symbolIn SourceName
bibtexKeyChar)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (m :: * -> *). PandocMonad m => LP m ()
sp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
',')
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (m :: * -> *). PandocMonad m => LP m ()
sp)
where bibtexKeyChar :: SourceName
bibtexKeyChar = SourceName
".:;?!`'()/*@_+=-&[]" :: [Char]
cites :: PandocMonad m
=> LP m Inlines -> CitationMode -> Bool -> LP m [Citation]
cites :: forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> Bool -> LP m [Citation]
cites LP m Inlines
inline CitationMode
mode Bool
multi = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
let paropt :: LP m Inlines
paropt = forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
parenWrapped LP m Inlines
inline
[[Citation]]
cits <- if Bool
multi
then do
Maybe [Inline]
multiprenote <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
paropt
Maybe [Inline]
multipostnote <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
paropt
let ([Inline]
pre, [Inline]
suf) = case (Maybe [Inline]
multiprenote, Maybe [Inline]
multipostnote) of
(Just [Inline]
s , Maybe [Inline]
Nothing) -> (forall a. Monoid a => a
mempty, [Inline]
s)
(Maybe [Inline]
Nothing , Just [Inline]
t) -> (forall a. Monoid a => a
mempty, [Inline]
t)
(Just [Inline]
s , Just [Inline]
t ) -> ([Inline]
s, [Inline]
t)
(Maybe [Inline], Maybe [Inline])
_ -> (forall a. Monoid a => a
mempty, forall a. Monoid a => a
mempty)
[[Citation]]
tempCits <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> LP m [Citation]
simpleCiteArgs LP m Inlines
inline
case [[Citation]]
tempCits of
([Citation]
k:[[Citation]]
ks) -> case [[Citation]]
ks of
([Citation]
_:[[Citation]]
_) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ([Inline] -> [Citation] -> [Citation]
addMprenote [Inline]
pre [Citation]
k forall a. a -> [a] -> [a]
: forall a. [a] -> [a]
init [[Citation]]
ks) forall a. [a] -> [a] -> [a]
++
[[Inline] -> [Citation] -> [Citation]
addMpostnote [Inline]
suf (forall a. [a] -> a
last [[Citation]]
ks)]
[[Citation]]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return [[Inline] -> [Citation] -> [Citation]
addMprenote [Inline]
pre ([Inline] -> [Citation] -> [Citation]
addMpostnote [Inline]
suf [Citation]
k)]
[[Citation]]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return [[]]
else forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> LP m [Citation]
simpleCiteArgs LP m Inlines
inline
let cs :: [Citation]
cs = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Citation]]
cits
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case CitationMode
mode of
CitationMode
AuthorInText -> case [Citation]
cs of
(Citation
c:[Citation]
rest) -> Citation
c {citationMode :: CitationMode
citationMode = CitationMode
mode} forall a. a -> [a] -> [a]
: [Citation]
rest
[] -> []
CitationMode
_ -> forall a b. (a -> b) -> [a] -> [b]
map (\Citation
a -> Citation
a {citationMode :: CitationMode
citationMode = CitationMode
mode}) [Citation]
cs
where mprenote :: [Inline] -> [Inline]
mprenote (Inline
k:[Inline]
ks) = (Inline
kforall a. a -> [a] -> [a]
:[Inline]
ks) forall a. [a] -> [a] -> [a]
++ [Inline
Space]
mprenote [Inline]
_ = forall a. Monoid a => a
mempty
mpostnote :: [Inline] -> [Inline]
mpostnote (Inline
k:[Inline]
ks) = [Text -> Inline
Str Text
",", Inline
Space] forall a. [a] -> [a] -> [a]
++ (Inline
kforall a. a -> [a] -> [a]
:[Inline]
ks)
mpostnote [Inline]
_ = forall a. Monoid a => a
mempty
addMprenote :: [Inline] -> [Citation] -> [Citation]
addMprenote [Inline]
mpn (Citation
k:[Citation]
ks) =
let mpnfinal :: [Inline]
mpnfinal = case Citation -> [Inline]
citationPrefix Citation
k of
(Inline
_:[Inline]
_) -> [Inline] -> [Inline]
mprenote [Inline]
mpn
[Inline]
_ -> [Inline]
mpn
in [Inline] -> [Citation] -> [Citation]
addPrefix [Inline]
mpnfinal (Citation
kforall a. a -> [a] -> [a]
:[Citation]
ks)
addMprenote [Inline]
_ [Citation]
_ = []
addMpostnote :: [Inline] -> [Citation] -> [Citation]
addMpostnote = [Inline] -> [Citation] -> [Citation]
addSuffix forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> [Inline]
mpostnote
citationWith :: PandocMonad m
=> LP m Inlines -> Text -> CitationMode -> Bool -> LP m Inlines
citationWith :: forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Text -> CitationMode -> Bool -> LP m Inlines
citationWith LP m Inlines
inline Text
name CitationMode
mode Bool
multi = do
([Citation]
c,[Tok]
raw) <- forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> Bool -> LP m [Citation]
cites LP m Inlines
inline CitationMode
mode Bool
multi
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Citation] -> Inlines -> Inlines
cite [Citation]
c (Text -> Text -> Inlines
rawInline Text
"latex" forall a b. (a -> b) -> a -> b
$ Text
"\\" forall a. Semigroup a => a -> a -> a
<> Text
name forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
raw)
handleCitationPart :: Inlines -> [Citation]
handleCitationPart :: Inlines -> [Citation]
handleCitationPart Inlines
ils =
let isCite :: Inline -> Bool
isCite Cite{} = Bool
True
isCite Inline
_ = Bool
False
([Inline]
pref, [Inline]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break Inline -> Bool
isCite (forall a. Many a -> [a]
toList Inlines
ils)
in case [Inline]
rest of
(Cite [Citation]
cs [Inline]
_:[Inline]
suff) -> [Inline] -> [Citation] -> [Citation]
addPrefix [Inline]
pref forall a b. (a -> b) -> a -> b
$ [Inline] -> [Citation] -> [Citation]
addSuffix [Inline]
suff [Citation]
cs
[Inline]
_ -> []
complexNatbibCitation :: PandocMonad m
=> LP m Inlines -> CitationMode -> LP m Inlines
complexNatbibCitation :: forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> LP m Inlines
complexNatbibCitation LP m Inlines
inline CitationMode
mode = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
([Citation]
cs, [Tok]
raw) <-
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup
[Inlines]
items <- forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
';') forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines
inline)
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
`sepBy1` forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
';'
forall (m :: * -> *). PandocMonad m => LP m Tok
egroup
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Inlines -> [Citation]
handleCitationPart [Inlines]
items
case [Citation]
cs of
[] -> forall (m :: * -> *) a. MonadPlus m => m a
mzero
(Citation
c:[Citation]
cits) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Citation] -> Inlines -> Inlines
cite (Citation
c{ citationMode :: CitationMode
citationMode = CitationMode
mode }forall a. a -> [a] -> [a]
:[Citation]
cits)
(Text -> Text -> Inlines
rawInline Text
"latex" forall a b. (a -> b) -> a -> b
$ Text
"\\citetext" forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
raw)
inNote :: Inlines -> Inlines
inNote :: Inlines -> Inlines
inNote Inlines
ils =
Blocks -> Inlines
note forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para forall a b. (a -> b) -> a -> b
$ Inlines
ils forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"."