{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns        #-}
{- |
   Module      : Text.Pandoc.Writers.ConTeXt
   Copyright   : Copyright (C) 2007-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

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

Conversion of 'Pandoc' format into ConTeXt.
-}
module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where
import Control.Monad.State.Strict
import Data.Char (ord, isDigit)
import Data.List (intersperse)
import Data.Maybe (mapMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Network.URI (unEscapeString)
import Text.Pandoc.BCP47
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.DocLayout
import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Walk (query)
import Text.Pandoc.Writers.Shared
import Text.Printf (printf)

data WriterState =
  WriterState { WriterState -> Int
stNextRef          :: Int  -- number of next URL reference
              , WriterState -> Int
stOrderedListLevel :: Int  -- level of ordered list
              , WriterState -> WriterOptions
stOptions          :: WriterOptions -- writer options
              , WriterState -> Bool
stHasCslRefs       :: Bool -- has CSL citations
              , WriterState -> Bool
stCslHangingIndent :: Bool -- CSL hanging indent
              }

data Tabl = Xtb | Ntb deriving (Int -> Tabl -> ShowS
[Tabl] -> ShowS
Tabl -> String
(Int -> Tabl -> ShowS)
-> (Tabl -> String) -> ([Tabl] -> ShowS) -> Show Tabl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tabl] -> ShowS
$cshowList :: [Tabl] -> ShowS
show :: Tabl -> String
$cshow :: Tabl -> String
showsPrec :: Int -> Tabl -> ShowS
$cshowsPrec :: Int -> Tabl -> ShowS
Show, Tabl -> Tabl -> Bool
(Tabl -> Tabl -> Bool) -> (Tabl -> Tabl -> Bool) -> Eq Tabl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tabl -> Tabl -> Bool
$c/= :: Tabl -> Tabl -> Bool
== :: Tabl -> Tabl -> Bool
$c== :: Tabl -> Tabl -> Bool
Eq)

orderedListStyles :: [Char]
orderedListStyles :: String
orderedListStyles = ShowS
forall a. [a] -> [a]
cycle String
"narg"

-- | Convert Pandoc to ConTeXt.
writeConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeConTeXt :: WriterOptions -> Pandoc -> m Text
writeConTeXt WriterOptions
options Pandoc
document =
  let defaultWriterState :: WriterState
defaultWriterState = WriterState :: Int -> Int -> WriterOptions -> Bool -> Bool -> WriterState
WriterState { stNextRef :: Int
stNextRef = Int
1
                                       , stOrderedListLevel :: Int
stOrderedListLevel = Int
0
                                       , stOptions :: WriterOptions
stOptions = WriterOptions
options
                                       , stHasCslRefs :: Bool
stHasCslRefs = Bool
False
                                       , stCslHangingIndent :: Bool
stCslHangingIndent = Bool
False
                                       }
  in StateT WriterState m Text -> WriterState -> m Text
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (WriterOptions -> Pandoc -> StateT WriterState m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> WM m Text
pandocToConTeXt WriterOptions
options Pandoc
document) WriterState
defaultWriterState

type WM = StateT WriterState

pandocToConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> WM m Text
pandocToConTeXt :: WriterOptions -> Pandoc -> WM m Text
pandocToConTeXt WriterOptions
options (Pandoc Meta
meta [Block]
blocks) = do
  let colwidth :: Maybe Int
colwidth = if WriterOptions -> WrapOption
writerWrapText WriterOptions
options WrapOption -> WrapOption -> Bool
forall a. Eq a => a -> a -> Bool
== WrapOption
WrapAuto
                    then Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Int
writerColumns WriterOptions
options
                    else Maybe Int
forall a. Maybe a
Nothing
  Context Text
metadata <- WriterOptions
-> ([Block] -> StateT WriterState m (Doc Text))
-> ([Inline] -> StateT WriterState m (Doc Text))
-> Meta
-> StateT WriterState m (Context Text)
forall (m :: * -> *) a.
(Monad m, TemplateTarget a) =>
WriterOptions
-> ([Block] -> m (Doc a))
-> ([Inline] -> m (Doc a))
-> Meta
-> m (Context a)
metaToContext WriterOptions
options
              [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt
              ((Doc Text -> Doc Text)
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp (StateT WriterState m (Doc Text)
 -> StateT WriterState m (Doc Text))
-> ([Inline] -> StateT WriterState m (Doc Text))
-> [Inline]
-> StateT WriterState m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt)
              Meta
meta
  Doc Text
main <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt ([Block] -> StateT WriterState m (Doc Text))
-> [Block] -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Int -> [Block] -> [Block]
makeSections Bool
False Maybe Int
forall a. Maybe a
Nothing [Block]
blocks
  let layoutFromMargins :: Doc Text
layoutFromMargins = [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse (Doc Text
"," :: Doc Text) ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$
                          ((Doc Text, Text) -> Maybe (Doc Text))
-> [(Doc Text, Text)] -> [Doc Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\(Doc Text
x,Text
y) ->
                                ((Doc Text
x Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"=") Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>) (Doc Text -> Doc Text) -> Maybe (Doc Text) -> Maybe (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Context Text -> Maybe (Doc Text)
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
y Context Text
metadata)
                              [(Doc Text
"leftmargin",Text
"margin-left")
                              ,(Doc Text
"rightmargin",Text
"margin-right")
                              ,(Doc Text
"top",Text
"margin-top")
                              ,(Doc Text
"bottom",Text
"margin-bottom")
                              ]
  Maybe Text
mblang <- Maybe Text -> WM m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
Maybe Text -> WM m (Maybe Text)
fromBCP47 (WriterOptions -> Meta -> Maybe Text
getLang WriterOptions
options Meta
meta)
  WriterState
st <- StateT WriterState m WriterState
forall s (m :: * -> *). MonadState s m => m s
get
  let context :: Context Text
context =   Text -> Bool -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"toc" (WriterOptions -> Bool
writerTableOfContents WriterOptions
options)
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"placelist"
                   ([Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat ([Doc Text] -> Doc Text)
-> ([Doc Text] -> [Doc Text]) -> [Doc Text] -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse (Doc Text
"," :: Doc Text) ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$
                     Int -> [Doc Text] -> [Doc Text]
forall a. Int -> [a] -> [a]
take (WriterOptions -> Int
writerTOCDepth WriterOptions
options Int -> Int -> Int
forall a. Num a => a -> a -> a
+
                           case WriterOptions -> TopLevelDivision
writerTopLevelDivision WriterOptions
options of
                             TopLevelDivision
TopLevelPart    -> Int
0
                             TopLevelDivision
TopLevelChapter -> Int
0
                             TopLevelDivision
_               -> Int
1)
                       [Doc Text
"chapter",Doc Text
"section",Doc Text
"subsection",Doc Text
"subsubsection",
                        Doc Text
"subsubsubsection",Doc Text
"subsubsubsubsection"])
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"body" Doc Text
main
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"layout" Doc Text
layoutFromMargins
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Bool -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"number-sections" (WriterOptions -> Bool
writerNumberSections WriterOptions
options)
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Bool -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"csl-refs" (WriterState -> Bool
stHasCslRefs WriterState
st)
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Bool -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"csl-hanging-indent" (WriterState -> Bool
stCslHangingIndent WriterState
st)
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ (Context Text -> Context Text)
-> (Text -> Context Text -> Context Text)
-> Maybe Text
-> Context Text
-> Context Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Context Text -> Context Text
forall a. a -> a
id (\Text
l ->
                     Text -> Doc Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"context-lang" (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
l :: Doc Text)) Maybe Text
mblang
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ (case Text -> String
T.unpack (Text -> String) -> (Doc Text -> Text) -> Doc Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing (Doc Text -> String) -> Maybe (Doc Text) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                      Text -> Context Text -> Maybe (Doc Text)
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"papersize" Context Text
metadata of
                        Just ((Char
'a':Char
d:String
ds) :: String)
                          | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit (Char
dChar -> ShowS
forall a. a -> [a] -> [a]
:String
ds) -> Text -> Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
resetField Text
"papersize"
                                                   (String -> Text
T.pack (Char
'A'Char -> ShowS
forall a. a -> [a] -> [a]
:Char
dChar -> ShowS
forall a. a -> [a] -> [a]
:String
ds))
                        Maybe String
_                     -> Context Text -> Context Text
forall a. a -> a
id)
                (Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ (case Text -> Text
T.toLower (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Meta -> Text
lookupMetaString Text
"pdfa" Meta
meta of
                        Text
"true" -> Text -> Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
resetField Text
"pdfa" (String -> Text
T.pack String
"1b:2005")
                        Text
_                     -> Context Text -> Context Text
forall a. a -> a
id) Context Text
metadata
  let context' :: Context Text
context' = Text -> Doc Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"context-dir" (Doc Text -> (Doc Text -> Doc Text) -> Maybe (Doc Text) -> Doc Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc Text
forall a. Monoid a => a
mempty Doc Text -> Doc Text
toContextDir
                                         (Maybe (Doc Text) -> Doc Text) -> Maybe (Doc Text) -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Context Text -> Maybe (Doc Text)
forall a b. FromContext a b => Text -> Context a -> Maybe b
getField Text
"dir" Context Text
context) Context Text
context
  Text -> WM m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> WM m Text) -> Text -> WM m Text
forall a b. (a -> b) -> a -> b
$ Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
colwidth (Doc Text -> Text) -> Doc Text -> Text
forall a b. (a -> b) -> a -> b
$
    case WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
options of
       Maybe (Template Text)
Nothing  -> Doc Text
main
       Just Template Text
tpl -> Template Text -> Context Text -> Doc Text
forall a b.
(TemplateTarget a, ToContext a b) =>
Template a -> b -> Doc a
renderTemplate Template Text
tpl Context Text
context'

-- change rtl to r2l, ltr to l2r
toContextDir :: Doc Text -> Doc Text
toContextDir :: Doc Text -> Doc Text
toContextDir = (Text -> Text) -> Doc Text -> Doc Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
t -> case Text
t of
                              Text
"ltr" -> Text
"l2r"
                              Text
"rtl" -> Text
"r2l"
                              Text
_     -> Text
t)

-- | escape things as needed for ConTeXt
escapeCharForConTeXt :: WriterOptions -> Char -> Text
escapeCharForConTeXt :: WriterOptions -> Char -> Text
escapeCharForConTeXt WriterOptions
opts Char
ch =
 let ligatures :: Bool
ligatures = Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts in
 case Char
ch of
    Char
'{'      -> Text
"\\{"
    Char
'}'      -> Text
"\\}"
    Char
'\\'     -> Text
"\\letterbackslash{}"
    Char
'$'      -> Text
"\\$"
    Char
'|'      -> Text
"\\letterbar{}"
    Char
'%'      -> Text
"\\letterpercent{}"
    Char
'~'      -> Text
"\\lettertilde{}"
    Char
'#'      -> Text
"\\#"
    Char
'['      -> Text
"{[}"
    Char
']'      -> Text
"{]}"
    Char
'\160'   -> Text
"~"
    Char
'\x2014' | Bool
ligatures -> Text
"---"
    Char
'\x2013' | Bool
ligatures -> Text
"--"
    Char
'\x2019' | Bool
ligatures -> Text
"'"
    Char
'\x2026' -> Text
"\\ldots{}"
    Char
x        -> Char -> Text
T.singleton Char
x

-- | Escape string for ConTeXt
stringToConTeXt :: WriterOptions -> Text -> Text
stringToConTeXt :: WriterOptions -> Text -> Text
stringToConTeXt WriterOptions
opts = (Char -> Text) -> Text -> Text
T.concatMap (WriterOptions -> Char -> Text
escapeCharForConTeXt WriterOptions
opts)

-- | Sanitize labels
toLabel :: Text -> Text
toLabel :: Text -> Text
toLabel Text
z = (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
go Text
z
 where go :: Char -> Text
go Char
x
         | Char
x Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"\\#[]\",{}%()|=" :: String) = Text
"ux" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%x" (Char -> Int
ord Char
x))
         | Bool
otherwise = Char -> Text
T.singleton Char
x

-- | Convert Pandoc block element to ConTeXt.
blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text)
blockToConTeXt :: Block -> WM m (Doc Text)
blockToConTeXt Block
Null = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
blockToConTeXt (Div attr :: Attr
attr@(Text
_,Text
"section":[Text]
_,[(Text, Text)]
_)
                 (Header Int
level Attr
_ [Inline]
title' : [Block]
xs)) = do
  Doc Text
header' <- Attr -> Int -> [Inline] -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Attr -> Int -> [Inline] -> WM m (Doc Text)
sectionHeader Attr
attr Int
level [Inline]
title'
  Doc Text
footer' <- Attr -> Int -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Attr -> Int -> WM m (Doc Text)
sectionFooter Attr
attr Int
level
  Doc Text
innerContents <- [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
xs
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
header' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
innerContents Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
footer'
blockToConTeXt (Plain [Inline]
lst) = [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
-- title beginning with fig: indicates that the image is a figure
blockToConTeXt (Para [Image Attr
attr [Inline]
txt (Text
src,Text
tgt)])
  | Just Text
_ <- Text -> Text -> Maybe Text
T.stripPrefix Text
"fig:" Text
tgt
  = do
      Doc Text
capt <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
txt
      Doc Text
img  <- Inline -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => Inline -> WM m (Doc Text)
inlineToConTeXt (Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr [Inline]
txt (Text
src, Text
""))
      let (Text
ident, [Text]
_, [(Text, Text)]
_) = Attr
attr
          label :: Doc Text
label = if Text -> Bool
T.null Text
ident
                  then Doc Text
forall a. Doc a
empty
                  else Doc Text
"[]" 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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
toLabel Text
ident)
      Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
forall a. Doc a
blankline Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\placefigure" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
label 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
capt Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
img Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (Para [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (LineBlock [[Inline]]
lns) = do
  Doc Text
doclines <- Doc Text -> Doc Text
forall a. IsString a => Doc a -> Doc a
nowrap (Doc Text -> Doc Text)
-> ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Inline] -> WM m (Doc Text))
-> [[Inline]] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [[Inline]]
lns
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startlines" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
doclines Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stoplines" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (BlockQuote [Block]
lst) = do
  Doc Text
contents <- [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startblockquote" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
0 Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopblockquote" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (CodeBlock Attr
_ Text
str) =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. Doc a -> Doc a
flush (Doc Text
"\\starttyping" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\stoptyping") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
forall a. Doc a
blankline
  -- blankline because \stoptyping can't have anything after it, inc. '}'
blockToConTeXt b :: Block
b@(RawBlock Format
f Text
str)
  | Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"context" Bool -> Bool -> Bool
|| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"tex" = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
  | Bool
otherwise = Doc Text
forall a. Doc a
empty Doc Text -> StateT WriterState m () -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Block -> LogMessage
BlockNotRendered Block
b)
blockToConTeXt (Div (Text
"refs",[Text]
classes,[(Text, Text)]
_) [Block]
bs) = do
  (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{ stHasCslRefs :: Bool
stHasCslRefs = Bool
True
                    , stCslHangingIndent :: Bool
stCslHangingIndent = Text
"hanging-indent" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes }
  Doc Text
inner <- [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
bs
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startcslreferences" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
inner Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopcslreferences"
blockToConTeXt (Div (Text
ident,[Text]
_,[(Text, Text)]
kvs) [Block]
bs) = do
  let align :: Doc a -> Doc a -> Doc a
align Doc a
dir Doc a
txt = Doc a
"\\startalignment[" Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
dir Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
"]" Doc a -> Doc a -> Doc a
forall a. Doc a -> Doc a -> Doc a
$$ Doc a
txt Doc a -> Doc a -> Doc a
forall a. Doc a -> Doc a -> Doc a
$$ Doc a
"\\stopalignment"
  Maybe Text
mblang <- Maybe Text -> WM m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
Maybe Text -> WM m (Maybe Text)
fromBCP47 (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lang" [(Text, Text)]
kvs)
  let wrapRef :: Doc Text -> Doc Text
wrapRef Doc Text
txt = if Text -> Bool
T.null Text
ident
                       then Doc Text
txt
                       else (Doc Text
"\\reference" 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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
toLabel Text
ident) 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
forall a. Doc a
empty Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"%") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
txt
      wrapDir :: Doc Text -> Doc Text
wrapDir = case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"dir" [(Text, Text)]
kvs of
                  Just Text
"rtl" -> Doc Text -> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a -> Doc a
align Doc Text
"righttoleft"
                  Just Text
"ltr" -> Doc Text -> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a -> Doc a
align Doc Text
"lefttoright"
                  Maybe Text
_          -> Doc Text -> Doc Text
forall a. a -> a
id
      wrapLang :: Doc Text -> Doc Text
wrapLang Doc Text
txt = case Maybe Text
mblang of
                       Just Text
lng -> Doc Text
"\\start\\language["
                                     Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
lng Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
txt Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stop"
                       Maybe Text
Nothing  -> Doc Text
txt
      wrapBlank :: Doc a -> Doc a
wrapBlank Doc a
txt = Doc a
forall a. Doc a
blankline Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
txt Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
forall a. Doc a
blankline
  Doc Text -> Doc Text
forall a. Doc a -> Doc a
wrapBlank (Doc Text -> Doc Text)
-> (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
wrapLang (Doc Text -> Doc Text)
-> (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
wrapDir (Doc Text -> Doc Text)
-> (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
wrapRef (Doc Text -> Doc Text) -> WM m (Doc Text) -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
bs
blockToConTeXt (BulletList [[Block]]
lst) = do
  [Doc Text]
contents <- ([Block] -> WM m (Doc Text))
-> [[Block]] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
listItemToConTeXt [[Block]]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ (Doc Text
"\\startitemize" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> if [[Block]] -> Bool
isTightList [[Block]]
lst
                                   then Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets Doc Text
"packed"
                                   else 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]
contents Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\stopitemize" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (OrderedList (Int
start, ListNumberStyle
style', ListNumberDelim
delim) [[Block]]
lst) = do
    WriterState
st <- StateT WriterState m WriterState
forall s (m :: * -> *). MonadState s m => m s
get
    let level :: Int
level = WriterState -> Int
stOrderedListLevel WriterState
st
    WriterState -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put WriterState
st {stOrderedListLevel :: Int
stOrderedListLevel = Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1}
    [Doc Text]
contents <- ([Block] -> WM m (Doc Text))
-> [[Block]] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
listItemToConTeXt [[Block]]
lst
    WriterState -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put WriterState
st {stOrderedListLevel :: Int
stOrderedListLevel = Int
level}
    let start' :: Text
start' = if Int
start Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then Text
"" else Text
"start=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
start
    let delim' :: Text
delim' = case ListNumberDelim
delim of
                        ListNumberDelim
DefaultDelim -> Text
""
                        ListNumberDelim
Period       -> Text
"stopper=."
                        ListNumberDelim
OneParen     -> Text
"stopper=)"
                        ListNumberDelim
TwoParens    -> Text
"left=(,stopper=)"
    let width :: Int
width = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
T.length ([Text] -> [Int]) -> [Text] -> [Int]
forall a b. (a -> b) -> a -> b
$ Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take ([Doc Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Doc Text]
contents)
                          ((Int, ListNumberStyle, ListNumberDelim) -> [Text]
orderedListMarkers (Int
start, ListNumberStyle
style', ListNumberDelim
delim))
    let width' :: Double
width' = (Int -> Double
forall a. Enum a => Int -> a
toEnum Int
width Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2
    let width'' :: Text
width'' = if Double
width' Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> (Double
1.5 :: Double)
                     then Text
"width=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Double -> Text
forall a. Show a => a -> Text
tshow Double
width' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"em"
                     else Text
""
    let specs2Items :: [Text]
specs2Items = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) [Text
start', Text
delim', Text
width'']
    let specs2 :: Text
