{- |
   Module      : Text.Pandoc.Writers.LaTeX.Caption
   Copyright   : Copyright (C) 2006-2023 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Write figure or table captions as LaTeX.
-}
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) )


-- | Produces the components of a LaTeX 'caption' command. Returns a triple
-- containing the caption text, the short caption for the list of
-- figures/tables, and the footnote definitions.
getCaption :: PandocMonad m
           => ([Inline] -> LW m (Doc Text)) -- ^ inlines converter
           -> Bool                          -- ^ whether to extract notes
           -> 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 <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stExternalNotes
  (WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stExternalNotes = externalNotes, stNotes = [] }
  Doc Text
capt <- [Inline] -> LW m (Doc Text)
inlineListToLaTeX [Inline]
long'
  Doc Text
footnotes <- if Bool
externalNotes
                  then [Doc Text] -> Doc Text
notesToLaTeX ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> LW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterState -> [Doc Text]) -> StateT WriterState m [Doc Text]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [Doc Text]
stNotes
                  else Doc Text -> LW m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
  (WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stExternalNotes = oldExternalNotes, stNotes = [] }
  -- We can't have footnotes in the list of figures/tables, so remove them:
  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 (Any -> Bool) -> ([Inline] -> Any) -> [Inline] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Any) -> [Inline] -> Any
forall c. Monoid c => (Inline -> c) -> [Inline] -> 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 = (Doc Text -> Doc Text) -> LW m (Doc Text) -> LW m (Doc Text)
forall a b.
(a -> b) -> StateT WriterState m a -> StateT WriterState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets (LW m (Doc Text) -> LW m (Doc Text))
-> ([Inline] -> LW m (Doc Text)) -> [Inline] -> LW m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> LW m (Doc Text)
inlineListToLaTeX ([Inline] -> LW m (Doc Text))
-> ([Inline] -> [Inline]) -> [Inline] -> LW m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> [Inline] -> [Inline]
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 Doc Text -> LW m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
                  Just [Inline]
short -> [Inline] -> LW m (Doc Text)
toShortCapt [Inline]
short
  (Doc Text, Doc Text, Doc Text)
-> LW m (Doc Text, Doc Text, Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
capt, Doc Text
captForLof, Doc Text
footnotes)