{-# LANGUAGE OverloadedStrings, LambdaCase, RankNTypes #-}
module Text.Pandoc.CrossRef.References.Refs (replaceRefs) where
import Control.Arrow as A
import Control.Monad.Reader
import Data.Function
import Data.List
import qualified Data.List.HT as HT
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Text as T
import Text.Pandoc.Builder
import qualified Data.Sequence as S
import Data.Sequence (ViewR(..))
import Debug.Trace
import Lens.Micro.Mtl
import Text.Pandoc.CrossRef.References.Types
import Text.Pandoc.CrossRef.References.Monad
import Text.Pandoc.CrossRef.Util.Options
import Text.Pandoc.CrossRef.Util.Template
import Text.Pandoc.CrossRef.Util.Util
replaceRefs :: [Inline] -> WS [Inline]
replaceRefs :: [Inline] -> WS [Inline]
replaceRefs (Cite [Citation]
cits [Inline]
_:[Inline]
xs) = do
Options
opts <- forall r (m :: * -> *). MonadReader r m => m r
ask :: WS Options
forall a. Many a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList [Inline]
xs) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (f :: * -> *).
(Eq a, Monoid a, Foldable f) =>
a -> f a -> a
intercalate' (Text -> Inlines
text Text
", ") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Many a
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Options -> [Citation] -> WS [Inline]
replaceRefs' Options
opts) (forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy Citation -> Citation -> Bool
eqPrefix [Citation]
cits)
where
eqPrefix :: Citation -> Citation -> Bool
eqPrefix Citation
a Citation
b = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Eq a => a -> a -> Bool
(==) forall a b. (a -> b) -> a -> b
$
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
uncapitalizeFirst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
getLabelPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId) forall {b'} {c'}. (b' -> c') -> (b', b') -> (c', c')
<***> (Citation
a,Citation
b)
<***> :: (b' -> c') -> (b', b') -> (c', c')
(<***>) = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
(***)
replaceRefs' :: Options -> [Citation] -> WS [Inline]
replaceRefs' :: Options -> [Citation] -> WS [Inline]
replaceRefs' Options
opts [Citation]
cits'
| Just Prefix
prefix <- [Citation] -> Maybe Prefix
allCitsPrefix [Citation]
cits'
= Options -> Prefix -> [Citation] -> WS [Inline]
replaceRefs'' Options
opts Prefix
prefix [Citation]
cits'
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return [[Citation] -> [Inline] -> Inline
Cite [Citation]
cits' [Inline]
il']
where
il' :: [Inline]
il' = forall a. Many a -> [a]
toList forall a b. (a -> b) -> a -> b
$
Text -> Inlines
str Text
"["
forall a. Semigroup a => a -> a -> a
<> forall a (f :: * -> *).
(Eq a, Monoid a, Foldable f) =>
a -> f a -> a
intercalate' (Text -> Inlines
text Text
"; ") (forall a b. (a -> b) -> [a] -> [b]
map Citation -> Inlines
citationToInlines [Citation]
cits')
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"]"
citationToInlines :: Citation -> Inlines
citationToInlines Citation
c =
forall a. [a] -> Many a
fromList (Citation -> [Inline]
citationPrefix Citation
c) forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
text (Text
"@" forall a. Semigroup a => a -> a -> a
<> Citation -> Text
citationId Citation
c)
forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList (Citation -> [Inline]
citationSuffix Citation
c)
replaceRefs'' :: Options -> Prefix -> [Citation] -> WS [Inline]
replaceRefs'' :: Options -> Prefix -> [Citation] -> WS [Inline]
replaceRefs'' Options
opts = (forall a b. (a -> b) -> a -> b
$ Options
opts) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ case Options -> Maybe Format
outFormat Options
opts of
Maybe Format
f | Maybe Format -> Bool
isLatexFormat Maybe Format
f -> Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex
Maybe Format
_ -> Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther
replaceRefs [Inline]
x = forall (m :: * -> *) a. Monad m => a -> m a
return [Inline]
x
pfxMap :: T.Text -> Maybe Prefix
pfxMap :: Text -> Maybe Prefix
pfxMap = \case
Text
"fig:" -> forall a. a -> Maybe a
Just Prefix
PfxImg
Text
"eq:" -> forall a. a -> Maybe a
Just Prefix
PfxEqn
Text
"tbl:" -> forall a. a -> Maybe a
Just Prefix
PfxTbl
Text
"lst:" -> forall a. a -> Maybe a
Just Prefix
PfxLst
Text
"sec:" -> forall a. a -> Maybe a
Just Prefix
PfxSec
Text
_ -> forall a. Maybe a
Nothing
pfxMapR :: Prefix -> T.Text
pfxMapR :: Prefix -> Text
pfxMapR = \case
Prefix
PfxImg -> Text
"fig:"
Prefix
PfxEqn -> Text
"eq:"
Prefix
PfxTbl -> Text
"tbl:"
Prefix
PfxLst -> Text
"lst:"
Prefix
PfxSec -> Text
"sec:"
prefMap :: Prefix -> (Options -> Bool -> Int -> [Inline], Options -> Template)
prefMap :: Prefix -> (Options -> Bool -> Int -> [Inline], Options -> Template)
prefMap = \case
Prefix
PfxImg -> (Options -> Bool -> Int -> [Inline]
figPrefix, Options -> Template
figPrefixTemplate)
Prefix
PfxEqn -> (Options -> Bool -> Int -> [Inline]
eqnPrefix, Options -> Template
eqnPrefixTemplate)
Prefix
PfxTbl -> (Options -> Bool -> Int -> [Inline]
tblPrefix, Options -> Template
tblPrefixTemplate)
Prefix
PfxLst -> (Options -> Bool -> Int -> [Inline]
lstPrefix, Options -> Template
lstPrefixTemplate)
Prefix
PfxSec -> (Options -> Bool -> Int -> [Inline]
secPrefix, Options -> Template
secPrefixTemplate)
prefixes :: [Prefix]
prefixes :: [Prefix]
prefixes = [forall a. Bounded a => a
minBound..]
getRefPrefix :: Options -> Prefix -> Bool -> Int -> [Inline] -> [Inline]
getRefPrefix :: Options -> Prefix -> Bool -> Int -> [Inline] -> [Inline]
getRefPrefix Options
opts Prefix
prefix Bool
capitalize Int
num [Inline]
cit =
forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' (forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList [(Text
"i", [Inline]
cit), (Text
"p", [Inline]
refprefix)])
forall a b. (a -> b) -> a -> b
$ Options -> Template
reftempl Options
opts
where (Options -> Bool -> Int -> [Inline]
refprefixf, Options -> Template
reftempl) = Prefix -> (Options -> Bool -> Int -> [Inline], Options -> Template)
prefMap Prefix
prefix
refprefix :: [Inline]
refprefix = Options -> Bool -> Int -> [Inline]
refprefixf Options
opts Bool
capitalize Int
num
allCitsPrefix :: [Citation] -> Maybe Prefix
allCitsPrefix :: [Citation] -> Maybe Prefix
allCitsPrefix [Citation]
cits = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find Prefix -> Bool
isCitationPrefix [Prefix]
prefixes
where
isCitationPrefix :: Prefix -> Bool
isCitationPrefix Prefix
p =
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Prefix -> Text
pfxMapR Prefix
p Text -> Text -> Bool
`T.isPrefixOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
uncapitalizeFirst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId) [Citation]
cits
replaceRefsLatex :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex Prefix
prefix Options
opts [Citation]
cits
| Options -> Bool
cref Options
opts
= Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex' Prefix
prefix Options
opts [Citation]
cits
| Bool
otherwise
= forall a. Many a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (f :: * -> *).
(Eq a, Monoid a, Foldable f) =>
a -> f a -> a
intercalate' (Text -> Inlines
text Text
", ") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Many a
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex' Prefix
prefix Options
opts) (forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy Citation -> Citation -> Bool
citationGroupPred [Citation]
cits)
replaceRefsLatex' :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex' :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsLatex' Prefix
prefix Options
opts [Citation]
cits =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
p [Inline
texcit]
where
texcit :: Inline
texcit =
Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"tex") forall a b. (a -> b) -> a -> b
$
if Options -> Bool
cref Options
opts then
Text
cref'forall a. Semigroup a => a -> a -> a
<>Text
"{"forall a. Semigroup a => a -> a -> a
<>Prefix -> Text -> Text -> Text -> [Citation] -> Text
listLabels Prefix
prefix Text
"" Text
"," Text
"" [Citation]
citsforall a. Semigroup a => a -> a -> a
<>Text
"}"
else
Prefix -> Text -> Text -> Text -> [Citation] -> Text
listLabels Prefix
prefix Text
"\\ref{" Text
", " Text
"}" [Citation]
cits
suppressAuthor :: Bool
suppressAuthor = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
==CitationMode
SuppressAuthor) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> CitationMode
citationMode) [Citation]
cits
noPrefix :: Bool
noPrefix = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> [Inline]
citationPrefix) [Citation]
cits
p :: [Inline] -> [Inline]
p | Options -> Bool
cref Options
opts = forall a. a -> a
id
| Bool
suppressAuthor
= forall a. a -> a
id
| Bool
noPrefix
= Options -> Prefix -> Bool -> Int -> [Inline] -> [Inline]
getRefPrefix Options
opts Prefix
prefix Bool
cap (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Citation]
cits forall a. Num a => a -> a -> a
- Int
1)
| Bool
otherwise = ((Citation -> [Inline]
citationPrefix (forall a. [a] -> a
head [Citation]
cits) forall a. Semigroup a => a -> a -> a
<> [Inline
Space]) forall a. Semigroup a => a -> a -> a
<>)
cap :: Bool
cap = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
isFirstUpper forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
getLabelPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ [Citation]
cits
cref' :: Text
cref' | Bool
suppressAuthor = Text
"\\labelcref"
| Bool
cap = Text
"\\Cref"
| Bool
otherwise = Text
"\\cref"
listLabels :: Prefix -> T.Text -> T.Text -> T.Text -> [Citation] -> T.Text
listLabels :: Prefix -> Text -> Text -> Text -> [Citation] -> Text
listLabels Prefix
prefix Text
p Text
sep Text
s =
Text -> [Text] -> Text
T.intercalate Text
sep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map ((Text
p forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Semigroup a => a -> a -> a
<> Text
s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
mkLaTeXLabel' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Prefix -> Text
pfxMapR Prefix
prefix forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
getLabelWithoutPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId)
getLabelWithoutPrefix :: T.Text -> T.Text
getLabelWithoutPrefix :: Text -> Text
getLabelWithoutPrefix = Int -> Text -> Text
T.drop Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropWhile (forall a. Eq a => a -> a -> Bool
/=Char
':')
getLabelPrefix :: T.Text -> Maybe T.Text
getLabelPrefix :: Text -> Maybe Text
getLabelPrefix Text
lab
| Just Prefix
pfx <- Text -> Maybe Prefix
pfxMap (Text -> Text
uncapitalizeFirst Text
p)
, Prefix
pfx forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Prefix]
prefixes = forall a. a -> Maybe a
Just Text
p
| Bool
otherwise = forall a. Maybe a
Nothing
where p :: Text
p = forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Char -> Text
T.snoc Char
':' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.takeWhile (forall a. Eq a => a -> a -> Bool
/=Char
':') forall a b. (a -> b) -> a -> b
$ Text
lab
replaceRefsOther :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther Prefix
prefix Options
opts [Citation]
cits = forall a. Many a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (f :: * -> *).
(Eq a, Monoid a, Foldable f) =>
a -> f a -> a
intercalate' (Text -> Inlines
text Text
", ") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Many a
fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther' Prefix
prefix Options
opts) (forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy Citation -> Citation -> Bool
citationGroupPred [Citation]
cits)
citationGroupPred :: Citation -> Citation -> Bool
citationGroupPred :: Citation -> Citation -> Bool
citationGroupPred = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) Citation -> [Inline]
citationPrefix Citation -> CitationMode
citationMode
replaceRefsOther' :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther' :: Prefix -> Options -> [Citation] -> WS [Inline]
replaceRefsOther' Prefix
prefix Options
opts [Citation]
cits = do
[RefData]
indices <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Prefix -> Options -> Citation -> WS RefData
getRefIndex Prefix
prefix Options
opts) [Citation]
cits
let
cap :: Bool
cap = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
isFirstUpper forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
getLabelPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ [Citation]
cits
writePrefix :: [Inline] -> [Inline]
writePrefix | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
==CitationMode
SuppressAuthor) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> CitationMode
citationMode) [Citation]
cits
= forall a. a -> a
id
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> [Inline]
citationPrefix) [Citation]
cits
= ([Inline] -> [Inline]) -> [Inline] -> [Inline]
cmap forall a b. (a -> b) -> a -> b
$ Options -> Prefix -> Bool -> Int -> [Inline] -> [Inline]
getRefPrefix Options
opts Prefix
prefix Bool
cap (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Citation]
cits forall a. Num a => a -> a -> a
- Int
1)
| Bool
otherwise
= ([Inline] -> [Inline]) -> [Inline] -> [Inline]
cmap forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((forall a. [a] -> Many a
fromList (Citation -> [Inline]
citationPrefix (forall a. [a] -> a
head [Citation]
cits)) forall a. Semigroup a => a -> a -> a
<> Inlines
space) forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Many a
fromList
cmap :: ([Inline] -> [Inline]) -> [Inline] -> [Inline]
cmap [Inline] -> [Inline]
f [Link Attr
attr [Inline]
t Target
w]
| Options -> Bool
nameInLink Options
opts = [Attr -> [Inline] -> Target -> Inline
Link Attr
attr ([Inline] -> [Inline]
f [Inline]
t) Target
w]
cmap [Inline] -> [Inline]
f [Inline]
x = [Inline] -> [Inline]
f [Inline]
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
writePrefix (Options -> [RefData] -> [Inline]
makeIndices Options
opts [RefData]
indices)
data RefData = RefData { RefData -> Text
rdLabel :: T.Text
, RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx :: Maybe Index
, RefData -> Maybe (Seq (Int, Maybe Text))
rdSubfig :: Maybe Index
, RefData -> [Inline]
rdSuffix :: [Inline]
, RefData -> Maybe [Inline]
rdTitle :: Maybe [Inline]
, RefData -> Text
rdPfx :: T.Text
} deriving (RefData -> RefData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefData -> RefData -> Bool
$c/= :: RefData -> RefData -> Bool
== :: RefData -> RefData -> Bool
$c== :: RefData -> RefData -> Bool
Eq)
instance Ord RefData where
<= :: RefData -> RefData -> Bool
(<=) = forall a. Ord a => a -> a -> Bool
(<=) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx
getRefIndex :: Prefix -> Options -> Citation -> WS RefData
getRefIndex :: Prefix -> Options -> Citation -> WS RefData
getRefIndex Prefix
prefix Options
_opts Citation{citationId :: Citation -> Text
citationId=Text
cid,citationSuffix :: Citation -> [Inline]
citationSuffix=[Inline]
suf}
= do
Maybe RefRec
ref <- forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
lab forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (RefMap -> Const RefMap RefMap)
-> References -> Const RefMap References
prop
let sub :: Maybe (Maybe (Seq (Int, Maybe Text)))
sub = RefRec -> Maybe (Seq (Int, Maybe Text))
refSubfigure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RefRec
ref
idx :: Maybe (Seq (Int, Maybe Text))
idx = RefRec -> Seq (Int, Maybe Text)
refIndex forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RefRec
ref
tit :: Maybe [Inline]
tit = RefRec -> [Inline]
refTitle forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RefRec
ref
forall (m :: * -> *) a. Monad m => a -> m a
return RefData
{ rdLabel :: Text
rdLabel = Text
lab
, rdIdx :: Maybe (Seq (Int, Maybe Text))
rdIdx = Maybe (Seq (Int, Maybe Text))
idx
, rdSubfig :: Maybe (Seq (Int, Maybe Text))
rdSubfig = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe (Seq (Int, Maybe Text)))
sub
, rdSuffix :: [Inline]
rdSuffix = [Inline]
suf
, rdTitle :: Maybe [Inline]
rdTitle = Maybe [Inline]
tit
, rdPfx :: Text
rdPfx = Prefix -> Text
pfxMapR Prefix
prefix
}
where
prop :: (RefMap -> Const RefMap RefMap)
-> References -> Const RefMap References
prop = Prefix -> Lens' References RefMap
refsAt Prefix
prefix
lab :: Text
lab = Prefix -> Text
pfxMapR Prefix
prefix forall a. Semigroup a => a -> a -> a
<> Text -> Text
getLabelWithoutPrefix Text
cid
data RefItem = RefRange RefData RefData | RefSingle RefData
makeIndices :: Options -> [RefData] -> [Inline]
makeIndices :: Options -> [RefData] -> [Inline]
makeIndices Options
o [RefData]
s = [RefItem] -> [Inline]
format forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [RefData] -> [RefItem]
f forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Bool) -> [a] -> [[a]]
HT.groupBy RefData -> RefData -> Bool
g forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a]
sort forall a b. (a -> b) -> a -> b
$ forall a. Eq a => [a] -> [a]
nub [RefData]
s
where
g :: RefData -> RefData -> Bool
g :: RefData -> RefData -> Bool
g RefData
a RefData
b = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. RefData -> [Inline]
rdSuffix) [RefData
a, RefData
b] Bool -> Bool -> Bool
&& (
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. RefData -> Maybe (Seq (Int, Maybe Text))
rdSubfig) [RefData
a, RefData
b] Bool -> Bool -> Bool
&&
forall a. a -> Maybe a
Just Bool
True forall a. Eq a => a -> a -> Bool
== (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Seq (Int, Maybe Text) -> Seq (Int, Maybe Text) -> Bool
follows forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx) RefData
b RefData
a Bool -> Bool -> Bool
||
RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx RefData
a forall a. Eq a => a -> a -> Bool
== RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx RefData
b Bool -> Bool -> Bool
&&
forall a. a -> Maybe a
Just Bool
True forall a. Eq a => a -> a -> Bool
== (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Seq (Int, Maybe Text) -> Seq (Int, Maybe Text) -> Bool
follows forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` RefData -> Maybe (Seq (Int, Maybe Text))
rdSubfig) RefData
b RefData
a
)
follows :: Index -> Index -> Bool
follows :: Seq (Int, Maybe Text) -> Seq (Int, Maybe Text) -> Bool
follows Seq (Int, Maybe Text)
a Seq (Int, Maybe Text)
b
| Seq (Int, Maybe Text)
ai :> (Int, Maybe Text)
al <- forall a. Seq a -> ViewR a
S.viewr Seq (Int, Maybe Text)
a
, Seq (Int, Maybe Text)
bi :> (Int, Maybe Text)
bl <- forall a. Seq a -> ViewR a
S.viewr Seq (Int, Maybe Text)
b
= Seq (Int, Maybe Text)
ai forall a. Eq a => a -> a -> Bool
== Seq (Int, Maybe Text)
bi Bool -> Bool -> Bool
&& forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
A.first forall a. Enum a => a -> a
succ (Int, Maybe Text)
bl forall a. Eq a => a -> a -> Bool
== (Int, Maybe Text)
al
| Bool
otherwise = Bool
False
f :: [RefData] -> [RefItem]
f :: [RefData] -> [RefItem]
f [] = []
f [RefData
w] = [RefData -> RefItem
RefSingle RefData
w]
f [RefData
w1,RefData
w2] = [RefData -> RefItem
RefSingle RefData
w1, RefData -> RefItem
RefSingle RefData
w2]
f (RefData
x:[RefData]
xs) = [RefData -> RefData -> RefItem
RefRange RefData
x (forall a. [a] -> a
last [RefData]
xs)]
format :: [RefItem] -> [Inline]
format :: [RefItem] -> [Inline]
format [] = []
format [RefItem
x] = forall a. Many a -> [a]
toList forall a b. (a -> b) -> a -> b
$ RefItem -> Inlines
show'' RefItem
x
format [RefItem
x, RefItem
y] = forall a. Many a -> [a]
toList forall a b. (a -> b) -> a -> b
$ RefItem -> Inlines
show'' RefItem
x forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList (Options -> [Inline]
pairDelim Options
o) forall a. Semigroup a => a -> a -> a
<> RefItem -> Inlines
show'' RefItem
y
format [RefItem]
xs = forall a. Many a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a (f :: * -> *).
(Eq a, Monoid a, Foldable f) =>
a -> f a -> a
intercalate' (forall a. [a] -> Many a
fromList forall a b. (a -> b) -> a -> b
$ Options -> [Inline]
refDelim Options
o) [Inlines]
init' forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList (Options -> [Inline]
lastDelim Options
o) forall a. Semigroup a => a -> a -> a
<> Inlines
last'
where initlast :: [a] -> ([a], a)
initlast [] = forall a. HasCallStack => [Char] -> a
error [Char]
"emtpy list in initlast"
initlast [a
y] = ([], a
y)
initlast (a
y:[a]
ys) = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (a
yforall a. a -> [a] -> [a]
:) forall a b. (a -> b) -> a -> b
$ [a] -> ([a], a)
initlast [a]
ys
([Inlines]
init', Inlines
last') = forall {a}. [a] -> ([a], a)
initlast forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map RefItem -> Inlines
show'' [RefItem]
xs
show'' :: RefItem -> Inlines
show'' :: RefItem -> Inlines
show'' (RefSingle RefData
x) = RefData -> Inlines
show' RefData
x
show'' (RefRange RefData
x RefData
y) = RefData -> Inlines
show' RefData
x forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList (Options -> [Inline]
rangeDelim Options
o) forall a. Semigroup a => a -> a -> a
<> RefData -> Inlines
show' RefData
y
show' :: RefData -> Inlines
show' :: RefData -> Inlines
show' RefData{rdLabel :: RefData -> Text
rdLabel=Text
l, rdIdx :: RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx=Just Seq (Int, Maybe Text)
i, rdSubfig :: RefData -> Maybe (Seq (Int, Maybe Text))
rdSubfig = Maybe (Seq (Int, Maybe Text))
sub, rdSuffix :: RefData -> [Inline]
rdSuffix = [Inline]
suf, rdTitle :: RefData -> Maybe [Inline]
rdTitle=Maybe [Inline]
tit, rdPfx :: RefData -> Text
rdPfx=Text
pfx}
| Options -> Bool
linkReferences Options
o = Text -> Text -> Inlines -> Inlines
link (Char
'#' Char -> Text -> Text
`T.cons` Text
l) Text
"" (forall a. [a] -> Many a
fromList [Inline]
txt)
| Bool
otherwise = forall a. [a] -> Many a
fromList [Inline]
txt
where
txt :: [Inline]
txt
| Just Seq (Int, Maybe Text)
sub' <- Maybe (Seq (Int, Maybe Text))
sub
= let vars :: Map Text [Inline]
vars = forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList
[ (Text
"i", [Inline] -> Seq (Int, Maybe Text) -> [Inline]
chapPrefix (Options -> [Inline]
chapDelim Options
o) Seq (Int, Maybe Text)
i)
, (Text
"s", [Inline] -> Seq (Int, Maybe Text) -> [Inline]
chapPrefix (Options -> [Inline]
chapDelim Options
o) Seq (Int, Maybe Text)
sub')
, (Text
"suf", [Inline]
suf)
, (Text
"t", forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty Maybe [Inline]
tit)
]
in forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' Map Text [Inline]
vars forall a b. (a -> b) -> a -> b
$ Options -> Template
subfigureRefIndexTemplate Options
o
| Bool
otherwise
= let vars :: Map Text [Inline]
vars = forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList
[ (Text
"i", [Inline] -> Seq (Int, Maybe Text) -> [Inline]
chapPrefix (Options -> [Inline]
chapDelim Options
o) Seq (Int, Maybe Text)
i)
, (Text
"suf", [Inline]
suf)
, (Text
"t", forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty Maybe [Inline]
tit)
]
in forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' Map Text [Inline]
vars forall a b. (a -> b) -> a -> b
$ Options -> Text -> Template
refIndexTemplate Options
o (Int -> Text -> Text
T.dropEnd Int
1 Text
pfx)
show' RefData{rdLabel :: RefData -> Text
rdLabel=Text
l, rdIdx :: RefData -> Maybe (Seq (Int, Maybe Text))
rdIdx=Maybe (Seq (Int, Maybe Text))
Nothing, rdSuffix :: RefData -> [Inline]
rdSuffix = [Inline]
suf} =
forall a. [Char] -> a -> a
trace (Text -> [Char]
T.unpack forall a b. (a -> b) -> a -> b
$ Text
"Undefined cross-reference: " forall a. Semigroup a => a -> a -> a
<> Text
l)
(Inlines -> Inlines
strong (Text -> Inlines
text forall a b. (a -> b) -> a -> b
$ Text
"¿" forall a. Semigroup a => a -> a -> a
<> Text
l forall a. Semigroup a => a -> a -> a
<> Text
"?") forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> Many a
fromList [Inline]
suf)