specs2 = if [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
specs2Items
                    then Text
""
                    else Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"," [Text]
specs2Items Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
    let style'' :: String
style'' = Char
'['Char -> ShowS
forall a. a -> [a] -> [a]
: (case ListNumberStyle
style' of
                          ListNumberStyle
DefaultStyle -> String
orderedListStyles String -> Int -> Char
forall a. [a] -> Int -> a
!! Int
level
                          ListNumberStyle
Decimal      -> Char
'n'
                          ListNumberStyle
Example      -> Char
'n'
                          ListNumberStyle
LowerRoman   -> Char
'r'
                          ListNumberStyle
UpperRoman   -> Char
'R'
                          ListNumberStyle
LowerAlpha   -> Char
'a'
                          ListNumberStyle
UpperAlpha   -> Char
'A') Char -> ShowS
forall a. a -> [a] -> [a]
:
                       if [[Block]] -> Bool
isTightList [[Block]]
lst then String
",packed]" else String
"]"
    let specs :: Text
specs = String -> Text
T.pack String
style'' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
specs2
    Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startitemize" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
specs 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]
contents Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
             Doc Text
"\\stopitemize" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToConTeXt (DefinitionList [([Inline], [[Block]])]
lst) =
  ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat (StateT WriterState m [Doc Text] -> WM m (Doc Text))
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ (([Inline], [[Block]]) -> WM m (Doc Text))
-> [([Inline], [[Block]])] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([Inline], [[Block]]) -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> WM m (Doc Text)
defListItemToConTeXt [([Inline], [[Block]])]
lst
blockToConTeXt Block
HorizontalRule = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\thinrule" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
-- If this is ever executed, provide a default for the reference identifier.
blockToConTeXt (Header Int
level Attr
attr [Inline]
lst) = Attr -> Int -> [Inline] -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Attr -> Int -> [Inline] -> WM m (Doc Text)
sectionHeader Attr
attr Int
level [Inline]
lst
blockToConTeXt (Table Attr
_ Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot) = do
    let ([Inline]
caption, [Alignment]
aligns, [Double]
widths, [[Block]]
heads, [[[Block]]]
rows) = Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
toLegacyTable Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot
    WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
    let tabl :: Tabl
