{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.LaTeX.Table
( tableToLaTeX
) where
import Control.Monad.State.Strict ( gets, modify )
import Control.Monad (when)
import Data.List (intersperse)
import qualified Data.List.NonEmpty as NonEmpty
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.DocLayout
( Doc, braces, cr, empty, hcat, hsep, isEmpty, literal, nest
, text, vcat, ($$) )
import Text.Pandoc.Shared (splitBy, tshow)
import Text.Pandoc.Walk (walk, query)
import Data.Monoid (Any(..))
import Text.Pandoc.Writers.LaTeX.Caption (getCaption)
import Text.Pandoc.Writers.LaTeX.Notes (notesToLaTeX)
import Text.Pandoc.Writers.LaTeX.Types
( LW, WriterState (stBeamer, stExternalNotes, stInMinipage, stMultiRow
, stNotes, stTable) )
import Text.Pandoc.Writers.LaTeX.Util (labelFor)
import Text.Printf (printf)
import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
tableToLaTeX :: PandocMonad m
=> ([Inline] -> LW m (Doc Text))
-> ([Block] -> LW m (Doc Text))
-> Ann.Table
-> LW m (Doc Text)
tableToLaTeX :: forall (m :: * -> *).
PandocMonad m =>
([Inline] -> LW m (Doc Text))
-> ([Block] -> LW m (Doc Text)) -> Table -> LW m (Doc Text)
tableToLaTeX [Inline] -> LW m (Doc Text)
inlnsToLaTeX [Block] -> LW m (Doc Text)
blksToLaTeX Table
tbl = do
let (Ann.Table (Text
ident, [Text]
_, [(Text, Text)]
_) Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbodies TableFoot
tfoot) = Table
tbl
CaptionDocs Doc Text
capt Doc Text
captNotes <- forall (m :: * -> *).
PandocMonad m =>
([Inline] -> LW m (Doc Text))
-> Caption -> Text -> LW m CaptionDocs
captionToLaTeX [Inline] -> LW m (Doc Text)
inlnsToLaTeX Caption
caption Text
ident
let isSimpleTable :: Bool
isSimpleTable = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Cell -> Bool
isSimpleCell) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ TableHead -> [[Cell]]
headRows TableHead
thead
, forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TableBody -> [[Cell]]
bodyRows [TableBody]
tbodies
, TableFoot -> [[Cell]]
footRows TableFoot
tfoot
]
let removeNote :: Inline -> Inline
removeNote (Note [Block]
_) = (Text, [Text], [(Text, Text)]) -> [Inline] -> Inline
Span (Text
"", [], []) []
removeNote Inline
x = Inline
x
let colCount :: ColumnCount
colCount = Int -> ColumnCount
ColumnCount forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
specs
Doc Text
head' <- do
let mkHead :: TableHead -> LW m (Doc Text)
mkHead = forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> TableHead -> LW m (Doc Text)
headToLaTeX [Block] -> LW m (Doc Text)
blksToLaTeX Bool
isSimpleTable ColumnCount
colCount
case (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall a. Doc a -> Bool
isEmpty Doc Text
capt, Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ TableHead -> Bool
isEmptyHead TableHead
thead) of
(Bool
False, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
"\\toprule\\noalign{}"
(Bool
False, Bool
True) -> TableHead -> LW m (Doc Text)
mkHead TableHead
thead
(Bool
True, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
capt forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\toprule\\noalign{}" forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\endfirsthead")
(Bool
True, Bool
True) -> do
Doc Text
firsthead <- TableHead -> LW m (Doc Text)
mkHead TableHead
thead
Doc Text
repeated <- TableHead -> LW m (Doc Text)
mkHead (forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
removeNote TableHead
thead)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Doc Text
capt forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
firsthead forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\endfirsthead" forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
repeated
[Doc Text]
rows' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> [Cell] -> LW m (Doc Text)
rowToLaTeX [Block] -> LW m (Doc Text)
blksToLaTeX Bool
isSimpleTable ColumnCount
colCount CellType
BodyCell) forall a b. (a -> b) -> a -> b
$
forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map TableBody -> [[Cell]]
bodyRows [TableBody]
tbodies)
Doc Text
foot' <- if TableFoot -> Bool
isEmptyFoot TableFoot
tfoot
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Doc a
empty
else do
[Doc Text]
lastfoot <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM
(forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> [Cell] -> LW m (Doc Text)
rowToLaTeX [Block] -> LW m (Doc Text)
blksToLaTeX Bool
isSimpleTable ColumnCount
colCount CellType
BodyCell) forall a b. (a -> b) -> a -> b
$
TableFoot -> [[Cell]]
footRows TableFoot
tfoot
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Doc Text
"\\midrule\\noalign{}" forall a. Doc a -> Doc a -> Doc a
$$ forall a. [Doc a] -> Doc a
vcat [Doc Text]
lastfoot
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stTable :: Bool
stTable = Bool
True }
Doc Text
notes <- [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
Bool
beamer <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stBeamer
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\begin{longtable}[]" forall a. Semigroup a => a -> a -> a
<>
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text
"@{}" forall a. Semigroup a => a -> a -> a
<> Bool -> Table -> Doc Text
colDescriptors Bool
isSimpleTable Table
tbl forall a. Semigroup a => a -> a -> a
<> Doc Text
"@{}")
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
head'
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\endhead"
forall a. Doc a -> Doc a -> Doc a
$$ forall a. [Doc a] -> Doc a
vcat
(if Bool
beamer
then [ forall a. [Doc a] -> Doc a
vcat [Doc Text]
rows'
, Doc Text
foot'
, Doc Text
"\\bottomrule\\noalign{}"
]
else [ Doc Text
foot'
, Doc Text
"\\bottomrule\\noalign{}"
, Doc Text
"\\endlastfoot"
, forall a. [Doc a] -> Doc a
vcat [Doc Text]
rows'
])
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\end{longtable}"
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
captNotes
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
notes
isSimpleCell :: Ann.Cell -> Bool
isSimpleCell :: Cell -> Bool
isSimpleCell (Ann.Cell NonEmpty ColSpec
_ ColNumber
_ (Cell (Text, [Text], [(Text, Text)])
_attr Alignment
_align RowSpan
_rowspan ColSpan
_colspan [Block]
blocks)) =
case [Block]
blocks of
[Para [Inline]
_] -> Bool
True
[Plain [Inline]
_] -> Bool
True
[] -> Bool
True
[Block]
_ -> Bool
False
newtype ColumnCount = ColumnCount Int
colDescriptors :: Bool -> Ann.Table -> Doc Text
colDescriptors :: Bool -> Table -> Doc Text
colDescriptors Bool
isSimpleTable
(Ann.Table (Text, [Text], [(Text, Text)])
_attr Caption
_caption [ColSpec]
specs TableHead
_thead [TableBody]
_tbodies TableFoot
_tfoot) =
let ([Alignment]
aligns, [ColWidth]
widths) = forall a b. [(a, b)] -> ([a], [b])
unzip [ColSpec]
specs
defaultWidthsOnly :: Bool
defaultWidthsOnly = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a. Eq a => a -> a -> Bool
== ColWidth
ColWidthDefault) [ColWidth]
widths
relativeWidths :: [Double]
relativeWidths = if Bool
defaultWidthsOnly
then forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
specs)
(Double
1 forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
specs))
else forall a b. (a -> b) -> [a] -> [b]
map ColWidth -> Double
toRelWidth [ColWidth]
widths
in if Bool
defaultWidthsOnly Bool -> Bool -> Bool
&& Bool
isSimpleTable
then forall a. [Doc a] -> Doc a
hcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. HasChars a => a -> Doc a
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Alignment -> Text
colAlign) [Alignment]
aligns
else (forall a. Doc a
cr forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Doc a] -> Doc a
vcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. HasChars a => a -> Doc a
literal forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int -> Alignment -> Double -> Text
toColDescriptor (forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
specs))
[Alignment]
aligns
[Double]
relativeWidths
where
toColDescriptor :: Int -> Alignment -> Double -> Text
toColDescriptor :: Int -> Alignment -> Double -> Text
toColDescriptor Int
numcols Alignment
align Double
width =
String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall r. PrintfType r => String -> r
printf
String
">{%s\\arraybackslash}p{(\\columnwidth - %d\\tabcolsep) * \\real{%0.4f}}"
(Text -> String
T.unpack (Alignment -> Text
alignCommand Alignment
align))
((Int
numcols forall a. Num a => a -> a -> a
- Int
1) forall a. Num a => a -> a -> a
* Int
2)
Double
width
toRelWidth :: ColWidth -> Double
toRelWidth ColWidth
ColWidthDefault = Double
0
toRelWidth (ColWidth Double
w) = Double
w
alignCommand :: Alignment -> Text
alignCommand :: Alignment -> Text
alignCommand = \case
Alignment
AlignLeft -> Text
"\\raggedright"
Alignment
AlignRight -> Text
"\\raggedleft"
Alignment
AlignCenter -> Text
"\\centering"
Alignment
AlignDefault -> Text
"\\raggedright"
colAlign :: Alignment -> Text
colAlign :: Alignment -> Text
colAlign = \case
Alignment
AlignLeft -> Text
"l"
Alignment
AlignRight -> Text
"r"
Alignment
AlignCenter -> Text
"c"
Alignment
AlignDefault -> Text
"l"
data CaptionDocs =
CaptionDocs
{ CaptionDocs -> Doc Text
captionCommand :: Doc Text
, CaptionDocs -> Doc Text
captionNotes :: Doc Text
}
captionToLaTeX :: PandocMonad m
=> ([Inline] -> LW m (Doc Text))
-> Caption
-> Text
-> LW m CaptionDocs
captionToLaTeX :: forall (m :: * -> *).
PandocMonad m =>
([Inline] -> LW m (Doc Text))
-> Caption -> Text -> LW m CaptionDocs
captionToLaTeX [Inline] -> LW m (Doc Text)
inlnsToLaTeX Caption
caption Text
ident = do
(Doc Text
captionText, Doc Text
captForLot, Doc Text
captNotes) <- 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)
inlnsToLaTeX Bool
False Caption
caption
Doc Text
label <- forall (m :: * -> *). PandocMonad m => Text -> LW m (Doc Text)
labelFor Text
ident
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ CaptionDocs
{ captionNotes :: Doc Text
captionNotes = Doc Text
captNotes
, captionCommand :: Doc Text
captionCommand = if forall a. Doc a -> Bool
isEmpty Doc Text
captionText Bool -> Bool -> Bool
&& forall a. Doc a -> Bool
isEmpty Doc Text
label
then forall a. Doc a
empty
else Doc Text
"\\caption" forall a. Semigroup a => a -> a -> a
<> Doc Text
captForLot forall a. Semigroup a => a -> a -> a
<>
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
captionText
forall a. Semigroup a => a -> a -> a
<> Doc Text
label
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\tabularnewline"
}
type BlocksWriter m = [Block] -> LW m (Doc Text)
headToLaTeX :: PandocMonad m
=> BlocksWriter m
-> Bool
-> ColumnCount
-> Ann.TableHead
-> LW m (Doc Text)
headToLaTeX :: forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> TableHead -> LW m (Doc Text)
headToLaTeX BlocksWriter m
blocksWriter Bool
isSimpleTable
ColumnCount
colCount (Ann.TableHead (Text, [Text], [(Text, Text)])
_attr [HeaderRow]
headerRows) = do
[Doc Text]
rowsContents <-
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> [Cell] -> LW m (Doc Text)
rowToLaTeX BlocksWriter m
blocksWriter Bool
isSimpleTable
ColumnCount
colCount CellType
HeaderCell forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderRow -> [Cell]
headerRowCells)
[HeaderRow]
headerRows
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
"\\toprule\\noalign{}" forall a. Doc a -> Doc a -> Doc a
$$ forall a. [Doc a] -> Doc a
vcat [Doc Text]
rowsContents forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\midrule\\noalign{}")
rowToLaTeX :: PandocMonad m
=> BlocksWriter m
-> Bool
-> ColumnCount
-> CellType
-> [Ann.Cell]
-> LW m (Doc Text)
rowToLaTeX :: forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> [Cell] -> LW m (Doc Text)
rowToLaTeX BlocksWriter m
blocksWriter Bool
isSimpleTable ColumnCount
colCount CellType
celltype [Cell]
row = do
[Doc Text]
cellsDocs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> Cell -> LW m (Doc Text)
cellToLaTeX BlocksWriter m
blocksWriter Bool
isSimpleTable
ColumnCount
colCount CellType
celltype) ([Cell] -> [Cell]
fillRow [Cell]
row)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [Doc a] -> Doc a
hsep (forall a. a -> [a] -> [a]
intersperse Doc Text
"&" [Doc Text]
cellsDocs) forall a. Semigroup a => a -> a -> a
<> Doc Text
" \\\\"
fillRow :: [Ann.Cell] -> [Ann.Cell]
fillRow :: [Cell] -> [Cell]
fillRow = Int -> [Cell] -> [Cell]
go Int
0
where
go :: Int -> [Cell] -> [Cell]
go Int
_ [] = []
go Int
n (acell :: Cell
acell@(Ann.Cell NonEmpty ColSpec
_spec (Ann.ColNumber Int
colnum) Cell
cell):[Cell]
cells) =
let (Cell (Text, [Text], [(Text, Text)])
_ Alignment
_ RowSpan
_ (ColSpan Int
colspan) [Block]
_) = Cell
cell
in forall a b. (a -> b) -> [a] -> [b]
map Int -> Cell
mkEmptyCell [Int
n .. Int
colnum forall a. Num a => a -> a -> a
- Int
1] forall a. [a] -> [a] -> [a]
++
Cell
acell forall a. a -> [a] -> [a]
: Int -> [Cell] -> [Cell]
go (Int
colnum forall a. Num a => a -> a -> a
+ Int
colspan) [Cell]
cells
mkEmptyCell :: Int -> Ann.Cell
mkEmptyCell :: Int -> Cell
mkEmptyCell Int
colnum =
NonEmpty ColSpec -> ColNumber -> Cell -> Cell
Ann.Cell ((Alignment
AlignDefault, ColWidth
ColWidthDefault)forall a. a -> [a] -> NonEmpty a
:|[])
(Int -> ColNumber
Ann.ColNumber Int
colnum)
Cell
B.emptyCell
isEmptyHead :: Ann.TableHead -> Bool
isEmptyHead :: TableHead -> Bool
isEmptyHead (Ann.TableHead (Text, [Text], [(Text, Text)])
_attr []) = Bool
True
isEmptyHead (Ann.TableHead (Text, [Text], [(Text, Text)])
_attr [HeaderRow]
rows) = 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
. HeaderRow -> [Cell]
headerRowCells) [HeaderRow]
rows
isEmptyFoot :: Ann.TableFoot -> Bool
(Ann.TableFoot (Text, [Text], [(Text, Text)])
_attr []) = Bool
True
isEmptyFoot (Ann.TableFoot (Text, [Text], [(Text, Text)])
_attr [HeaderRow]
rows) = 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
. HeaderRow -> [Cell]
headerRowCells) [HeaderRow]
rows
headerRowCells :: Ann.HeaderRow -> [Ann.Cell]
(Ann.HeaderRow (Text, [Text], [(Text, Text)])
_attr RowNumber
_rownum [Cell]
cells) = [Cell]
cells
bodyRowCells :: Ann.BodyRow -> [Ann.Cell]
bodyRowCells :: BodyRow -> [Cell]
bodyRowCells (Ann.BodyRow (Text, [Text], [(Text, Text)])
_attr RowNumber
_rownum [Cell]
rowhead [Cell]
cells) = [Cell]
rowhead forall a. Semigroup a => a -> a -> a
<> [Cell]
cells
bodyRows :: Ann.TableBody -> [[Ann.Cell]]
bodyRows :: TableBody -> [[Cell]]
bodyRows (Ann.TableBody (Text, [Text], [(Text, Text)])
_attr RowHeadColumns
_rowheads [HeaderRow]
headerRows [BodyRow]
rows) =
forall a b. (a -> b) -> [a] -> [b]
map HeaderRow -> [Cell]
headerRowCells [HeaderRow]
headerRows forall a. Semigroup a => a -> a -> a
<> forall a b. (a -> b) -> [a] -> [b]
map BodyRow -> [Cell]
bodyRowCells [BodyRow]
rows
headRows :: Ann.TableHead -> [[Ann.Cell]]
headRows :: TableHead -> [[Cell]]
headRows (Ann.TableHead (Text, [Text], [(Text, Text)])
_attr [HeaderRow]
rows) = forall a b. (a -> b) -> [a] -> [b]
map HeaderRow -> [Cell]
headerRowCells [HeaderRow]
rows
footRows :: Ann.TableFoot -> [[Ann.Cell]]
(Ann.TableFoot (Text, [Text], [(Text, Text)])
_attr [HeaderRow]
rows) = forall a b. (a -> b) -> [a] -> [b]
map HeaderRow -> [Cell]
headerRowCells [HeaderRow]
rows
fixLineBreaks :: Block -> Block
fixLineBreaks :: Block -> Block
fixLineBreaks = forall a b. Walkable a b => (a -> a) -> b -> b
walk [Inline] -> [Inline]
fixLineBreaks'
fixLineBreaks' :: [Inline] -> [Inline]
fixLineBreaks' :: [Inline] -> [Inline]
fixLineBreaks' [Inline]
ils = case forall a. (a -> Bool) -> [a] -> [[a]]
splitBy (forall a. Eq a => a -> a -> Bool
== Inline
LineBreak) [Inline]
ils of
[] -> []
[[Inline]
xs] -> [Inline]
xs
[[Inline]]
chunks -> Format -> Text -> Inline
RawInline Format
"tex" Text
"\\vtop{" forall a. a -> [a] -> [a]
:
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [Inline] -> [Inline]
tohbox [[Inline]]
chunks forall a. Semigroup a => a -> a -> a
<>
[Format -> Text -> Inline
RawInline Format
"tex" Text
"}"]
where tohbox :: [Inline] -> [Inline]
tohbox [Inline]
ys = Format -> Text -> Inline
RawInline Format
"tex" Text
"\\hbox{\\strut " forall a. a -> [a] -> [a]
: [Inline]
ys forall a. Semigroup a => a -> a -> a
<>
[Format -> Text -> Inline
RawInline Format
"tex" Text
"}"]
displayMathToInline :: Inline -> Inline
displayMathToInline :: Inline -> Inline
displayMathToInline (Math MathType
DisplayMath Text
x) = MathType -> Text -> Inline
Math MathType
InlineMath Text
x
displayMathToInline Inline
x = Inline
x
cellToLaTeX :: PandocMonad m
=> BlocksWriter m
-> Bool
-> ColumnCount
-> CellType
-> Ann.Cell
-> LW m (Doc Text)
cellToLaTeX :: forall (m :: * -> *).
PandocMonad m =>
BlocksWriter m
-> Bool -> ColumnCount -> CellType -> Cell -> LW m (Doc Text)
cellToLaTeX BlocksWriter m
blockListToLaTeX Bool
isSimpleTable ColumnCount
colCount CellType
celltype Cell
annotatedCell = do
let (Ann.Cell NonEmpty ColSpec
specs ColNumber
colnum Cell
cell) = Cell
annotatedCell
let colWidths :: NonEmpty ColWidth
colWidths = forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NonEmpty.map forall a b. (a, b) -> b
snd NonEmpty ColSpec
specs
let hasWidths :: Bool
hasWidths = forall a. NonEmpty a -> a
NonEmpty.head NonEmpty ColWidth
colWidths forall a. Eq a => a -> a -> Bool
/= ColWidth
ColWidthDefault
let specAlign :: Alignment
specAlign = forall a b. (a, b) -> a
fst (forall a. NonEmpty a -> a
NonEmpty.head NonEmpty ColSpec
specs)
let (Cell (Text, [Text], [(Text, Text)])
_attr Alignment
align' RowSpan
rowspan ColSpan
colspan [Block]
blocks) = Cell
cell
let align :: Alignment
align = case Alignment
align' of
Alignment
AlignDefault -> Alignment
specAlign
Alignment
_ -> Alignment
align'
Bool
beamer <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stBeamer
Bool
externalNotes <- 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
beamer }
let isPlainOrPara :: Block -> Bool
isPlainOrPara = \case
Para{} -> Bool
True
Plain{} -> Bool
True
Block
_ -> Bool
False
let hasLineBreak :: Inline -> Any
hasLineBreak Inline
LineBreak = Bool -> Any
Any Bool
True
hasLineBreak Inline
_ = Bool -> Any
Any Bool
False
let hasLineBreaks :: Bool
hasLineBreaks = Any -> Bool
getAny forall a b. (a -> b) -> a -> b
$ forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> Any
hasLineBreak [Block]
blocks
Doc Text
result <-
if Bool -> Bool
not Bool
hasWidths Bool -> Bool -> Bool
|| (CellType
celltype forall a. Eq a => a -> a -> Bool
/= CellType
HeaderCell
Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Block -> Bool
isPlainOrPara [Block]
blocks
Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
hasLineBreaks)
then
BlocksWriter m
blockListToLaTeX forall a b. (a -> b) -> a -> b
$ forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
fixLineBreaks forall a b. (a -> b) -> a -> b
$ forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
displayMathToInline [Block]
blocks
else do
Doc Text
cellContents <- forall (m :: * -> *) a. Monad m => LW m a -> LW m a
inMinipage forall a b. (a -> b) -> a -> b
$ BlocksWriter m
blockListToLaTeX [Block]
blocks
let valign :: Doc Text
valign = forall a. HasChars a => String -> Doc a
text forall a b. (a -> b) -> a -> b
$ case CellType
celltype of
CellType
HeaderCell -> String
"[b]"
CellType
BodyCell -> String
"[t]"
let halign :: Doc Text
halign = forall a. HasChars a => a -> Doc a
literal forall a b. (a -> b) -> a -> b
$ Alignment -> Text
alignCommand Alignment
align
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Doc Text
"\\begin{minipage}" forall a. Semigroup a => a -> a -> a
<> Doc Text
valign forall a. Semigroup a => a -> a -> a
<>
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
"\\linewidth" forall a. Semigroup a => a -> a -> a
<> Doc Text
halign forall a. Semigroup a => a -> a -> a
<> forall a. Doc a
cr forall a. Semigroup a => a -> a -> a
<>
Doc Text
cellContents forall a. Semigroup a => a -> a -> a
<>
(if Bool
hasLineBreaks then Doc Text
"\\strut" else forall a. Monoid a => a
mempty)
forall a. Semigroup a => a -> a -> a
<> forall a. Doc a
cr forall a. Semigroup a => a -> a -> a
<>
Doc Text
"\\end{minipage}"
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 }
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RowSpan
rowspan forall a. Eq a => a -> a -> Bool
/= Int -> RowSpan
RowSpan Int
1) forall a b. (a -> b) -> a -> b
$
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
st -> WriterState
st{ stMultiRow :: Bool
stMultiRow = Bool
True })
let inMultiColumn :: Doc Text -> Doc Text
inMultiColumn Doc Text
x = case ColSpan
colspan of
(ColSpan Int
1) -> Doc Text
x
(ColSpan Int
n) ->
let colDescr :: Text
colDescr = Bool
-> Alignment
-> NonEmpty ColWidth
-> ColumnCount
-> ColNumber
-> Text
multicolumnDescriptor Bool
isSimpleTable
Alignment
align
NonEmpty ColWidth
colWidths
ColumnCount
colCount
ColNumber
colnum
in Doc Text
"\\multicolumn"
forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces (forall a. HasChars a => a -> Doc a
literal (forall a. Show a => a -> Text
tshow Int
n))
forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces (forall a. HasChars a => a -> Doc a
literal Text
colDescr)
forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces (Doc Text
"%\n" forall a. Semigroup a => a -> a -> a
<> Doc Text
x)
let inMultiRow :: Doc Text -> Doc Text
inMultiRow Doc Text
x = case RowSpan
rowspan of
(RowSpan Int
1) -> Doc Text
x
(RowSpan Int
n) -> let nrows :: Doc Text
nrows = forall a. HasChars a => a -> Doc a
literal (forall a. Show a => a -> Text
tshow Int
n)
in Doc Text
"\\multirow" forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces Doc Text
nrows
forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces Doc Text
"*" forall a. Semigroup a => a -> a -> a
<> forall a. HasChars a => Doc a -> Doc a
braces Doc Text
x
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
inMultiColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
inMultiRow forall a b. (a -> b) -> a -> b
$ Doc Text
result
multicolumnDescriptor :: Bool
-> Alignment
-> NonEmpty ColWidth
-> ColumnCount
-> Ann.ColNumber
-> Text
multicolumnDescriptor :: Bool
-> Alignment
-> NonEmpty ColWidth
-> ColumnCount
-> ColNumber
-> Text
multicolumnDescriptor Bool
isSimpleTable
Alignment
align
NonEmpty ColWidth
colWidths
(ColumnCount Int
numcols)
(Ann.ColNumber Int
colnum) =
let toWidth :: ColWidth -> Double
toWidth = \case
ColWidth
ColWidthDefault -> (Double
1 forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
numcols)
ColWidth Double
x -> Double
x
colspan :: Int
colspan = forall (t :: * -> *) a. Foldable t => t a -> Int
length NonEmpty ColWidth
colWidths
width :: Double
width = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NonEmpty.map ColWidth -> Double
toWidth NonEmpty ColWidth
colWidths
skipColSep :: String
skipColSep = String
"@{}" :: String
in String -> Text
T.pack forall a b. (a -> b) -> a -> b
$
if Bool
isSimpleTable
then forall r. PrintfType r => String -> r
printf String
"%s%s%s"
(if Int
colnum forall a. Eq a => a -> a -> Bool
== Int
0 then String
skipColSep else String
"")
(Text -> String
T.unpack (Alignment -> Text
colAlign Alignment
align))
(if Int
colnum forall a. Num a => a -> a -> a
+ Int
colspan forall a. Ord a => a -> a -> Bool
>= Int
numcols then String
skipColSep else String
"")
else forall r. PrintfType r => String -> r
printf String
"%s>{%s\\arraybackslash}p{(\\columnwidth - %d\\tabcolsep) * \\real{%0.4f} + %d\\tabcolsep}%s"
(if Int
colnum forall a. Eq a => a -> a -> Bool
== Int
0 then String
skipColSep else String
"")
(Text -> String
T.unpack (Alignment -> Text
alignCommand Alignment
align))
(Int
2 forall a. Num a => a -> a -> a
* (Int
numcols forall a. Num a => a -> a -> a
- Int
1))
Double
width
(Int
2 forall a. Num a => a -> a -> a
* (Int
colspan forall a. Num a => a -> a -> a
- Int
1))
(if Int
colnum forall a. Num a => a -> a -> a
+ Int
colspan forall a. Ord a => a -> a -> Bool
>= Int
numcols then String
skipColSep else String
"")
inMinipage :: Monad m => LW m a -> LW m a
inMinipage :: forall (m :: * -> *) a. Monad m => LW m a -> LW m a
inMinipage LW m a
action = do
Bool
isInMinipage <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInMinipage
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stInMinipage :: Bool
stInMinipage = Bool
True }
a
result <- LW m a
action
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stInMinipage :: Bool
stInMinipage = Bool
isInMinipage }
forall (m :: * -> *) a. Monad m => a -> m a
return a
result
data CellType
=
| BodyCell
deriving CellType -> CellType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellType -> CellType -> Bool
$c/= :: CellType -> CellType -> Bool
== :: CellType -> CellType -> Bool
$c== :: CellType -> CellType -> Bool
Eq