{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
import Control.Monad (zipWithM, unless)
import Control.Monad.Except (throwError)
import Control.Monad.State.Strict
( StateT, MonadState(get), gets, modify, evalStateT )
import Data.Char (chr, ord, isAlphaNum)
import Data.List (maximumBy, transpose, foldl')
import Data.List.NonEmpty (nonEmpty)
import Data.Ord (comparing)
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import Network.URI (unEscapeString)
import System.FilePath
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Error
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.DocLayout
import Text.Pandoc.Shared
import Text.Pandoc.URI
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared
import Text.Printf (printf)
data WriterState =
WriterState { WriterState -> Bool
stStrikeout :: Bool
, WriterState -> Context
stContext :: Context
, WriterState -> Map Text Int
stNodes :: M.Map Text Int
, WriterState -> Map Text Text
stHeadings :: M.Map Text Text
, WriterState -> WriterOptions
stOptions :: WriterOptions
}
data Context = NormalContext | NodeContext
deriving (Context -> Context -> Bool
(Context -> Context -> Bool)
-> (Context -> Context -> Bool) -> Eq Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
/= :: Context -> Context -> Bool
Eq, Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
(Int -> Context -> ShowS)
-> (Context -> String) -> ([Context] -> ShowS) -> Show Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Context -> ShowS
showsPrec :: Int -> Context -> ShowS
$cshow :: Context -> String
show :: Context -> String
$cshowList :: [Context] -> ShowS
showList :: [Context] -> ShowS
Show)
withContext :: PandocMonad m => Context -> TI m a -> TI m a
withContext :: forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
context TI m a
pa = do
Context
oldContext <- (WriterState -> Context) -> StateT WriterState m Context
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Context
stContext
(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
s -> WriterState
s{ stContext = context }
a
res <- TI m a
pa
(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
s -> WriterState
s{ stContext = oldContext }
a -> TI m a
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
res
disallowedInNode :: Char -> Bool
disallowedInNode :: Char -> Bool
disallowedInNode Char
c = Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'.',Char
':',Char
',',Char
'(',Char
')']
type TI m = StateT WriterState m
writeTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeTexinfo :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeTexinfo WriterOptions
options Pandoc
document =
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 -> TI m Text
pandocToTexinfo WriterOptions
options (Pandoc -> StateT WriterState m Text)
-> Pandoc -> StateT WriterState m Text
forall a b. (a -> b) -> a -> b
$ Pandoc -> Pandoc
wrapTop Pandoc
document)
WriterState { stStrikeout :: Bool
stStrikeout = Bool
False,
stContext :: Context
stContext = Context
NormalContext,
stNodes :: Map Text Int
stNodes = Map Text Int
forall a. Monoid a => a
mempty,
stHeadings :: Map Text Text
stHeadings = Map Text Text
forall a. Monoid a => a
mempty,
stOptions :: WriterOptions
stOptions = WriterOptions
options}
wrapTop :: Pandoc -> Pandoc
wrapTop :: Pandoc -> Pandoc
wrapTop (Pandoc Meta
meta [Block]
blocks) =
Meta -> [Block] -> Pandoc
Pandoc Meta
meta (Int -> Attr -> [Inline] -> Block
Header Int
0 Attr
nullAttr (Meta -> [Inline]
docTitle Meta
meta) Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
blocks)
addNodeText :: PandocMonad m => Block -> TI m Block
addNodeText :: forall (m :: * -> *). PandocMonad m => Block -> TI m Block
addNodeText (Header Int
lev (Text
ident,[Text]
_,[(Text, Text)]
_) [Inline]
ils) | Int
lev Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 Bool -> Bool -> Bool
&& Int
lev Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
4 = do
Text
node <- Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing (Doc Text -> Text)
-> StateT WriterState m (Doc Text) -> StateT WriterState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Context
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
NodeContext ([Inline] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
ils)
Map Text Int
nodes <- (WriterState -> Map Text Int)
-> StateT WriterState m (Map Text Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Text Int
stNodes
Text
node' <- case Text -> Map Text Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
node Map Text Int
nodes of
Just Int
i -> 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{ stNodes = M.adjust (+ 1) node nodes }
Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> StateT WriterState m Text)
-> Text -> StateT WriterState m Text
forall a b. (a -> b) -> a -> b
$ Text
node Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Maybe Int
Nothing -> 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{ stNodes = M.insert node 1 nodes }
Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
node
Bool -> StateT WriterState m () -> StateT WriterState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
ident) (StateT WriterState m () -> StateT WriterState m ())
-> StateT WriterState m () -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$
(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{ stHeadings = M.insert ident node' (stHeadings st) }
Block -> TI m Block
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Block -> TI m Block) -> Block -> TI m Block
forall a b. (a -> b) -> a -> b
$ Int -> Attr -> [Inline] -> Block
Header Int
lev (Text
ident,[],[(Text
"node", Text
node')]) [Inline]
ils
addNodeText Block
x = Block -> TI m Block
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Block
x
pandocToTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> TI m Text
pandocToTexinfo :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> TI m Text
pandocToTexinfo WriterOptions
options (Pandoc Meta
meta [Block]
blocks') = do
[Block]
blocks <- (Block -> StateT WriterState m Block)
-> [Block] -> StateT WriterState m [Block]
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Block -> m Block) -> [Block] -> m [Block]
walkM Block -> StateT WriterState m Block
forall (m :: * -> *). PandocMonad m => Block -> TI m Block
addNodeText [Block]
blocks'
let titlePage :: Bool
titlePage = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ([Inline] -> Bool) -> [[Inline]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
([[Inline]] -> Bool) -> [[Inline]] -> Bool
forall a b. (a -> b) -> a -> b
$ Meta -> [Inline]
docTitle Meta
meta [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: Meta -> [Inline]
docDate Meta
meta [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: Meta -> [[Inline]]
docAuthors Meta
meta
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] -> TI m (Doc Text)
blockListToTexinfo
((Doc Text -> Doc Text)
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall a b.
(a -> b) -> StateT WriterState m a -> StateT WriterState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Doc Text -> Doc Text
forall a. 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] -> TI m (Doc Text)
inlineListToTexinfo)
Meta
meta
Doc Text
body <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
blocks
WriterState
st <- StateT WriterState m WriterState
forall s (m :: * -> *). MonadState s m => m s
get
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
"body" Doc Text
body
(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
"toc" (WriterOptions -> Bool
writerTableOfContents 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
"titlepage" Bool
titlePage
(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
"strikeout" (WriterState -> Bool
stStrikeout WriterState
st) Context Text
metadata
Text -> TI m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TI m Text) -> Text -> TI 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
body
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
stringToTexinfo :: PandocMonad m => Text -> TI m Text
stringToTexinfo :: forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo Text
t
| (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isAlphaNum Text
t = Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
t
| Bool
otherwise = do
Context
context <- (WriterState -> Context) -> StateT WriterState m Context
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Context
stContext
let escChar :: Char -> Text
escChar Char
'{' = Text
"@{"
escChar Char
'}' = Text
"@}"
escChar Char
'@' = Text
"@@"
escChar Char
'\160' = Text
"@ "
escChar Char
'\x2014' = Text
"---"
escChar Char
'\x2013' = Text
"--"
escChar Char
'\x2026' = Text
"@dots{}"
escChar Char
'\x2019' = Text
"'"
escChar Char
',' | Context
context Context -> Context -> Bool
forall a. Eq a => a -> a -> Bool
== Context
NodeContext = Text
""
escChar Char
':' | Context
context Context -> Context -> Bool
forall a. Eq a => a -> a -> Bool
== Context
NodeContext = Text
""
escChar Char
'.' | Context
context Context -> Context -> Bool
forall a. Eq a => a -> a -> Bool
== Context
NodeContext = Text
""
escChar Char
'(' | Context
context Context -> Context -> Bool
forall a. Eq a => a -> a -> Bool
== Context
NodeContext = Text
""
escChar Char
')' | Context
context Context -> Context -> Bool
forall a. Eq a => a -> a -> Bool
== Context
NodeContext = Text
""
escChar Char
c = Char -> Text
T.singleton Char
c
Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> StateT WriterState m Text)
-> Text -> StateT WriterState m Text
forall a b. (a -> b) -> a -> b
$ (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
escChar Text
t
inCmd :: Text -> Doc Text -> Doc Text
inCmd :: Text -> Doc Text -> Doc Text
inCmd Text
cmd Doc Text
contents = 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
cmd 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
blockToTexinfo :: PandocMonad m
=> Block
-> TI m (Doc Text)
blockToTexinfo :: forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo (Div Attr
_ [Block]
bs) = [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
bs
blockToTexinfo (Plain [Inline]
lst) =
[Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
blockToTexinfo (Para [Inline]
lst) =
[Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
blockToTexinfo (LineBlock [[Inline]]
lns) =
Block -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo (Block -> TI m (Doc Text)) -> Block -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [[Inline]] -> Block
linesToPara [[Inline]]
lns
blockToTexinfo (BlockQuote [Block]
lst) = do
Doc Text
contents <- [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@quotation" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end quotation"
blockToTexinfo (CodeBlock Attr
_ Text
str) =
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@verbatim" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text -> Doc Text
forall a. Doc a -> Doc a
flush (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end verbatim" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToTexinfo b :: Block
b@(RawBlock Format
f Text
str)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"texinfo" = Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"latex" Bool -> Bool -> Bool
|| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"tex" =
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@tex" 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
str Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end tex"
| Bool
otherwise = do
LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT WriterState m ())
-> LogMessage -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ Block -> LogMessage
BlockNotRendered Block
b
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
blockToTexinfo (BulletList [[Block]]
lst) = do
[Doc Text]
items <- ([Block] -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
listItemToTexinfo [[Block]]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@itemize" 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]
items Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end itemize" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToTexinfo (OrderedList (Int
start, ListNumberStyle
numstyle, ListNumberDelim
_) [[Block]]
lst) = do
[Doc Text]
items <- ([Block] -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
listItemToTexinfo [[Block]]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@enumerate " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
exemplar 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]
items Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end enumerate" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
where
exemplar :: Doc Text
exemplar = case ListNumberStyle
numstyle of
ListNumberStyle
DefaultStyle -> Doc Text
decimal
ListNumberStyle
Decimal -> Doc Text
decimal
ListNumberStyle
Example -> Doc Text
decimal
ListNumberStyle
UpperRoman -> Doc Text
decimal
ListNumberStyle
LowerRoman -> Doc Text
decimal
ListNumberStyle
UpperAlpha -> Doc Text
upperAlpha
ListNumberStyle
LowerAlpha -> Doc Text
lowerAlpha
decimal :: Doc Text
decimal = if Int
start Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
then Doc Text
forall a. Doc a
empty
else String -> Doc Text
forall a. HasChars a => String -> Doc a
text (Int -> String
forall a. Show a => a -> String
show Int
start)
upperAlpha :: Doc Text
upperAlpha = String -> Doc Text
forall a. HasChars a => String -> Doc a
text [Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Char -> Int
ord Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
lowerAlpha :: Doc Text
lowerAlpha = String -> Doc Text
forall a. HasChars a => String -> Doc a
text [Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Char -> Int
ord Char
'a' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
blockToTexinfo (DefinitionList [([Inline], [[Block]])]
lst) = do
[Doc Text]
items <- (([Inline], [[Block]]) -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ([Inline], [[Block]]) -> TI m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> TI m (Doc Text)
defListItemToTexinfo [([Inline], [[Block]])]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@table @asis" 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]
items Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end table" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToTexinfo Block
HorizontalRule =
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@iftex" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@bigskip@hrule@bigskip" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end iftex" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@ifnottex" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
72 Char
'-') Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end ifnottex"
blockToTexinfo (Header Int
0 Attr
_ [Inline]
lst) = do
Doc Text
txt <- if [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
lst
then Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"Top"
else [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@node Top" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@top " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
txt Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToTexinfo (Header Int
level (Text
_,[Text]
_,[(Text
"node",Text
node)]) [Inline]
lst) = do
Doc Text
txt <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Text
sec <- Int -> TI m Text
forall (m :: * -> *). PandocMonad m => Int -> TI m Text
seccmd Int
level
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if (Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) Bool -> Bool -> Bool
&& (Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
4)
then Doc Text
forall a. Doc a
blankline Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@node " 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
node 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
sec Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
txt
else Doc Text
txt
where
seccmd :: PandocMonad m => Int -> TI m Text
seccmd :: forall (m :: * -> *). PandocMonad m => Int -> TI m Text
seccmd Int
1 = Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"@chapter "
seccmd Int
2 = Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"@section "
seccmd Int
3 = Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"@subsection "
seccmd Int
4 = Text -> StateT WriterState m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"@subsubsection "
seccmd Int
_ = PandocError -> StateT WriterState m Text
forall a. PandocError -> StateT WriterState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> StateT WriterState m Text)
-> PandocError -> StateT WriterState m Text
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError Text
"illegal seccmd level"
blockToTexinfo (Header Int
_ Attr
_ [Inline]
lst) = Block -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo ([Inline] -> Block
Para [Inline]
lst)
blockToTexinfo (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
Doc Text
headers <- if ([Block] -> Bool) -> [[Block]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Block]]
heads
then Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
else [Alignment] -> [[Block]] -> TI m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Alignment] -> [[Block]] -> TI m (Doc Text)
tableHeadToTexinfo [Alignment]
aligns [[Block]]
heads
Doc Text
captionText <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
caption
[Doc Text]
rowsText <- ([[Block]] -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ([Alignment] -> [[Block]] -> TI m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Alignment] -> [[Block]] -> TI m (Doc Text)
tableRowToTexinfo [Alignment]
aligns) [[[Block]]]
rows
String
colDescriptors <-
if (Double -> Bool) -> [Double] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0) [Double]
widths
then do
[[String]]
cols <- ([[Block]] -> StateT WriterState m [String])
-> [[[Block]]] -> StateT WriterState m [[String]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (([Block] -> StateT WriterState m String)
-> [[Block]] -> StateT WriterState m [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (([Doc Text] -> String)
-> StateT WriterState m [Doc Text] -> StateT WriterState m String
forall a b.
(a -> b) -> StateT WriterState m a -> StateT WriterState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (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 -> Text)
-> ([Doc Text] -> Doc Text) -> [Doc Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat) (StateT WriterState m [Doc Text] -> StateT WriterState m String)
-> ([Block] -> StateT WriterState m [Doc Text])
-> [Block]
-> StateT WriterState m String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Block -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Block -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo)) ([[[Block]]] -> StateT WriterState m [[String]])
-> [[[Block]]] -> StateT WriterState m [[String]]
forall a b. (a -> b) -> a -> b
$
[[[Block]]] -> [[[Block]]]
forall a. [[a]] -> [[a]]
transpose ([[[Block]]] -> [[[Block]]]) -> [[[Block]]] -> [[[Block]]]
forall a b. (a -> b) -> a -> b
$ [[Block]]
heads [[Block]] -> [[[Block]]] -> [[[Block]]]
forall a. a -> [a] -> [a]
: [[[Block]]]
rows
String -> StateT WriterState m String
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> StateT WriterState m String)
-> String -> StateT WriterState m String
forall a b. (a -> b) -> a -> b
$ ([String] -> String) -> [[String]] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
((\String
x -> String
"{"String -> ShowS
forall a. [a] -> [a] -> [a]
++String
xString -> ShowS
forall a. [a] -> [a] -> [a]
++String
"} ") ShowS -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String
-> (NonEmpty String -> String) -> Maybe (NonEmpty String) -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ((String -> String -> Ordering) -> NonEmpty String -> String
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
maximumBy ((String -> Int) -> String -> String -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length)) (Maybe (NonEmpty String) -> String)
-> ([String] -> Maybe (NonEmpty String)) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Maybe (NonEmpty String)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty)
[[String]]
cols
else String -> StateT WriterState m String
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> StateT WriterState m String)
-> String -> StateT WriterState m String
forall a b. (a -> b) -> a -> b
$ String
"@columnfractions " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Double -> String) -> [Double] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String -> Double -> String
forall r. PrintfType r => String -> r
printf String
"%.2f ") [Double]
widths
let tableBody :: Doc Text
tableBody = String -> Doc Text
forall a. HasChars a => String -> Doc a
text (String
"@multitable " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
colDescriptors) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text
headers 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]
rowsText Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end multitable"
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
captionText
then Doc Text
tableBody Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
else String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@float Table" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text
tableBody Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Text -> Doc Text -> Doc Text
inCmd Text
"caption" Doc Text
captionText Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end float"
blockToTexinfo (Figure Attr
_ Caption
caption [SimpleFigure Attr
attr [Inline]
figCaption (Text, Text)
tgt]) = do
let capt :: [Inline]
capt = if [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
figCaption
then let (Caption Maybe [Inline]
_ [Block]
cblks) = Caption
caption
in [Block] -> [Inline]
blocksToInlines [Block]
cblks
else [Inline]
figCaption
Doc Text
captionText <- if [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
capt
then Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
else (String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@caption" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>) (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
braces (Doc Text -> Doc Text) -> TI m (Doc Text) -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
capt
Doc Text
img <- Inline -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Inline -> TI m (Doc Text)
inlineToTexinfo (Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr [Inline]
figCaption (Text, Text)
tgt)
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@float Figure" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
img Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
captionText Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end float"
blockToTexinfo (Figure Attr
_ Caption
fCaption [
Table Attr
attr tCaption :: Caption
tCaption@(Caption Maybe [Inline]
_ [Block]
cbody) [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot]) = do
let caption :: Caption
caption = case [Block]
cbody of
[] -> Caption
fCaption
[Block]
_ -> Caption
tCaption
Block -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo (Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
attr Caption
caption [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot)
blockToTexinfo (Figure Attr
_ (Caption Maybe [Inline]
_ [Block]
caption) [Block]
body) = do
Doc Text
captionText <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo ([Inline] -> TI m (Doc Text)) -> [Inline] -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Block] -> [Inline]
blocksToInlines [Block]
caption
Doc Text
content <- [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
body
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text (String
"@float" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Block] -> String
forall {a}. IsString a => [Block] -> a
floatType [Block]
body) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
content 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
captionText
then Doc Text
forall a. Doc a
empty
else Text -> Doc Text -> Doc Text
inCmd Text
"caption" Doc Text
captionText
) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end float"
where
floatType :: [Block] -> a
floatType [SimpleFigure {}] = a
" Figure"
floatType [Table {}] = a
" Table"
floatType [Block]
_ = a
""
tableHeadToTexinfo :: PandocMonad m
=> [Alignment]
-> [[Block]]
-> TI m (Doc Text)
tableHeadToTexinfo :: forall (m :: * -> *).
PandocMonad m =>
[Alignment] -> [[Block]] -> TI m (Doc Text)
tableHeadToTexinfo = Text -> [Alignment] -> [[Block]] -> TI m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> [Alignment] -> [[Block]] -> TI m (Doc Text)
tableAnyRowToTexinfo Text
"@headitem "
tableRowToTexinfo :: PandocMonad m
=> [Alignment]
-> [[Block]]
-> TI m (Doc Text)
tableRowToTexinfo :: forall (m :: * -> *).
PandocMonad m =>
[Alignment] -> [[Block]] -> TI m (Doc Text)
tableRowToTexinfo = Text -> [Alignment] -> [[Block]] -> TI m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> [Alignment] -> [[Block]] -> TI m (Doc Text)
tableAnyRowToTexinfo Text
"@item "
tableAnyRowToTexinfo :: PandocMonad m
=> Text
-> [Alignment]
-> [[Block]]
-> TI m (Doc Text)
tableAnyRowToTexinfo :: forall (m :: * -> *).
PandocMonad m =>
Text -> [Alignment] -> [[Block]] -> TI m (Doc Text)
tableAnyRowToTexinfo Text
itemtype [Alignment]
aligns [[Block]]
cols =
(Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
itemtype 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
. (Doc Text -> Doc Text -> Doc Text)
-> Doc Text -> [Doc Text] -> Doc Text
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Doc Text
row Doc Text
item -> Doc Text
row 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
row then Doc Text
forall a. Doc a
empty else String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
" @tab ") Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
item) Doc Text
forall a. Doc a
empty ([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
<$> (Alignment -> [Block] -> StateT WriterState m (Doc Text))
-> [Alignment] -> [[Block]] -> StateT WriterState m [Doc Text]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Alignment -> [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Alignment -> [Block] -> TI m (Doc Text)
alignedBlock [Alignment]
aligns [[Block]]
cols
alignedBlock :: PandocMonad m
=> Alignment
-> [Block]
-> TI m (Doc Text)
alignedBlock :: forall (m :: * -> *).
PandocMonad m =>
Alignment -> [Block] -> TI m (Doc Text)
alignedBlock Alignment
_ = [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo
blockListToTexinfo :: PandocMonad m
=> [Block]
-> TI m (Doc Text)
blockListToTexinfo :: forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [] = Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
blockListToTexinfo (Block
x:[Block]
xs) = do
Doc Text
x' <- Block -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
blockToTexinfo Block
x
case Block
x of
Header Int
level Attr
_ [Inline]
_ -> do
let ([Block]
before, [Block]
after) = (Block -> Bool) -> [Block] -> ([Block], [Block])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Block -> Bool
isHeaderBlock [Block]
xs
Doc Text
before' <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
before
let menu :: [Block]
menu = if Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
4
then Int -> [Block] -> [Block]
collectNodes (Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) [Block]
after
else []
[Doc Text]
lines' <- (Block -> StateT WriterState 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Block -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => Block -> TI m (Doc Text)
makeMenuLine [Block]
menu
let menu' :: Doc Text
menu' = if [Doc Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc Text]
lines'
then Doc Text
forall a. Doc a
empty
else Doc Text
forall a. Doc a
blankline Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@menu" 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]
lines' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end menu"
Doc Text
after' <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
after
Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> StateT WriterState m (Doc Text))
-> Doc Text -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
before' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
menu' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
after'
Para [Inline]
_ -> do
Doc Text
xs' <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
xs
case [Block]
xs of
(CodeBlock Attr
_ Text
_:[Block]
_) -> Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> StateT WriterState m (Doc Text))
-> Doc Text -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
xs'
[Block]
_ -> Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> StateT WriterState m (Doc Text))
-> Doc Text -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$+$ Doc Text
xs'
Block
_ -> do
Doc Text
xs' <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
xs
Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> StateT WriterState m (Doc Text))
-> Doc Text -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
xs'
collectNodes :: Int -> [Block] -> [Block]
collectNodes :: Int -> [Block] -> [Block]
collectNodes Int
_ [] = []
collectNodes Int
level (Block
x:[Block]
xs) =
case Block
x of
(Header Int
hl Attr
_ [Inline]
_)
| Int
hl Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
level -> []
| Int
hl Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
level -> Block
x Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: Int -> [Block] -> [Block]
collectNodes Int
level [Block]
xs
| Bool
otherwise -> Int -> [Block] -> [Block]
collectNodes Int
level [Block]
xs
Block
_ ->
Int -> [Block] -> [Block]
collectNodes Int
level [Block]
xs
makeMenuLine :: PandocMonad m
=> Block
-> TI m (Doc Text)
(Header Int
_ (Text
_,[Text]
_,[(Text
"node", Text
node)]) [Inline]
lst) = do
Doc Text
txt <- Context -> TI m (Doc Text) -> TI m (Doc Text)
forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
NodeContext (TI m (Doc Text) -> TI m (Doc Text))
-> TI m (Doc Text) -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. IsString a => Doc a -> Doc a
nowrap (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"* " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>
if Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing Doc Text
txt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
node
then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
node Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"::"
else Doc Text
txt 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
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
node Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"."
makeMenuLine Block
_ = PandocError -> TI m (Doc Text)
forall a. PandocError -> StateT WriterState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> TI m (Doc Text)) -> PandocError -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError Text
"makeMenuLine called with non-node"
listItemToTexinfo :: PandocMonad m
=> [Block]
-> TI m (Doc Text)
listItemToTexinfo :: forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
listItemToTexinfo [Block]
lst = do
Doc Text
contents <- [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
lst
let spacer :: Doc a
spacer = case [Block] -> [Block]
forall a. [a] -> [a]
reverse [Block]
lst of
(Para{}:[Block]
_) -> Doc a
forall a. Doc a
blankline
[Block]
_ -> Doc a
forall a. Doc a
empty
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@item" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
spacer
defListItemToTexinfo :: PandocMonad m
=> ([Inline], [[Block]])
-> TI m (Doc Text)
defListItemToTexinfo :: forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> TI m (Doc Text)
defListItemToTexinfo ([Inline]
term, [[Block]]
defs) = do
Doc Text
term' <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
term
let defToTexinfo :: [Block] -> StateT WriterState m (Doc Text)
defToTexinfo [Block]
bs = do Doc Text
d <- [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
bs
case [Block] -> [Block]
forall a. [a] -> [a]
reverse [Block]
bs of
(Para{}:[Block]
_) -> Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> StateT WriterState m (Doc Text))
-> Doc Text -> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
d Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
[Block]
_ -> Doc Text -> StateT WriterState m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
d
[Doc Text]
defs' <- ([Block] -> TI 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
defToTexinfo [[Block]]
defs
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@item " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
term' 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]
defs'
inlineListToTexinfo :: PandocMonad m
=> [Inline]
-> TI m (Doc Text)
inlineListToTexinfo :: forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst = [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat ([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
<$> (Inline -> StateT WriterState 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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *). PandocMonad m => Inline -> TI m (Doc Text)
inlineToTexinfo [Inline]
lst
inlineToTexinfo :: PandocMonad m
=> Inline
-> TI m (Doc Text)
inlineToTexinfo :: forall (m :: * -> *). PandocMonad m => Inline -> TI m (Doc Text)
inlineToTexinfo (Span Attr
_ [Inline]
lst) =
[Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
inlineToTexinfo (Emph [Inline]
lst) =
Text -> Doc Text -> Doc Text
inCmd Text
"emph" (Doc Text -> Doc Text) -> TI m (Doc Text) -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
inlineToTexinfo (Underline [Inline]
lst) =
Inline -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => Inline -> TI m (Doc Text)
inlineToTexinfo ([Inline] -> Inline
Emph [Inline]
lst)
inlineToTexinfo (Strong [Inline]
lst) =
Text -> Doc Text -> Doc Text
inCmd Text
"strong" (Doc Text -> Doc Text) -> TI m (Doc Text) -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
inlineToTexinfo (Strikeout [Inline]
lst) = 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{ stStrikeout = True }
Doc Text
contents <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@textstrikeout{" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"}"
inlineToTexinfo (Superscript [Inline]
lst) = do
Doc Text
contents <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@sup{" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> 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
'}'
inlineToTexinfo (Subscript [Inline]
lst) = do
Doc Text
contents <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@sub{" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> 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
'}'
inlineToTexinfo (SmallCaps [Inline]
lst) =
Text -> Doc Text -> Doc Text
inCmd Text
"sc" (Doc Text -> Doc Text) -> TI m (Doc Text) -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
inlineToTexinfo (Code (Text
_, [Text]
cls , [(Text, Text)]
_) Text
str) | String -> Text
T.pack String
"variable" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
cls = do
Text
code <- Text -> TI m Text
forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo Text
str
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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
$ Text
"@code{@var{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
code Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}}"
inlineToTexinfo (Code Attr
_ Text
str) = do
Text
code <- Text -> TI m Text
forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo Text
str
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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
$ Text
"@code{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
code Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
inlineToTexinfo (Quoted QuoteType
SingleQuote [Inline]
lst) = do
Doc Text
contents <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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
<> 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
'\''
inlineToTexinfo (Quoted QuoteType
DoubleQuote [Inline]
lst) = do
Doc Text
contents <- [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"``" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"''"
inlineToTexinfo (Cite [Citation]
_ [Inline]
lst) =
[Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
lst
inlineToTexinfo (Str Text
str) = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> TI m Text -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TI m Text
forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo Text
str
inlineToTexinfo (Math MathType
_ Text
str) = Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text -> Doc Text
inCmd Text
"math" (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
str
inlineToTexinfo il :: Inline
il@(RawInline Format
f Text
str)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"latex" Bool -> Bool -> Bool
|| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"tex" =
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@tex" 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
str Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@end tex"
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"texinfo" = Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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 = do
LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT WriterState m ())
-> LogMessage -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ Inline -> LogMessage
InlineNotRendered Inline
il
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToTexinfo Inline
LineBreak = Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@*" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
inlineToTexinfo 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)
case WrapOption
wrapText of
WrapOption
WrapAuto -> Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
WrapOption
WrapNone -> Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
WrapOption
WrapPreserve -> Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
cr
inlineToTexinfo Inline
Space = Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
inlineToTexinfo (Link Attr
_ [Inline]
txt (Text
src, Text
_))
| Just (Char
'#', Text
ident) <- Text -> Maybe (Char, Text)
T.uncons Text
src = do
Map Text Text
headings <- (WriterState -> Map Text Text)
-> StateT WriterState m (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Text Text
stHeadings
Doc Text
target <- case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
ident Map Text Text
headings of
Maybe Text
Nothing -> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> TI m Text -> TI m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TI m Text
forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo
((Char -> Bool) -> Text -> Text
T.filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
disallowedInNode) Text
src)
Just Text
node -> Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
node
Doc Text
contents <- Context -> TI m (Doc Text) -> TI m (Doc Text)
forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
NodeContext (TI m (Doc Text) -> TI m (Doc Text))
-> TI m (Doc Text) -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
txt
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@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
braces (Doc Text
target Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> if Doc Text
contents Doc Text -> Doc Text -> Bool
forall a. Eq a => a -> a -> Bool
== Doc Text
target
then Doc Text
forall a. Monoid a => a
mempty
else String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
",," Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
contents)
| Bool
otherwise = case [Inline]
txt of
[Str Text
x] | Text -> Text
escapeURI Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
src ->
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI 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
$ Text
"@url{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
[Inline]
_ -> do
Doc Text
contents <- Context -> TI m (Doc Text) -> TI m (Doc Text)
forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
NodeContext (TI m (Doc Text) -> TI m (Doc Text))
-> TI m (Doc Text) -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
txt
Text
src1 <- Text -> TI m Text
forall (m :: * -> *). PandocMonad m => Text -> TI m Text
stringToTexinfo Text
src
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text
"@uref{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
src1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
",") Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> 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
'}'
inlineToTexinfo (Image Attr
attr [Inline]
alternate (Text
source, Text
_)) = do
Doc Text
content <- Context -> TI m (Doc Text) -> TI m (Doc Text)
forall (m :: * -> *) a.
PandocMonad m =>
Context -> TI m a -> TI m a
withContext Context
NodeContext (TI m (Doc Text) -> TI m (Doc Text))
-> TI m (Doc Text) -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Inline] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Inline] -> TI m (Doc Text)
inlineListToTexinfo [Inline]
alternate
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 -> Text
showDim Direction
dim = case Direction -> Attr -> Maybe Dimension
dimension Direction
dim Attr
attr of
(Just (Pixel Integer
a)) -> WriterOptions -> Dimension -> Text
showInInch WriterOptions
opts (Integer -> Dimension
Pixel Integer
a) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in"
(Just (Percent Double
_)) -> Text
""
(Just Dimension
d) -> Dimension -> Text
forall a. Show a => a -> Text
tshow Dimension
d
Maybe Dimension
Nothing -> Text
""
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text
"@image{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
base Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Direction -> Text
showDim Direction
Width Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Direction -> Text
showDim Direction
Height Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
",")
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
content Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"," 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
ext Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}")
where
ext :: Text
ext = Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtension String
source'
base :: Text
base = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
dropExtension String
source'
source' :: String
source' = if Text -> Bool
isURI Text
source
then Text -> String
T.unpack Text
source
else ShowS
unEscapeString ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
source
inlineToTexinfo (Note [Block]
contents) = do
Doc Text
contents' <- [Block] -> TI m (Doc Text)
forall (m :: * -> *). PandocMonad m => [Block] -> TI m (Doc Text)
blockListToTexinfo [Block]
contents
Doc Text -> TI m (Doc Text)
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> TI m (Doc Text)) -> Doc Text -> TI m (Doc Text)
forall a b. (a -> b) -> a -> b
$ String -> Doc Text
forall a. HasChars a => String -> Doc a
text String
"@footnote" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces Doc Text
contents'