tabl = if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_ntb WriterOptions
opts
          then Tabl
Ntb
          else Tabl
Xtb
    Doc Text
captionText <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
caption
    Doc Text
headers <- if ([Block] -> Bool) -> [[Block]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Block]]
heads
               then Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
               else Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
tableRowToConTeXt Tabl
tabl [Alignment]
aligns [Double]
widths [[Block]]
heads
    [Doc Text]
rows' <- ([[Block]] -> WM m (Doc Text))
-> [[[Block]]] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
tableRowToConTeXt Tabl
tabl [Alignment]
aligns [Double]
widths) [[[Block]]]
rows
    Doc Text
body <- Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text)
tableToConTeXt Tabl
tabl Doc Text
headers [Doc Text]
rows'
    Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startplacetable" 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
brackets (
      if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
caption
        then Doc Text
"location=none"
        else Doc Text
"title=" 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
captionText
      ) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
body Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopplacetable" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline

tableToConTeXt :: PandocMonad m
               => Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text)
tableToConTeXt :: Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text)
tableToConTeXt Tabl
Xtb Doc Text
heads [Doc Text]
rows =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startxtable" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    (if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
heads
      then Doc Text
forall a. Doc a
empty
      else Doc Text
"\\startxtablehead[head]" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
heads Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopxtablehead") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    (if [Doc Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc Text]
rows
      then Doc Text
