{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Writers.LaTeX.Notes
   Copyright   : Copyright (C) 2006-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

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

Output tables as LaTeX.
-}
module Text.Pandoc.Writers.LaTeX.Notes
  ( notesToLaTeX
  ) where

import Data.List (intersperse)
import Text.DocLayout ( Doc, braces, empty, text, vcat, ($$))
import Data.Text (Text)

notesToLaTeX :: [Doc Text] -> Doc Text
notesToLaTeX :: [Doc Text] -> Doc Text
notesToLaTeX = \case
  [] -> Doc Text
forall a. Doc a
empty
  [Doc Text]
ns -> (case [Doc Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Doc Text]
ns of
            Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 -> Doc Text
"\\addtocounter" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>
                         Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
"footnote" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>
                         Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (String -> Doc Text
forall a. HasChars a => String -> Doc a
text (String -> Doc Text) -> String -> Doc Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
              | Bool
otherwise -> Doc Text
forall a. Doc a
empty)
        Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
        [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat (Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse
               (Doc Text
"\\addtocounter" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
"footnote" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
"1")
               ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> [a] -> [b]
map (\Doc Text
x -> Doc Text
"\\footnotetext" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
x)
               ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> [Doc Text]
forall a. [a] -> [a]
reverse [Doc Text]
ns)