{-# LANGUAGE Rank2Types, OverloadedStrings, FlexibleContexts #-}
module Text.Pandoc.CrossRef.References.Blocks.Util where
import Control.Monad.Reader.Class
import Control.Monad.State hiding (get, modify)
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Text as T
import Text.Pandoc.Definition
import Text.Pandoc.Shared (stringify)
import Text.Pandoc.Walk (walk)
import Control.Applicative
import Lens.Micro
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.Util
setLabel :: Options -> [Inline] -> [(T.Text, T.Text)] -> [(T.Text, T.Text)]
setLabel :: Options -> [Inline] -> [(Text, Text)] -> [(Text, Text)]
setLabel Options
opts [Inline]
idx
| Options -> Bool
setLabelAttribute Options
opts
= ((Text
"label", forall a. Walkable Inline a => a -> Text
stringify [Inline]
idx) forall a. a -> [a] -> [a]
:)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
/= Text
"label") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
| Bool
otherwise = forall a. a -> a
id
walkReplaceInlines :: [Inline] -> [Inline] -> Block -> Block
walkReplaceInlines :: [Inline] -> [Inline] -> Block -> Block
walkReplaceInlines [Inline]
newTitle [Inline]
title = forall a b. Walkable a b => (a -> a) -> b -> b
walk [Inline] -> [Inline]
replaceInlines
where
replaceInlines :: [Inline] -> [Inline]
replaceInlines [Inline]
xs
| [Inline]
xs forall a. Eq a => a -> a -> Bool
== [Inline]
title = [Inline]
newTitle
| Bool
otherwise = [Inline]
xs
replaceAttr :: Either T.Text T.Text -> Maybe T.Text -> [Inline] -> Lens References References RefMap RefMap -> WS [Inline]
replaceAttr :: Either Text Text
-> Maybe Text
-> [Inline]
-> Lens References References RefMap RefMap
-> WS [Inline]
replaceAttr Either Text Text
label Maybe Text
refLabel [Inline]
title Lens References References RefMap RefMap
prop
= do
Options
o <- forall r (m :: * -> *). MonadReader r m => m r
ask
[(Int, Maybe Text)]
chap <- forall a. Int -> [a] -> [a]
take (Options -> Int
chaptersDepth Options
o) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Lens' References [(Int, Maybe Text)]
curChap
RefMap
prop' <- forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Lens References References RefMap RefMap
prop
let i :: Int
i = Int
1forall a. Num a => a -> a -> a
+ (forall k a. Map k a -> Int
M.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter (\RefRec
x -> ([(Int, Maybe Text)]
chap forall a. Eq a => a -> a -> Bool
== forall a. [a] -> [a]
init (RefRec -> [(Int, Maybe Text)]
refIndex RefRec
x)) Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing (RefRec -> Maybe [(Int, Maybe Text)]
refSubfigure RefRec
x)) forall a b. (a -> b) -> a -> b
$ RefMap
prop')
index :: [(Int, Maybe Text)]
index = [(Int, Maybe Text)]
chap forall a. Semigroup a => a -> a -> a
<> [(Int
i, Maybe Text
refLabel forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Text -> Int -> Maybe Text
customLabel Options
o Text
ref Int
i)]
ref :: Text
ref = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id ((Char -> Bool) -> Text -> Text
T.takeWhile (forall a. Eq a => a -> a -> Bool
/=Char
':')) Either Text Text
label
label' :: Text
label' = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Char
':' forall a. a -> [a] -> [a]
: forall a. Show a => a -> String
show [(Int, Maybe Text)]
index)) forall a. a -> a
id Either Text Text
label
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall k a. Ord k => k -> Map k a -> Bool
M.member Text
label' RefMap
prop') forall a b. (a -> b) -> a -> b
$
forall a. HasCallStack => String -> a
error forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ Text
"Duplicate label: " forall a. Semigroup a => a -> a -> a
<> Text
label'
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
modifying Lens References References RefMap RefMap
prop forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
label' RefRec {
refIndex :: [(Int, Maybe Text)]
refIndex= [(Int, Maybe Text)]
index
, refTitle :: [Inline]
refTitle= [Inline]
title
, refSubfigure :: Maybe [(Int, Maybe Text)]
refSubfigure = forall a. Maybe a
Nothing
}
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Inline] -> [(Int, Maybe Text)] -> [Inline]
chapPrefix (Options -> [Inline]
chapDelim Options
o) [(Int, Maybe Text)]
index
mkCaption :: Options -> T.Text -> [Inline] -> Block
mkCaption :: Options -> Text -> [Inline] -> Block
mkCaption Options
opts Text
style
| Options -> Maybe Format
outFormat Options
opts forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just (Text -> Format
Format Text
"docx") = Attr -> [Block] -> Block
Div (Text
"", [], [(Text
"custom-style", Text
style)]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Block
Para
| Bool
otherwise = [Inline] -> Block
Para