forall a. Doc a
empty
      else Doc Text
"\\startxtablebody[body]" 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]
forall a. [a] -> [a]
init [Doc Text]
rows) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopxtablebody" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
           Doc Text
"\\startxtablefoot[foot]" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ [Doc Text] -> Doc Text
forall a. [a] -> a
last [Doc Text]
rows Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopxtablefoot") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    Doc Text
"\\stopxtable"
tableToConTeXt Tabl
Ntb Doc Text
heads [Doc Text]
rows =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startTABLE" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    (if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
heads
      then Doc Text
forall a. Doc a
empty
      else Doc Text
"\\startTABLEhead" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
heads Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopTABLEhead") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    (if [Doc Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc Text]
rows
      then Doc Text
forall a. Doc a
empty
      else Doc Text
"\\startTABLEbody" 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]
forall a. [a] -> [a]
init [Doc Text]
rows) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopTABLEbody" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
           Doc Text
"\\startTABLEfoot" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ [Doc Text] -> Doc Text
forall a. [a] -> a
last [Doc Text]
rows Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopTABLEfoot") Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
    Doc Text
"\\stopTABLE"

tableRowToConTeXt :: PandocMonad m => Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
tableRowToConTeXt :: Tabl -> [Alignment] -> [Double] -> [[Block]] -> WM m (Doc Text)
tableRowToConTeXt Tabl
Xtb [Alignment]
aligns [Double]
widths [[Block]]
cols = do
  [Doc Text]
