{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc, writeAsciiDoctor) where
import Control.Monad.State.Strict
import Data.Char (isPunctuation, isSpace)
import Data.List (intercalate, intersperse)
import Data.Maybe (fromMaybe, isJust)
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Text (Text)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (blankline, space)
import Text.DocLayout
import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared
data WriterState = WriterState { WriterState -> Text
defListMarker :: Text
, WriterState -> Int
orderedListLevel :: Int
, WriterState -> Int
bulletListLevel :: Int
, WriterState -> Bool
intraword :: Bool
, WriterState -> Set Text
autoIds :: Set.Set Text
, WriterState -> Bool
asciidoctorVariant :: Bool
, WriterState -> Bool
inList :: Bool
, WriterState -> Bool
hasMath :: Bool
}
defaultWriterState :: WriterState
defaultWriterState :: WriterState
defaultWriterState = WriterState :: Text
-> Int
-> Int
-> Bool
-> Set Text
-> Bool
-> Bool
-> Bool
-> WriterState
WriterState { defListMarker :: Text
defListMarker = Text
"::"
, orderedListLevel :: Int
orderedListLevel = Int
0
, bulletListLevel :: Int
bulletListLevel = Int
0
, intraword :: Bool
intraword = Bool
False
, autoIds :: Set Text
autoIds = Set Text
forall a. Set a
Set.empty
, asciidoctorVariant :: Bool
asciidoctorVariant = Bool
False
, inList :: Bool
inList = Bool
False
, hasMath :: Bool
hasMath = Bool
False
}
writeAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeAsciiDoc :: WriterOptions -> Pandoc -> m Text
writeAsciiDoc WriterOptions
opts 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 -> ADW m Text
pandocToAsciiDoc WriterOptions
opts Pandoc
document) WriterState
defaultWriterState
writeAsciiDoctor :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeAsciiDoctor :: WriterOptions -> Pandoc -> m Text
writeAsciiDoctor WriterOptions
opts 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 -> ADW m Text
pandocToAsciiDoc WriterOptions
opts Pandoc
document)
WriterState
defaultWriterState{ asciidoctorVariant :: Bool
asciidoctorVariant = Bool
True }
type ADW = StateT WriterState
pandocToAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> ADW m Text
pandocToAsciiDoc :: WriterOptions -> Pandoc -> ADW m Text
pandocToAsciiDoc WriterOptions
opts (Pandoc Meta
meta [Block]
blocks) = do
let titleblock :: Bool
titleblock = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Meta -> [Inline]
docTitle Meta
meta) Bool -> Bool -> Bool
&& [[Inline]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Meta -> [[Inline]]
docAuthors Meta
meta) Bool -> Bool -> Bool
&&
[Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Meta -> [Inline]
docDate Meta
meta)
let colwidth :: Maybe Int
colwidth = if WriterOptions -> WrapOption
writerWrapText WriterOptions
opts 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
opts
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
opts
(WriterOptions -> [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts)
((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
. WriterOptions -> [Inline] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts)
Meta
meta
Doc Text
main <- WriterOptions -> [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts ([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 (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) [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
main
(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
opts Bool -> Bool -> Bool
&&
Maybe (Template Text) -> Bool
forall a. Maybe a -> Bool
isJust (WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
opts))
(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
"math" (WriterState -> Bool
hasMath 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
"titleblock" Bool
titleblock Context Text
metadata
Text -> ADW m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ADW m Text) -> Text -> ADW 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
opts 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
escapeString :: Text -> Text
escapeString :: Text -> Text
escapeString = [(Char, Text)] -> Text -> Text
escapeStringUsing [(Char, Text)]
escs
where escs :: [(Char, Text)]
escs = [Char] -> [(Char, Text)]
backslashEscapes [Char]
"{"
olMarker :: Parser Text ParserState Char
olMarker :: Parser Text ParserState Char
olMarker = do (Int
start, ListNumberStyle
style', ListNumberDelim
delim) <- ParserT
Text ParserState Identity (Int, ListNumberStyle, ListNumberDelim)
forall s (m :: * -> *).
Stream s m Char =>
ParserT s ParserState m (Int, ListNumberStyle, ListNumberDelim)
anyOrderedListMarker
if ListNumberDelim
delim ListNumberDelim -> ListNumberDelim -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberDelim
Period Bool -> Bool -> Bool
&&
(ListNumberStyle
style' ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
UpperAlpha Bool -> Bool -> Bool
|| (ListNumberStyle
style' ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
UpperRoman Bool -> Bool -> Bool
&&
Int
start Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int
1, Int
5, Int
10, Int
50, Int
100, Int
500, Int
1000]))
then Parser Text ParserState Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar Parser Text ParserState Char
-> Parser Text ParserState Char -> Parser Text ParserState Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser Text ParserState Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar
else Parser Text ParserState Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar
needsEscaping :: Text -> Bool
needsEscaping :: Text -> Bool
needsEscaping Text
s = Text -> Bool
beginsWithOrderedListMarker Text
s Bool -> Bool -> Bool
|| Text -> Bool
isBracketed Text
s
where
beginsWithOrderedListMarker :: Text -> Bool
beginsWithOrderedListMarker Text
str =
case Parser Text ParserState Char
-> ParserState -> [Char] -> Text -> Either ParseError Char
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> [Char] -> s -> Either ParseError a
runParser Parser Text ParserState Char
olMarker ParserState
defaultParserState [Char]
"para start" (Int -> Text -> Text
T.take Int
10 Text
str) of
Left ParseError
_ -> Bool
False
Right Char
_ -> Bool
True
isBracketed :: Text -> Bool
isBracketed Text
t
| Just (Char
'[', Text
t') <- Text -> Maybe (Char, Text)
T.uncons Text
t
, Just (Text
_, Char
']') <- Text -> Maybe (Text, Char)
T.unsnoc Text
t'
= Bool
True
| Bool
otherwise = Bool
False
blockToAsciiDoc :: PandocMonad m
=> WriterOptions
-> Block
-> ADW m (Doc Text)
blockToAsciiDoc :: WriterOptions -> Block -> ADW m (Doc Text)
blockToAsciiDoc WriterOptions
_ Block
Null = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
blockToAsciiDoc WriterOptions
opts (Div (Text
id',Text
"section":[Text]
_,[(Text, Text)]
_)
(Header Int
level (Text
_,[Text]
cls,[(Text, Text)]
kvs) [Inline]
ils : [Block]
xs)) = do
Doc Text
hdr <- WriterOptions -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ADW m (Doc Text)
blockToAsciiDoc WriterOptions
opts (Int -> (Text, [Text], [(Text, Text)]) -> [Inline] -> Block
Header Int
level (Text
id',[Text]
cls,[(Text, Text)]
kvs) [Inline]
ils)
Doc Text
rest <- WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
xs
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
hdr Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
rest
blockToAsciiDoc WriterOptions
opts (Plain [Inline]
inlines) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
inlines
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW 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
blockToAsciiDoc WriterOptions
opts (Para [Image (Text, [Text], [(Text, Text)])
attr [Inline]
alternate (Text
src,Text
tgt)])
| Just Text
tit <- Text -> Text -> Maybe Text
T.stripPrefix Text
"fig:" Text
tgt
= (\Doc Text
args -> Doc Text
"image::" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
args Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline) (Doc Text -> Doc Text) -> ADW m (Doc Text) -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
WriterOptions
-> (Text, [Text], [(Text, Text)])
-> [Inline]
-> Text
-> Text
-> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions
-> (Text, [Text], [(Text, Text)])
-> [Inline]
-> Text
-> Text
-> ADW m (Doc Text)
imageArguments WriterOptions
opts (Text, [Text], [(Text, Text)])
attr [Inline]
alternate Text
src Text
tit
blockToAsciiDoc WriterOptions
opts (Para [Inline]
inlines) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
inlines
let esc :: Doc Text
esc = if Text -> Bool
needsEscaping (Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing Doc Text
contents)
then [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"{empty}"
else Doc Text
forall a. Doc a
empty
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
esc 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
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (LineBlock [[Inline]]
lns) = do
let docify :: [Inline] -> StateT WriterState m (Doc Text)
docify [Inline]
line = if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
line
then Doc Text -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
blankline
else WriterOptions -> [Inline] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
line
let joinWithLinefeeds :: [Doc Text] -> Doc Text
joinWithLinefeeds = 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. 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
forall a. Doc a
cr
Doc Text
contents <- [Doc Text] -> Doc Text
joinWithLinefeeds ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Inline] -> ADW 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] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Inline] -> StateT WriterState m (Doc Text)
docify [[Inline]]
lns
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"[verse]" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"--" 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
$$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"--" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
_ b :: Block
b@(RawBlock Format
f Text
s)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"asciidoc" = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
s
| 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 -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
blockToAsciiDoc WriterOptions
_ Block
HorizontalRule =
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW 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. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"'''''" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (Header Int
level (Text
ident,[Text]
_,[(Text, Text)]
_) [Inline]
inlines) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
inlines
Set Text
ids <- (WriterState -> Set Text) -> StateT WriterState m (Set Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Set Text
autoIds
let autoId :: Text
autoId = Extensions -> [Inline] -> Set Text -> Text
uniqueIdent (WriterOptions -> Extensions
writerExtensions WriterOptions
opts) [Inline]
inlines Set Text
ids
(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{ autoIds :: Set Text
autoIds = Text -> Set Text -> Set Text
forall a. Ord a => a -> Set a -> Set a
Set.insert Text
autoId Set Text
ids }
let identifier :: Doc Text
identifier = if Text -> Bool
T.null Text
ident Bool -> Bool -> Bool
||
(Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_auto_identifiers WriterOptions
opts Bool -> Bool -> Bool
&& Text
ident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
autoId)
then Doc Text
forall a. Doc a
empty
else 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
ident Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]]"
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
identifier Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text -> Doc Text
forall a. IsString a => Doc a -> Doc a
nowrap ([Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text (Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char
'=') Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
space 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
<>
Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
_ (CodeBlock (Text
_,[Text]
classes,[(Text, Text)]
_) Text
str) = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text -> Doc Text
forall a. Doc a -> Doc a
flush (
if [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
classes
then Doc Text
"...." 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
$$ Doc Text
"...."
else Doc Text
attrs Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"----" 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
$$ Doc Text
"----")
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
where attrs :: Doc Text
attrs = 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 -> [Text] -> Text
T.intercalate Text
"," (Text
"source" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
classes)) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"
blockToAsciiDoc WriterOptions
opts (BlockQuote [Block]
blocks) = do
Doc Text
contents <- WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
blocks
let isBlock :: Block -> Bool
isBlock (BlockQuote [Block]
_) = Bool
True
isBlock Block
_ = Bool
False
let contents' :: Doc Text
contents' = if (Block -> Bool) -> [Block] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Block -> Bool
isBlock [Block]
blocks
then Doc Text
"--" 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
$$ Doc Text
"--"
else Doc Text
contents
let bar :: Doc Text
bar = [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"____"
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
bar Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
contents' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
bar Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (Table (Text, [Text], [(Text, Text)])
_ Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot) = do
let ([Inline]
caption, [Alignment]
aligns, [Double]
widths, [[Block]]
headers, [[[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
caption' <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
caption
let caption'' :: Doc Text
caption'' = if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
caption
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
caption' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
let isSimple :: Bool
isSimple = (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
let relativePercentWidths :: [Double]
relativePercentWidths = if Bool
isSimple
then [Double]
widths
else (Double -> Double) -> [Double] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Double]
widths) [Double]
widths
let widths'' :: [Integer]
widths'' :: [Integer]
widths'' = (Double -> Integer) -> [Double] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Integer) -> (Double -> Double) -> Double -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100)) [Double]
relativePercentWidths
let widths' :: [Integer]
widths' = case [Integer]
widths'' of
[Integer]
_ | Bool
isSimple -> [Integer]
widths''
(Integer
w:[Integer]
ws) | [Integer] -> Integer
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (Integer
wInteger -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
:[Integer]
ws) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
100
-> (Integer
100 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- [Integer] -> Integer
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer]
ws) Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: [Integer]
ws
[Integer]
ws -> [Integer]
ws
let totalwidth :: Integer
totalwidth :: Integer
totalwidth = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Integer) -> Double -> Integer
forall a b. (a -> b) -> a -> b
$ [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Double]
widths Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100
let colspec :: Alignment -> a -> [Char]
colspec Alignment
al a
wi = (case Alignment
al of
Alignment
AlignLeft -> [Char]
"<"
Alignment
AlignCenter -> [Char]
"^"
Alignment
AlignRight -> [Char]
">"
Alignment
AlignDefault -> [Char]
"") [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
if a
wi a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 then [Char]
"" else a -> [Char]
forall a. Show a => a -> [Char]
show a
wi [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"%"
let headerspec :: Doc Text
headerspec = 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]]
headers
then Doc Text
forall a. Doc a
empty
else [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"options=\"header\","
let widthspec :: Doc Text
widthspec = if Integer
totalwidth Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0
then Doc Text
forall a. Doc a
empty
else [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"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
doubleQuotes ([Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text ([Char] -> Doc Text) -> [Char] -> Doc Text
forall a b. (a -> b) -> a -> b
$ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
totalwidth [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"%")
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
","
let tablespec :: Doc Text
tablespec = [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"["
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
widthspec
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"cols="
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
doubleQuotes ([Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text ([Char] -> Doc Text) -> [Char] -> Doc Text
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
","
([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ (Alignment -> Integer -> [Char])
-> [Alignment] -> [Integer] -> [[Char]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Alignment -> Integer -> [Char]
forall a. (Eq a, Num a, Show a) => Alignment -> a -> [Char]
colspec [Alignment]
aligns [Integer]
widths')
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
","
Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
headerspec Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"]"
let makeCell :: [Block] -> StateT WriterState m (Doc Text)
makeCell [Plain [Inline]
x] = do Doc Text
d <- WriterOptions -> [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [[Inline] -> Block
Plain [Inline]
x]
Doc Text -> StateT WriterState m (Doc Text)
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
$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"|" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
d
makeCell [Para [Inline]
x] = [Block] -> StateT WriterState m (Doc Text)
makeCell [[Inline] -> Block
Plain [Inline]
x]
makeCell [] = Doc Text -> StateT WriterState m (Doc Text)
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
$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"|"
makeCell [Block]
bs = do Doc Text
d <- WriterOptions -> [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
bs
Doc Text -> StateT WriterState m (Doc Text)
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
$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"a|" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
d
let makeRow :: [[Block]] -> StateT WriterState m (Doc Text)
makeRow [[Block]]
cells = [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hsep ([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` ([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)
mapM [Block] -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Block] -> StateT WriterState m (Doc Text)
makeCell [[Block]]
cells
[Doc Text]
rows' <- ([[Block]] -> ADW 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]] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[[Block]] -> StateT WriterState m (Doc Text)
makeRow [[[Block]]]
rows
Doc Text
head' <- [[Block]] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[[Block]] -> StateT WriterState m (Doc Text)
makeRow [[Block]]
headers
let head'' :: Doc Text
head'' = 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]]
headers then Doc Text
forall a. Doc a
empty else Doc Text
head'
let colwidth :: Int
colwidth = if WriterOptions -> WrapOption
writerWrapText WriterOptions
opts WrapOption -> WrapOption -> Bool
forall a. Eq a => a -> a -> Bool
== WrapOption
WrapAuto
then WriterOptions -> Int
writerColumns WriterOptions
opts
else Int
100000
let maxwidth :: Int
maxwidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Int) -> [Doc Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Doc Text -> Int
forall a. (IsString a, HasChars a) => Doc a -> Int
offset (Doc Text
head'Doc Text -> [Doc Text] -> [Doc Text]
forall a. a -> [a] -> [a]
:[Doc Text]
rows')
let body :: Doc Text
body = if Int
maxwidth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
colwidth then [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vsep [Doc Text]
rows' else [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat [Doc Text]
rows'
let border :: Doc Text
border = [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"|==="
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$
Doc Text
caption'' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
tablespec Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
border Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
head'' 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
border Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (BulletList [[Block]]
items) = do
Bool
inlist <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
inList
(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{ inList :: Bool
inList = Bool
True }
[Doc Text]
contents <- ([Block] -> ADW 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 (WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
bulletListItemToAsciiDoc WriterOptions
opts) [[Block]]
items
(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{ inList :: Bool
inList = Bool
inlist }
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat [Doc Text]
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (OrderedList (Int
start, ListNumberStyle
sty, ListNumberDelim
_delim) [[Block]]
items) = do
let listStyle :: [Text]
listStyle = case ListNumberStyle
sty of
ListNumberStyle
DefaultStyle -> []
ListNumberStyle
Decimal -> [Text
"arabic"]
ListNumberStyle
Example -> []
ListNumberStyle
_ -> [Text -> Text
T.toLower (ListNumberStyle -> Text
forall a. Show a => a -> Text
tshow ListNumberStyle
sty)]
let listStart :: [Text]
listStart = [Text
"start=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
start | Int
start Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1]
let listoptions :: Doc Text
listoptions = case Text -> [Text] -> Text
T.intercalate Text
", " ([Text]
listStyle [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
listStart) of
Text
"" -> Doc Text
forall a. Doc a
empty
Text
x -> 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
x)
Bool
inlist <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
inList
(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{ inList :: Bool
inList = Bool
True }
[Doc Text]
contents <- ([Block] -> ADW 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 (WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
orderedListItemToAsciiDoc WriterOptions
opts) [[Block]]
items
(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{ inList :: Bool
inList = Bool
inlist }
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
listoptions Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat [Doc Text]
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (DefinitionList [([Inline], [[Block]])]
items) = do
Bool
inlist <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
inList
(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{ inList :: Bool
inList = Bool
True }
[Doc Text]
contents <- (([Inline], [[Block]]) -> ADW 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 (WriterOptions -> ([Inline], [[Block]]) -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> ([Inline], [[Block]]) -> ADW m (Doc Text)
definitionListItemToAsciiDoc WriterOptions
opts) [([Inline], [[Block]])]
items
(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{ inList :: Bool
inList = Bool
inlist }
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat [Doc Text]
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
blankline
blockToAsciiDoc WriterOptions
opts (Div (Text
ident,[Text]
classes,[(Text, Text)]
_) [Block]
bs) = do
let identifier :: Doc Text
identifier = 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
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
ident Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]]"
let admonitions :: [Text]
admonitions = [Text
"attention",Text
"caution",Text
"danger",Text
"error",Text
"hint",
Text
"important",Text
"note",Text
"tip",Text
"warning"]
Doc Text
contents <-
case [Text]
classes of
(Text
l:[Text]
_) | Text
l Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
admonitions -> do
let ([Block]
titleBs, [Block]
bodyBs) =
case [Block]
bs of
(Div (Text
_,[Text
"title"],[(Text, Text)]
_) [Block]
ts : [Block]
rest) -> ([Block]
ts, [Block]
rest)
[Block]
_ -> ([], [Block]
bs)
Doc Text
admonitionTitle <- if [Block] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Block]
titleBs
then Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Monoid a => a
mempty
else (Doc Text
"." Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>) (Doc Text -> Doc Text) -> ADW m (Doc Text) -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
titleBs
Doc Text
admonitionBody <- WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
bodyBs
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ 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 -> Text
T.toUpper Text
l) 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 -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
admonitionTitle Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text
"====" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp Doc Text
admonitionBody Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$
Doc Text
"===="
[Text]
_ -> WriterOptions -> [Block] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
bs
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
identifier 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
$$ Doc Text
forall a. Doc a
blankline
bulletListItemToAsciiDoc :: PandocMonad m
=> WriterOptions -> [Block] -> ADW m (Doc Text)
bulletListItemToAsciiDoc :: WriterOptions -> [Block] -> ADW m (Doc Text)
bulletListItemToAsciiDoc WriterOptions
opts [Block]
blocks = do
Int
lev <- (WriterState -> Int) -> StateT WriterState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
bulletListLevel
(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{ bulletListLevel :: Int
bulletListLevel = Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
Doc Text
contents <- (Doc Text -> Block -> ADW m (Doc Text))
-> Doc Text -> [Block] -> ADW m (Doc Text)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
addBlock WriterOptions
opts) Doc Text
forall a. Doc a
empty [Block]
blocks
(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{ bulletListLevel :: Int
bulletListLevel = Int
lev }
let marker :: Doc Text
marker = [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text (Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char
'*')
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
marker Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
" " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Block] -> Doc Text
listBegin [Block]
blocks 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
<> Doc Text
forall a. Doc a
cr
addBlock :: PandocMonad m
=> WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
addBlock :: WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
addBlock WriterOptions
opts Doc Text
d Block
b = do
Doc Text
x <- Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp (Doc Text -> Doc Text) -> ADW m (Doc Text) -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ADW m (Doc Text)
blockToAsciiDoc WriterOptions
opts Block
b
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$
case Block
b of
BulletList{} -> Doc Text
d 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
x
OrderedList{} -> Doc Text
d 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
x
Para (Math MathType
DisplayMath Text
_:[Inline]
_) -> Doc Text
d 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
x
Plain (Math MathType
DisplayMath Text
_:[Inline]
_) -> Doc Text
d 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
x
Para{} | Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
d -> Doc Text
x
Plain{} | Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
d -> Doc Text
x
Block
_ -> Doc Text
d 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
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"+" 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
x
listBegin :: [Block] -> Doc Text
listBegin :: [Block] -> Doc Text
listBegin [Block]
blocks =
case [Block]
blocks of
Para (Math MathType
DisplayMath Text
_:[Inline]
_) : [Block]
_ -> Doc Text
"{blank}"
Plain (Math MathType
DisplayMath Text
_:[Inline]
_) : [Block]
_ -> Doc Text
"{blank}"
Para [Inline]
_ : [Block]
_ -> Doc Text
forall a. Doc a
empty
Plain [Inline]
_ : [Block]
_ -> Doc Text
forall a. Doc a
empty
Block
_ : [Block]
_ -> Doc Text
"{blank}"
[] -> Doc Text
"{blank}"
orderedListItemToAsciiDoc :: PandocMonad m
=> WriterOptions
-> [Block]
-> ADW m (Doc Text)
orderedListItemToAsciiDoc :: WriterOptions -> [Block] -> ADW m (Doc Text)
orderedListItemToAsciiDoc WriterOptions
opts [Block]
blocks = do
Int
lev <- (WriterState -> Int) -> StateT WriterState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
orderedListLevel
(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{ orderedListLevel :: Int
orderedListLevel = Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
Doc Text
contents <- (Doc Text -> Block -> ADW m (Doc Text))
-> Doc Text -> [Block] -> ADW m (Doc Text)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Doc Text -> Block -> ADW m (Doc Text)
addBlock WriterOptions
opts) Doc Text
forall a. Doc a
empty [Block]
blocks
(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{ orderedListLevel :: Int
orderedListLevel = Int
lev }
let marker :: Doc Text
marker = [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text (Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char
'.')
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
marker Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
" " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Block] -> Doc Text
listBegin [Block]
blocks 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
<> Doc Text
forall a. Doc a
cr
definitionListItemToAsciiDoc :: PandocMonad m
=> WriterOptions
-> ([Inline],[[Block]])
-> ADW m (Doc Text)
definitionListItemToAsciiDoc :: WriterOptions -> ([Inline], [[Block]]) -> ADW m (Doc Text)
definitionListItemToAsciiDoc WriterOptions
opts ([Inline]
label, [[Block]]
defs) = do
Doc Text
labelText <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
label
Text
marker <- (WriterState -> Text) -> StateT WriterState m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
defListMarker
if Text
marker Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"::"
then (WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
st -> WriterState
st{ defListMarker :: Text
defListMarker = Text
";;"})
else (WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
st -> WriterState
st{ defListMarker :: Text
defListMarker = Text
"::"})
let divider :: Doc Text
divider = Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"+" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
let defsToAsciiDoc :: PandocMonad m => [Block] -> ADW m (Doc Text)
defsToAsciiDoc :: [Block] -> ADW m (Doc Text)
defsToAsciiDoc [Block]
ds = ([Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat ([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
divider ([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]
forall a b. (a -> b) -> [a] -> [b]
map Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp)
([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (Block -> ADW 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 (WriterOptions -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ADW m (Doc Text)
blockToAsciiDoc WriterOptions
opts) [Block]
ds
[Doc Text]
defs' <- ([Block] -> ADW 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] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Block] -> StateT WriterState m (Doc Text)
defsToAsciiDoc [[Block]]
defs
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
st -> WriterState
st{ defListMarker :: Text
defListMarker = Text
marker })
let contents :: Doc Text
contents = Int -> Doc Text -> Doc Text
forall a. IsString a => Int -> Doc a -> Doc a
nest Int
2 (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
vcat ([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
divider ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text) -> [Doc Text] -> [Doc Text]
forall a b. (a -> b) -> [a] -> [b]
map Doc Text -> Doc Text
forall a. Doc a -> Doc a
chomp [Doc Text]
defs'
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
labelText 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
marker 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
contents Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
blockListToAsciiDoc :: PandocMonad m
=> WriterOptions
-> [Block]
-> ADW m (Doc Text)
blockListToAsciiDoc :: WriterOptions -> [Block] -> ADW m (Doc Text)
blockListToAsciiDoc WriterOptions
opts [Block]
blocks =
[Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat ([Doc Text] -> Doc Text)
-> StateT WriterState m [Doc Text] -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (Block -> ADW 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 (WriterOptions -> Block -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ADW m (Doc Text)
blockToAsciiDoc WriterOptions
opts) [Block]
blocks
data SpacyLocation = End | Start
inlineListToAsciiDoc :: PandocMonad m =>
WriterOptions ->
[Inline] ->
ADW m (Doc Text)
inlineListToAsciiDoc :: WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst = do
Bool
oldIntraword <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
intraword
Bool -> ADW m ()
forall (m :: * -> *). PandocMonad m => Bool -> ADW m ()
setIntraword Bool
False
Doc Text
result <- [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Inline] -> StateT WriterState m (Doc Text)
go [Inline]
lst
Bool -> ADW m ()
forall (m :: * -> *). PandocMonad m => Bool -> ADW m ()
setIntraword Bool
oldIntraword
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
result
where go :: [Inline] -> StateT WriterState m (Doc Text)
go [] = Doc Text -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
go (Inline
y:Inline
x:[Inline]
xs)
| Bool -> Bool
not (SpacyLocation -> Inline -> Bool
isSpacy SpacyLocation
End Inline
y) = do
Doc Text
y' <- if SpacyLocation -> Inline -> Bool
isSpacy SpacyLocation
Start Inline
x
then WriterOptions -> Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts Inline
y
else StateT WriterState m (Doc Text) -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. PandocMonad m => ADW m a -> ADW m a
withIntraword (StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text))
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts Inline
y
Doc Text
x' <- StateT WriterState m (Doc Text) -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. PandocMonad m => ADW m a -> ADW m a
withIntraword (StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text))
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts Inline
x
Doc Text
xs' <- [Inline] -> StateT WriterState m (Doc Text)
go [Inline]
xs
Doc Text -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
y' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
xs')
| Bool -> Bool
not (SpacyLocation -> Inline -> Bool
isSpacy SpacyLocation
Start Inline
x) = do
Doc Text
y' <- StateT WriterState m (Doc Text) -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. PandocMonad m => ADW m a -> ADW m a
withIntraword (StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text))
-> StateT WriterState m (Doc Text)
-> StateT WriterState m (Doc Text)
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts Inline
y
Doc Text
xs' <- [Inline] -> StateT WriterState m (Doc Text)
go (Inline
xInline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
:[Inline]
xs)
Doc Text -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
y' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
xs')
go (Inline
x:[Inline]
xs) = do
Doc Text
x' <- WriterOptions -> Inline -> StateT WriterState m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts Inline
x
Doc Text
xs' <- [Inline] -> StateT WriterState m (Doc Text)
go [Inline]
xs
Doc Text -> StateT WriterState m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text
x' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
xs')
isSpacy :: SpacyLocation -> Inline -> Bool
isSpacy :: SpacyLocation -> Inline -> Bool
isSpacy SpacyLocation
_ Inline
Space = Bool
True
isSpacy SpacyLocation
_ Inline
LineBreak = Bool
True
isSpacy SpacyLocation
_ Inline
SoftBreak = Bool
True
isSpacy SpacyLocation
End (Str Text
xs) = case Text -> Maybe (Text, Char)
T.unsnoc Text
xs of
Just (Text
_, Char
c) -> Char -> Bool
isPunctuation Char
c Bool -> Bool -> Bool
|| Char -> Bool
isSpace Char
c
Maybe (Text, Char)
_ -> Bool
False
isSpacy SpacyLocation
Start (Str Text
xs)
| Just (Char
c, Text
_) <- Text -> Maybe (Char, Text)
T.uncons Text
xs = Char -> Bool
isPunctuation Char
c Bool -> Bool -> Bool
|| Char -> Bool
isSpace Char
c
isSpacy SpacyLocation
_ Inline
_ = Bool
False
setIntraword :: PandocMonad m => Bool -> ADW m ()
setIntraword :: Bool -> ADW m ()
setIntraword Bool
b = (WriterState -> WriterState) -> ADW m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> ADW m ())
-> (WriterState -> WriterState) -> ADW m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ intraword :: Bool
intraword = Bool
b }
withIntraword :: PandocMonad m => ADW m a -> ADW m a
withIntraword :: ADW m a -> ADW m a
withIntraword ADW m a
p = Bool -> ADW m ()
forall (m :: * -> *). PandocMonad m => Bool -> ADW m ()
setIntraword Bool
True ADW m () -> ADW m a -> ADW m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ADW m a
p ADW m a -> ADW m () -> ADW m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Bool -> ADW m ()
forall (m :: * -> *). PandocMonad m => Bool -> ADW m ()
setIntraword Bool
False
inlineToAsciiDoc :: PandocMonad m => WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc :: WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts (Emph [Strong [Inline]
xs]) =
WriterOptions -> Inline -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts ([Inline] -> Inline
Strong [[Inline] -> Inline
Emph [Inline]
xs])
inlineToAsciiDoc WriterOptions
opts (Emph [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Bool
isIntraword <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
intraword
let marker :: Doc Text
marker = if Bool
isIntraword then Doc Text
"__" else Doc Text
"_"
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
marker 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
<> Doc Text
marker
inlineToAsciiDoc WriterOptions
opts (Underline [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc 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
<> Doc Text
"+++"
inlineToAsciiDoc WriterOptions
opts (Strong [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Bool
isIntraword <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
intraword
let marker :: Doc Text
marker = if Bool
isIntraword then Doc Text
"**" else Doc Text
"*"
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
marker 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
<> Doc Text
marker
inlineToAsciiDoc WriterOptions
opts (Strikeout [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"[line-through]*" 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
<> Doc Text
"*"
inlineToAsciiDoc WriterOptions
opts (Superscript [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc 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
<> Doc Text
"^"
inlineToAsciiDoc WriterOptions
opts (Subscript [Inline]
lst) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc 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
<> Doc Text
"~"
inlineToAsciiDoc WriterOptions
opts (SmallCaps [Inline]
lst) = WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
inlineToAsciiDoc WriterOptions
opts (Quoted QuoteType
qt [Inline]
lst) = do
Bool
isAsciidoctor <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
asciidoctorVariant
WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts ([Inline] -> ADW m (Doc Text)) -> [Inline] -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$
case QuoteType
qt of
QuoteType
SingleQuote
| Bool
isAsciidoctor -> [Text -> Inline
Str Text
"'`"] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Inline]
lst [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"`'"]
| Bool
otherwise -> [Text -> Inline
Str Text
"`"] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Inline]
lst [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"'"]
QuoteType
DoubleQuote
| Bool
isAsciidoctor -> [Text -> Inline
Str Text
"\"`"] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Inline]
lst [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"`\""]
| Bool
otherwise -> [Text -> Inline
Str Text
"``"] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Inline]
lst [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"''"]
inlineToAsciiDoc WriterOptions
_ (Code (Text, [Text], [(Text, Text)])
_ Text
str) = do
Bool
isAsciidoctor <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
asciidoctorVariant
let contents :: Doc Text
contents = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal ([(Char, Text)] -> Text -> Text
escapeStringUsing ([Char] -> [(Char, Text)]
backslashEscapes [Char]
"`") Text
str)
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$
if Bool
isAsciidoctor
then [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [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
<> Doc Text
"+`"
else [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [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
<> Doc Text
"`"
inlineToAsciiDoc WriterOptions
_ (Str Text
str) = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW 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 -> Text
escapeString Text
str
inlineToAsciiDoc WriterOptions
_ (Math MathType
InlineMath Text
str) = do
Bool
isAsciidoctor <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
asciidoctorVariant
(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{ hasMath :: Bool
hasMath = Bool
True }
let content :: Doc Text
content = if Bool
isAsciidoctor
then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
else 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"$"
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"latexmath:[" 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
<> Doc Text
"]"
inlineToAsciiDoc WriterOptions
_ (Math MathType
DisplayMath Text
str) = do
Bool
isAsciidoctor <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
asciidoctorVariant
(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{ hasMath :: Bool
hasMath = Bool
True }
let content :: Doc Text
content = if Bool
isAsciidoctor
then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
else 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\]"
Bool
inlist <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
inList
let sepline :: Doc Text
sepline = if Bool
inlist
then [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"+"
else Doc Text
forall a. Doc a
blankline
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$
(Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
sepline) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"[latexmath]" Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
$$ Doc Text
"++++" 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
$$ Doc Text
"++++" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
inlineToAsciiDoc WriterOptions
_ il :: Inline
il@(RawInline Format
f Text
s)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
"asciidoc" = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
s
| 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 -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToAsciiDoc WriterOptions
_ Inline
LineBreak = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
" +" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
inlineToAsciiDoc WriterOptions
_ Inline
Space = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
inlineToAsciiDoc WriterOptions
opts Inline
SoftBreak =
case WriterOptions -> WrapOption
writerWrapText WriterOptions
opts of
WrapOption
WrapAuto -> Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
WrapOption
WrapPreserve -> Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
cr
WrapOption
WrapNone -> Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
space
inlineToAsciiDoc WriterOptions
opts (Cite [Citation]
_ [Inline]
lst) = WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
lst
inlineToAsciiDoc WriterOptions
opts (Link (Text, [Text], [(Text, Text)])
_ [Inline]
txt (Text
src, Text
_tit)) = do
Doc Text
linktext <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
txt
let isRelative :: Bool
isRelative = (Char -> Bool) -> Text -> Bool
T.all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':') Text
src
let prefix :: Doc Text
prefix = if Bool
isRelative
then [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"link:"
else Doc Text
forall a. Doc a
empty
let srcSuffix :: Text
srcSuffix = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
src (Text -> Text -> Maybe Text
T.stripPrefix Text
"mailto:" Text
src)
let useAuto :: Bool
useAuto = case [Inline]
txt of
[Str Text
s] | Text -> Text
escapeURI Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
srcSuffix -> Bool
True
[Inline]
_ -> Bool
False
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Bool
useAuto
then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
srcSuffix
else Doc Text
prefix 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
src 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
linktext Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"
inlineToAsciiDoc WriterOptions
opts (Image (Text, [Text], [(Text, Text)])
attr [Inline]
alternate (Text
src, Text
tit)) =
(Doc Text
"image:" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>) (Doc Text -> Doc Text) -> ADW m (Doc Text) -> ADW m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions
-> (Text, [Text], [(Text, Text)])
-> [Inline]
-> Text
-> Text
-> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions
-> (Text, [Text], [(Text, Text)])
-> [Inline]
-> Text
-> Text
-> ADW m (Doc Text)
imageArguments WriterOptions
opts (Text, [Text], [(Text, Text)])
attr [Inline]
alternate Text
src Text
tit
inlineToAsciiDoc WriterOptions
opts (Note [Para [Inline]
inlines]) =
WriterOptions -> Inline -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ADW m (Doc Text)
inlineToAsciiDoc WriterOptions
opts ([Block] -> Inline
Note [[Inline] -> Block
Plain [Inline]
inlines])
inlineToAsciiDoc WriterOptions
opts (Note [Plain [Inline]
inlines]) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
inlines
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text [Char]
"footnote:[" 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
<> Doc Text
"]"
inlineToAsciiDoc WriterOptions
_ (Note [Block]
_) = Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
"[multiblock footnote omitted]"
inlineToAsciiDoc WriterOptions
opts (Span (Text
ident,[Text]
classes,[(Text, Text)]
_) [Inline]
ils) = do
Doc Text
contents <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
ils
Bool
isIntraword <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
intraword
let marker :: Doc Text
marker = if Bool
isIntraword then Doc Text
"##" else Doc Text
"#"
if Text -> Bool
T.null Text
ident Bool -> Bool -> Bool
&& [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
classes
then Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
contents
else do
let modifier :: Doc Text
modifier = 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
T.unwords ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ident | Bool -> Bool
not (Text -> Bool
T.null Text
ident)] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) [Text]
classes
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
modifier Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
marker 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
<> Doc Text
marker
imageArguments :: PandocMonad m => WriterOptions ->
Attr -> [Inline] -> Text -> Text ->
ADW m (Doc Text)
imageArguments :: WriterOptions
-> (Text, [Text], [(Text, Text)])
-> [Inline]
-> Text
-> Text
-> ADW m (Doc Text)
imageArguments WriterOptions
opts (Text, [Text], [(Text, Text)])
attr [Inline]
altText Text
src Text
title = do
let txt :: [Inline]
txt = if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
altText Bool -> Bool -> Bool
|| ([Inline]
altText [Inline] -> [Inline] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text -> Inline
Str Text
""])
then [Text -> Inline
Str Text
"image"]
else [Inline]
altText
Doc Text
linktext <- WriterOptions -> [Inline] -> ADW m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc WriterOptions
opts [Inline]
txt
let linktitle :: Doc Text
linktitle = if Text -> Bool
T.null Text
title
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
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
title Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\""
showDim :: Direction -> [Doc Text]
showDim Direction
dir = case Direction -> (Text, [Text], [(Text, Text)]) -> Maybe Dimension
dimension Direction
dir (Text, [Text], [(Text, Text)])
attr of
Just (Percent Double
a) ->
[Doc Text
"scaledwidth=" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text (Dimension -> [Char]
forall a. Show a => a -> [Char]
show (Double -> Dimension
Percent Double
a))]
Just Dimension
dim ->
[[Char] -> Doc Text
forall a. HasChars a => [Char] -> Doc a
text (Direction -> [Char]
forall a. Show a => a -> [Char]
show Direction
dir) 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 (WriterOptions -> Dimension -> Text
showInPixel WriterOptions
opts 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 -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [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)
Doc Text -> ADW m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ADW m (Doc Text)) -> Doc Text -> ADW m (Doc Text)
forall a b. (a -> b) -> a -> b
$ 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
"[" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
linktext Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
linktitle 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
"]"