module Text.Pandoc.Writers.LaTeX.Caption
( getCaption
) where
import Control.Monad.State.Strict
import Data.Monoid (Any(..))
import Data.Text (Text)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.DocLayout (Doc, brackets, empty)
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.Pandoc.Writers.LaTeX.Notes (notesToLaTeX)
import Text.Pandoc.Writers.LaTeX.Types
( LW, WriterState (stExternalNotes, stNotes) )
getCaption :: PandocMonad m
=> ([Inline] -> LW m (Doc Text))
-> Bool
-> Caption
-> LW m (Doc Text, Doc Text, Doc Text)
getCaption :: forall (m :: * -> *).
PandocMonad m =>
([Inline] -> LW m (Doc Text))
-> Bool -> Caption -> LW m (Doc Text, Doc Text, Doc Text)
getCaption [Inline] -> LW m (Doc Text)
inlineListToLaTeX Bool
externalNotes (Caption Maybe [Inline]
maybeShort [Block]
long) = do
let long' :: [Inline]
long' = [Block] -> [Inline]
blocksToInlines [Block]
long
Bool
oldExternalNotes <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stExternalNotes
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stExternalNotes :: Bool
stExternalNotes = Bool
externalNotes, stNotes :: [Doc Text]
stNotes = [] }
Doc Text
capt <- [Inline] -> LW m (Doc Text)
inlineListToLaTeX [Inline]
long'
Doc Text
footnotes <- if Bool
externalNotes
then [Doc Text] -> Doc Text
notesToLaTeX forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [Doc Text]
stNotes
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Doc a
empty
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stExternalNotes :: Bool
stExternalNotes = Bool
oldExternalNotes, stNotes :: [Doc Text]
stNotes = [] }
let getNote :: Inline -> Any
getNote (Note [Block]
_) = Bool -> Any
Any Bool
True
getNote Inline
_ = Bool -> Any
Any Bool
False
let hasNotes :: [Inline] -> Bool
hasNotes = Any -> Bool
getAny forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> Any
getNote
let toShortCapt :: [Inline] -> LW m (Doc Text)
toShortCapt = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. HasChars a => Doc a -> Doc a
brackets forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> LW m (Doc Text)
inlineListToLaTeX forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
deNote
Doc Text
captForLof <- case Maybe [Inline]
maybeShort of
Maybe [Inline]
Nothing -> if [Inline] -> Bool
hasNotes [Inline]
long'
then [Inline] -> LW m (Doc Text)
toShortCapt [Inline]
long'
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Doc a
empty
Just [Inline]
short -> [Inline] -> LW m (Doc Text)
toShortCapt [Inline]
short
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
capt, Doc Text
captForLof, Doc Text
footnotes)