cells <- ((Alignment, Double, [Block]) -> WM m (Doc Text))
-> [(Alignment, Double, [Block])]
-> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
tableColToConTeXt Tabl
Xtb) ([(Alignment, Double, [Block])] -> StateT WriterState m [Doc Text])
-> [(Alignment, Double, [Block])]
-> StateT WriterState m [Doc Text]
forall a b. (a -> b) -> a -> b
$ [Alignment]
-> [Double] -> [[Block]] -> [(Alignment, Double, [Block])]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Alignment]
aligns [Double]
widths [[Block]]
cols
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startxrow" 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]
cells Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\stopxrow"
tableRowToConTeXt Tabl
Ntb [Alignment]
aligns [Double]
widths [[Block]]
cols = do
  [Doc Text]
cells <- ((Alignment, Double, [Block]) -> WM m (Doc Text))
-> [(Alignment, Double, [Block])]
-> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
tableColToConTeXt Tabl
Ntb) ([(Alignment, Double, [Block])] -> StateT WriterState m [Doc Text])
-> [(Alignment, Double, [Block])]
-> StateT WriterState m [Doc Text]
forall a b. (a -> b) -> a -> b
$ [Alignment]
-> [Double] -> [[Block]] -> [(Alignment, Double, [Block])]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Alignment]
aligns [Double]
widths [[Block]]
cols
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat [Doc Text]
cells Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"\\NC\\NR"

tableColToConTeXt :: PandocMonad m => Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
tableColToConTeXt :: Tabl -> (Alignment, Double, [Block]) -> WM m (Doc Text)
tableColToConTeXt Tabl
tabl (Alignment
align, Double
width, [Block]
blocks) = do
  Doc Text
cellContents <- [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
blocks
  let colwidth :: Doc Text
colwidth = if Double
width Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0
        then Doc Text
forall a. Doc a
empty
        else Doc Text
"width=" 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 -> Double -> String
forall r. PrintfType r => String -> r
printf String
"%.2f\\textwidth" Double
width))
  let halign :: Doc Text
halign = Alignment -> Doc Text
alignToConTeXt Alignment
align
  let options :: Doc Text
options = (if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
keys
                 then Doc Text
forall a. Doc a
empty
                 else Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets Doc Text
keys) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
space
        where keys :: Doc Text
keys = [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse Doc Text
"," ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Bool) -> [Doc Text] -> [Doc Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Doc Text -> Bool) -> Doc Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty) [Doc Text
halign, Doc Text
colwidth]
  Tabl -> Doc Text -> Doc Text -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Tabl -> Doc Text -> Doc Text -> WM m (Doc Text)
tableCellToConTeXt Tabl
tabl Doc Text
options Doc Text
cellContents

tableCellToConTeXt :: PandocMonad m
                   => Tabl -> Doc Text -> Doc Text -> WM m (Doc Text)
tableCellToConTeXt :: Tabl -> Doc Text -> Doc Text -> WM m (Doc Text)
tableCellToConTeXt Tabl
Xtb Doc Text
options Doc Text
cellContents =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startxcell" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
options Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
cellContents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
" \\stopxcell"
tableCellToConTeXt Tabl
Ntb Doc Text
options Doc Text
cellContents =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\NC" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
options Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
cellContents

alignToConTeXt :: Alignment -> Doc Text
alignToConTeXt :: Alignment -> Doc Text
alignToConTeXt Alignment
align = case Alignment
align of
                         Alignment
AlignLeft    -> Doc Text
"align=right"
                         Alignment
AlignRight   -> Doc Text
"align=left"
                         Alignment
AlignCenter  -> Doc Text
"align=middle"
                         Alignment
AlignDefault -> Doc Text
forall a. Doc a
empty

listItemToConTeXt :: PandocMonad m => [Block] -> WM m (Doc Text)
listItemToConTeXt :: [Block] -> WM m (Doc Text)
listItemToConTeXt [Block]
list = (Doc Text
"\\item" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$) (Doc Text -> Doc Text)
-> (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 (Doc Text -> Doc Text) -> WM m (Doc Text) -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
list

defListItemToConTeXt :: PandocMonad m => ([Inline], [[Block]]) -> WM m (Doc Text)
defListItemToConTeXt :: ([Inline], [[Block]]) -> WM m (Doc Text)
defListItemToConTeXt ([Inline]
term, [[Block]]
defs) = do
  Doc Text
term' <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
term
  Doc Text
def'  <- ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vsep (StateT WriterState m [Doc Text] -> WM m (Doc Text))
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ ([Block] -> WM m (Doc Text))
-> [[Block]] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [[Block]]
defs
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\startdescription" 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
term' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 Doc Text
def' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
           Doc Text
"\\stopdescription" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline

-- | Convert list of block elements to ConTeXt.
blockListToConTeXt :: PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt :: [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
lst = ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat (StateT WriterState m [Doc Text] -> WM m (Doc Text))
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ (Block -> WM m (Doc Text))
-> [Block] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Block -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> WM m (Doc Text)
blockToConTeXt [Block]
lst

-- | Convert list of inline elements to ConTeXt.
inlineListToConTeXt :: PandocMonad m
                    => [Inline]  -- ^ Inlines to convert
                    -> WM m (Doc Text)
inlineListToConTeXt :: [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst = ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat (StateT WriterState m [Doc Text] -> WM m (Doc Text))
-> StateT WriterState m [Doc Text] -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ (Inline -> WM m (Doc Text))
-> [Inline] -> StateT WriterState m [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => Inline -> WM m (Doc Text)
inlineToConTeXt ([Inline] -> StateT WriterState m [Doc Text])
-> [Inline] -> StateT WriterState m [Doc Text]
forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
addStruts [Inline]
lst
  -- We add a \strut after a line break that precedes a space,
  -- or the space gets swallowed
  where addStruts :: [Inline] -> [Inline]
addStruts (Inline
LineBreak : Inline
s : [Inline]
xs) | Inline -> Bool
isSpacey Inline
s =
           Inline
LineBreak Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"context") Text
"\\strut " Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
s Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
:
             [Inline] -> [Inline]
addStruts [Inline]
xs
        addStruts (Inline
x:[Inline]
xs) = Inline
x Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
addStruts [Inline]
xs
        addStruts [] = []
        isSpacey :: Inline -> Bool
isSpacey Inline
Space                               = Bool
True
        isSpacey (Str (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'\160',Text
_))) = Bool
True
        isSpacey Inline
_                                   = Bool
False

-- | Convert inline element to ConTeXt
inlineToConTeXt :: PandocMonad m
                => Inline    -- ^ Inline to convert
                -> WM m (Doc Text)
inlineToConTeXt :: Inline -> WM m (Doc Text)
inlineToConTeXt (Emph [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\em " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents
inlineToConTeXt (Underline [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\underbar" 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
contents
inlineToConTeXt (Strong [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\bf " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents
inlineToConTeXt (Strikeout [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\overstrikes" 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
contents
inlineToConTeXt (Superscript [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\high" 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
contents
inlineToConTeXt (Subscript [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\low" 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
contents
inlineToConTeXt (SmallCaps [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\sc " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents
inlineToConTeXt (Code Attr
_ Text
str) | Bool -> Bool
not (Char
'{' Char -> Text -> Bool
`elemText` Text
str Bool -> Bool -> Bool
|| Char
'}' Char -> Text -> Bool
`elemText` Text
str) =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\type" 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 (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str)
inlineToConTeXt (Code Attr
_ Text
str) = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\mono" 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 (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Text -> Text
stringToConTeXt WriterOptions
opts Text
str)
inlineToConTeXt (Quoted QuoteType
SingleQuote [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\quote" 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
contents
inlineToConTeXt (Quoted QuoteType
DoubleQuote [Inline]
lst) = do
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\quotation" 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
contents
inlineToConTeXt (Cite [Citation]
_ [Inline]
lst) = [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
inlineToConTeXt (Str Text
str) = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Text -> Text
stringToConTeXt WriterOptions
opts Text
str
inlineToConTeXt (Math MathType
InlineMath Text
str) =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Char -> Doc Text
forall a. HasChars a => Char -> Doc a
char Char
'$' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Char -> Doc Text
forall a. HasChars a => Char -> Doc a
char Char
'$'
inlineToConTeXt (Math MathType
DisplayMath Text
str) =
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\startformula "  Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
" \\stopformula" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
space
inlineToConTeXt il :: Inline
il@(RawInline Format
f Text
str)
  | Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"tex" Bool -> Bool -> Bool
|| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"context" = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
  | Bool
otherwise = Doc Text
forall a. Doc a
empty Doc Text -> StateT WriterState m () -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Inline -> LogMessage
InlineNotRendered Inline
il)
inlineToConTeXt Inline
LineBreak = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\crlf" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
inlineToConTeXt Inline
SoftBreak = do
  WrapOption
wrapText <- (WriterState -> WrapOption) -> StateT WriterState m WrapOption
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (WriterOptions -> WrapOption
writerWrapText (WriterOptions -> WrapOption)
-> (WriterState -> WriterOptions) -> WriterState -> WrapOption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterState -> WriterOptions
stOptions)
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case WrapOption
wrapText of
               WrapOption
WrapAuto     -> Doc Text
forall a. Doc a
space
               WrapOption
WrapNone     -> Doc Text
forall a. Doc a
space
               WrapOption
WrapPreserve -> Doc Text
forall a. Doc a
cr
inlineToConTeXt Inline
Space = Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
-- Handle HTML-like internal document references to sections
inlineToConTeXt (Link Attr
_ [Inline]
txt (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'#', Text
ref), Text
_)) = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  Doc Text
contents <-  [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
txt
  let ref' :: Text
ref' = Text -> Text
toLabel (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Text -> Text
stringToConTeXt WriterOptions
opts Text
ref
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\goto"
           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
contents
           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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
ref')

inlineToConTeXt (Link Attr
_ [Inline]
txt (Text
src, Text
_)) = do
  let isAutolink :: Bool
isAutolink = [Inline]
txt [Inline] -> [Inline] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text -> Inline
Str (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
unEscapeString ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
src)]
  WriterState
st <- StateT WriterState m WriterState
forall s (m :: * -> *). MonadState s m => m s
get
  let next :: Int
next = WriterState -> Int
stNextRef WriterState
st
  WriterState -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (WriterState -> StateT WriterState m ())
-> WriterState -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ WriterState
st {stNextRef :: Int
stNextRef = Int
next Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1}
  let ref :: Text
ref = Text
"url" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
next
  Doc Text
contents <-  [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
txt
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\useURL"
           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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
ref)
           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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ [(Char, Text)] -> Text -> Text
escapeStringUsing [(Char
'#',Text
"\\#"),(Char
'%',Text
"\\%")] Text
src)
           Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> (if Bool
isAutolink
                  then Doc Text
forall a. Doc a
empty
                  else Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets Doc Text
forall a. Doc a
empty 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
brackets Doc Text
contents)
           Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\from"
           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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
ref)
inlineToConTeXt (Image attr :: Attr
attr@(Text
_,[Text]
cls,[(Text, Text)]
_) [Inline]
_ (Text
src, Text
_)) = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  let showDim :: Direction -> [Doc Text]
showDim Direction
dir = let d :: Doc Text
d = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Direction -> Text
forall a. Show a => a -> Text
tshow Direction
dir) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"="
                    in case Direction -> Attr -> Maybe Dimension
dimension Direction
dir Attr
attr of
                         Just (Pixel Integer
a)   ->
                           [Doc Text
d Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (WriterOptions -> Dimension -> Text
showInInch WriterOptions
opts (Integer -> Dimension
Pixel Integer
a)) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"in"]
                         Just (Percent Double
a) ->
                           [Doc Text
d Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Double -> Text
forall a. RealFloat a => a -> Text
showFl (Double
a Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
100)) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\textwidth"]
                         Just Dimension
dim         ->
                           [Doc Text
d Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Dimension -> Text
forall a. Show a => a -> Text
tshow Dimension
dim)]
                         Maybe Dimension
Nothing          ->
                           []
      dimList :: [Doc Text]
dimList = Direction -> [Doc Text]
showDim Direction
Width [Doc Text] -> [Doc Text] -> [Doc Text]
forall a. [a] -> [a] -> [a]
++ Direction -> [Doc Text]
showDim Direction
Height
      dims :: Doc Text
dims = if [Doc Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc Text]
dimList
                then Doc Text
forall a. Doc a
empty
                else Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat (Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse Doc Text
"," [Doc Text]
dimList)
      clas :: Doc Text
clas = if [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
cls
                then Doc Text
forall a. Doc a
empty
                else Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
toLabel (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. [a] -> a
head [Text]
cls
      -- Use / for path separators on Windows; see #4918
      fixPathSeparators :: Text -> Text
fixPathSeparators = (Char -> Char) -> Text -> Text
T.map ((Char -> Char) -> Text -> Text) -> (Char -> Char) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ \Char
c -> case Char
c of
                                          Char
'\\' -> Char
'/'
                                          Char
_    -> Char
c
      src' :: Text
src' = Text -> Text
fixPathSeparators (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
             if Text -> Bool
isURI Text
src
                then Text
src
                else String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
unEscapeString ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
src
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text
"\\externalfigure" 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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
src') Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
dims Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
clas
inlineToConTeXt (Note [Block]
contents) = do
  Doc Text
contents' <- [Block] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> WM m (Doc Text)
blockListToConTeXt [Block]
contents
  let codeBlock :: Block -> [Block]
codeBlock x :: Block
x@(CodeBlock Attr
_ Text
_) = [Block
x]
      codeBlock Block
_                 = []
  let codeBlocks :: [Block]
codeBlocks = (Block -> [Block]) -> [Block] -> [Block]
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> [Block]
codeBlock [Block]
contents
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if [Block] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Block]
codeBlocks
              then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\footnote{" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 (Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
contents') Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Char -> Doc Text
forall a. HasChars a => Char -> Doc a
char Char
'}'
              else Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\startbuffer " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 (Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
contents') Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>
                   Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\stopbuffer\\footnote{\\getbuffer}"
inlineToConTeXt (Span (Text
_,[Text]
_,[(Text, Text)]
kvs) [Inline]
ils) = do
  Maybe Text
mblang <- Maybe Text -> WM m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
Maybe Text -> WM m (Maybe Text)
fromBCP47 (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lang" [(Text, Text)]
kvs)
  let wrapDir :: Doc a -> Doc a
wrapDir Doc a
txt = case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"dir" [(Text, Text)]
kvs of
                      Just Text
"rtl" -> Doc a -> Doc a
forall a. HasChars a => Doc a -> Doc a
braces (Doc a -> Doc a) -> Doc a -> Doc a
forall a b. (a -> b) -> a -> b
$ Doc a
"\\righttoleft " Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
txt
                      Just Text
"ltr" -> Doc a -> Doc a
forall a. HasChars a => Doc a -> Doc a
braces (Doc a -> Doc a) -> Doc a -> Doc a
forall a b. (a -> b) -> a -> b
$ Doc a
"\\lefttoright " Doc a -> Doc a -> Doc a
forall a. Semigroup a => a -> a -> a
<> Doc a
txt
                      Maybe Text
_          -> Doc a
txt
      wrapLang :: Doc Text -> Doc Text
wrapLang Doc Text
txt = case Maybe Text
mblang of
                       Just Text
lng -> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text
"\\language" 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
brackets (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
lng) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
txt)
                       Maybe Text
Nothing -> Doc Text
txt
  Doc Text -> Doc Text
wrapLang (Doc Text -> Doc Text)
-> (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
wrapDir (Doc Text -> Doc Text) -> WM m (Doc Text) -> WM m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
ils

-- | Craft the section header, inserting the section reference, if supplied.
sectionHeader :: PandocMonad m
              => Attr
              -> Int
              -> [Inline]
              -> WM m (Doc Text)
sectionHeader :: Attr -> Int -> [Inline] -> WM m (Doc Text)
sectionHeader (Text
ident,[Text]
classes,[(Text, Text)]
kvs) Int
hdrLevel [Inline]
lst = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  Doc Text
contents <- [Inline] -> WM m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> WM m (Doc Text)
inlineListToConTeXt [Inline]
lst
  Doc Text
levelText <- WriterOptions -> Attr -> Int -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Attr -> Int -> WM m (Doc Text)
sectionLevelToText WriterOptions
opts (Text
ident,[Text]
classes,[(Text, Text)]
kvs) Int
hdrLevel
  let ident' :: Doc Text
ident' = if Text -> Bool
T.null Text
ident
               then Doc Text
forall a. Doc a
empty
               else Doc Text
"reference=" 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 (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Text
toLabel Text
ident))
  let contents' :: Doc Text
contents' = if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
contents
                  then Doc Text
forall a. Doc a
empty
                  else Doc Text
"title=" 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
contents
  let options :: Doc Text
options = if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
keys Bool -> Bool -> Bool
|| Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
levelText
                then Doc Text
forall a. Doc a
empty
                else Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
brackets Doc Text
keys
        where keys :: Doc Text
keys = [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$ Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
intersperse Doc Text
"," ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Bool) -> [Doc Text] -> [Doc Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Doc Text -> Bool) -> Doc Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty) [Doc Text
contents', Doc Text
ident']
  let starter :: Doc Text
starter = if WriterOptions -> Bool
writerSectionDivs WriterOptions
opts
                then Doc Text
"\\start"
                else Doc Text
"\\"
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
starter Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
levelText Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
options Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline

-- | Craft the section footer
sectionFooter :: PandocMonad m => Attr -> Int -> WM m (Doc Text)
sectionFooter :: Attr -> Int -> WM m (Doc Text)
sectionFooter Attr
attr Int
hdrLevel = do
  WriterOptions
opts <- (WriterState -> WriterOptions)
-> StateT WriterState m WriterOptions
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
  Doc Text
levelText <- WriterOptions -> Attr -> Int -> WM m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Attr -> Int -> WM m (Doc Text)
sectionLevelToText WriterOptions
opts Attr
attr Int
hdrLevel
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if WriterOptions -> Bool
writerSectionDivs WriterOptions
opts
           then Doc Text
"\\stop" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
levelText Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
           else Doc Text
forall a. Doc a
empty

-- | Generate a textual representation of the section level
sectionLevelToText :: PandocMonad m => WriterOptions -> Attr -> Int -> WM m (Doc Text)
sectionLevelToText :: WriterOptions -> Attr -> Int -> WM m (Doc Text)
sectionLevelToText WriterOptions
opts (Text
_,[Text]
classes,[(Text, Text)]
_) Int
hdrLevel = do
  let level' :: Int
level' = case WriterOptions -> TopLevelDivision
writerTopLevelDivision WriterOptions
opts of
                 TopLevelDivision
TopLevelPart    -> Int
hdrLevel Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2
                 TopLevelDivision
TopLevelChapter -> Int
hdrLevel Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
                 TopLevelDivision
TopLevelSection -> Int
hdrLevel
                 TopLevelDivision
TopLevelDefault -> Int
hdrLevel
  let (Doc Text
section, Doc Text
chapter) = if Text
"unnumbered" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
                              then (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"subject", Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"title")
                              else (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"section", Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"chapter")
  Doc Text -> WM m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> WM m (Doc Text)) -> Doc Text -> WM m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case Int
level' of
             -1         -> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"part"
             Int
0          -> Doc Text
chapter
             Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 -> String -> Doc Text
forall a. HasChars a => String -> Doc a
text ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Int -> String -> [String]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) String
"sub"))
                           Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
section
             Int
_          -> Doc Text
forall a. Doc a
empty -- cannot happen

fromBCP47 :: PandocMonad m => Maybe Text -> WM m (Maybe Text)
fromBCP47 :: Maybe Text -> WM m (Maybe Text)
fromBCP47 Maybe Text
mbs = Maybe Lang -> Maybe Text
fromBCP47' (Maybe Lang -> Maybe Text)
-> StateT WriterState m (Maybe Lang) -> WM m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> StateT WriterState m (Maybe Lang)
forall (m :: * -> *). PandocMonad m => Maybe Text -> m (Maybe Lang)
toLang Maybe Text
mbs

-- Takes a list of the constituents of a BCP 47 language code
-- and irons out ConTeXt's exceptions
-- https://tools.ietf.org/html/bcp47#section-2.1
-- http://wiki.contextgarden.net/Language_Codes
fromBCP47' :: Maybe Lang -> Maybe Text
fromBCP47' :: Maybe Lang -> Maybe Text
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"SY" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-sy"
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"IQ" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-iq"
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"JO" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-jo"
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"LB" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-lb"
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"DZ" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-dz"
fromBCP47' (Just (Lang Text
"ar" Text
_ Text
"MA" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ar-ma"
fromBCP47' (Just (Lang Text
"de" Text
_ Text
_ [Text
"1901"]) ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"deo"
fromBCP47' (Just (Lang Text
"de" Text
_ Text
"DE" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"de-de"
fromBCP47' (Just (Lang Text
"de" Text
_ Text
"AT" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"de-at"
fromBCP47' (Just (Lang Text
"de" Text
_ Text
"CH" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"de-ch"
fromBCP47' (Just (Lang Text
"el" Text
_ Text
_ [Text
"poly"]) ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"agr"
fromBCP47' (Just (Lang Text
"en" Text
_ Text
"US" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"en-us"
fromBCP47' (Just (Lang Text
"en" Text
_ Text
"GB" [Text]
_)     ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"en-gb"
fromBCP47' (Just (Lang Text
"grc"Text
_  Text
_ [Text]
_)       ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"agr"
fromBCP47' (Just (Lang Text
"el" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"gr"
fromBCP47' (Just (Lang Text
"eu" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ba"
fromBCP47' (Just (Lang Text
"he" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"il"
fromBCP47' (Just (Lang Text
"jp" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ja"
fromBCP47' (Just (Lang Text
"uk" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ua"
fromBCP47' (Just (Lang Text
"vi" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"vn"
fromBCP47' (Just (Lang Text
"zh" Text
_ Text
_ [Text]
_)        ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"cn"
fromBCP47' (Just (Lang Text
l Text
_ Text
_ [Text]
_)           ) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
l
fromBCP47' Maybe Lang
Nothing                          = Maybe Text
forall a. Maybe a
Nothing