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

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable
-}
module Text.Pandoc.Writers.Markdown.Inline (
  inlineListToMarkdown
  ) where
import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Char (isAlphaNum, isDigit)
import Data.List (find, intersperse)
import Data.List.NonEmpty (nonEmpty)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Network.HTTP (urlEncode)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space)
import Text.DocLayout
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Walk
import Text.Pandoc.Writers.HTML (writeHtml5String)
import Text.Pandoc.Writers.Math (texMathToInlines)
import Text.Pandoc.XML (toHtml5Entities)
import Data.Coerce (coerce)
import Text.Pandoc.Writers.Markdown.Types (MarkdownVariant(..),
                                           WriterState(..),
                                           WriterEnv(..), MD)

-- | Escape special characters for Markdown.
escapeText :: WriterOptions -> Text -> Text
escapeText :: WriterOptions -> Text -> Text
escapeText WriterOptions
opts = String -> Text
T.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
go (String -> String) -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
  where
  go :: String -> String
go [] = []
  go (Char
c:String
cs) =
    case Char
c of
       Char
'<' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_all_symbols_escapable WriterOptions
opts ->
              Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'<' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
cs
           | Bool
otherwise -> String
"&lt;" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
go String
cs
       Char
'>' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_all_symbols_escapable WriterOptions
opts ->
              Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'>' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
cs
           | Bool
otherwise -> String
"&gt;" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
go String
cs
       Char
'@' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_citations WriterOptions
opts ->
               case String
cs of
                    (Char
d:String
_)
                      | Char -> Bool
isAlphaNum Char
d Bool -> Bool -> Bool
|| Char
d Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
                         -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'@'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
                    String
_ -> Char
'@'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
_ | Char
c Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'\\',Char
'`',Char
'*',Char
'_',Char
'[',Char
']',Char
'#'] ->
              Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'|' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_pipe_tables WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'|'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'^' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_superscript WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'^'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'~' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_subscript WriterOptions
opts Bool -> Bool -> Bool
||
             Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_strikeout WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'~'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'$' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_dollars WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'$'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'\'' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'\''Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'"' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'"'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'-' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts ->
              case String
cs of
                   Char
'-':String
_ -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'-'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
                   String
_     -> Char
'-'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
'.' | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts ->
              case String
cs of
                   Char
'.':Char
'.':String
rest -> Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'.'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'.'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
'.'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
rest
                   String
_            -> Char
'.'Char -> String -> String
forall a. a -> [a] -> [a]
:String -> String
go String
cs
       Char
_   -> case String
cs of
                Char
'_':Char
x:String
xs
                  | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_intraword_underscores WriterOptions
opts
                  , Char -> Bool
isAlphaNum Char
c
                  , Char -> Bool
isAlphaNum Char
x -> Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: Char
'_' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
xs
                String
_                -> Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
go String
cs

attrsToMarkdown :: Attr -> Doc Text
attrsToMarkdown :: Attr -> Doc Text
attrsToMarkdown Attr
attribs = Doc Text -> Doc Text
forall a. HasChars a => Doc a -> Doc a
braces (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hsep [Doc Text
attribId, Doc Text
attribClasses, Doc Text
attribKeys]
        where attribId :: Doc Text
attribId = case Attr
attribs of
                                (Text
"",[Text]
_,[(Text, Text)]
_) -> Doc Text
forall a. Doc a
empty
                                (Text
i,[Text]
_,[(Text, Text)]
_)  -> Doc Text
"#" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Text -> Doc Text
escAttr Text
i
              attribClasses :: Doc Text
attribClasses = case Attr
attribs of
                                (Text
_,[],[(Text, Text)]
_) -> Doc Text
forall a. Doc a
empty
                                (Text
_,[Text]
cs,[(Text, Text)]
_) -> [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hsep ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$
                                            (Text -> Doc Text) -> [Text] -> [Doc Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Doc Text
escAttr (Text -> Doc Text) -> (Text -> Text) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"."Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>))
                                            [Text]
cs
              attribKeys :: Doc Text
attribKeys = case Attr
attribs of
                                (Text
_,[Text]
_,[]) -> Doc Text
forall a. Doc a
empty
                                (Text
_,[Text]
_,[(Text, Text)]
ks) -> [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hsep ([Doc Text] -> Doc Text) -> [Doc Text] -> Doc Text
forall a b. (a -> b) -> a -> b
$
                                            ((Text, Text) -> Doc Text) -> [(Text, Text)] -> [Doc Text]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
k,Text
v) -> Text -> Doc Text
escAttr Text
k
                                              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
escAttr Text
v Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\"") [(Text, Text)]
ks
              escAttr :: Text -> Doc Text
escAttr          = [Doc Text] -> Doc Text
forall a. Monoid a => [a] -> a
mconcat ([Doc Text] -> Doc Text)
-> (Text -> [Doc Text]) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Doc Text) -> String -> [Doc Text]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Doc Text
escAttrChar (String -> [Doc Text]) -> (Text -> String) -> Text -> [Doc Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
              escAttrChar :: Char -> Doc Text
escAttrChar Char
'"'  = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\\""
              escAttrChar Char
'\\' = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"\\\\"
              escAttrChar Char
c    = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c

linkAttributes :: WriterOptions -> Attr -> Doc Text
linkAttributes :: WriterOptions -> Attr -> Doc Text
linkAttributes WriterOptions
opts Attr
attr =
  if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_link_attributes WriterOptions
opts Bool -> Bool -> Bool
&& Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
nullAttr
     then Attr -> Doc Text
attrsToMarkdown Attr
attr
     else Doc Text
forall a. Doc a
empty

getKey :: Doc Text -> Key
getKey :: Doc Text -> Key
getKey = Text -> Key
toKey (Text -> Key) -> (Doc Text -> Text) -> Doc Text -> Key
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

findUsableIndex :: [Text] -> Int -> Int
findUsableIndex :: [Text] -> Int -> Int
findUsableIndex [Text]
lbls Int
i = if Int -> Text
forall a. Show a => a -> Text
tshow Int
i Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
lbls
                         then [Text] -> Int -> Int
findUsableIndex [Text]
lbls (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
                         else Int
i

getNextIndex :: PandocMonad m => MD m Int
getNextIndex :: MD m Int
getNextIndex = do
  Refs
prevRefs <- (WriterState -> Refs)
-> ReaderT WriterEnv (StateT WriterState m) Refs
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Refs
stPrevRefs
  Refs
refs <- (WriterState -> Refs)
-> ReaderT WriterEnv (StateT WriterState m) Refs
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Refs
stRefs
  Int
i <- (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int -> Int) -> MD m Int -> MD m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterState -> Int) -> MD m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
stLastIdx
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stLastIdx :: Int
stLastIdx = Int
i }
  let refLbls :: [Text]
refLbls = ((Text, (Text, Text), Attr) -> Text) -> Refs -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
r,(Text, Text)
_,Attr
_) -> Text
r) (Refs -> [Text]) -> Refs -> [Text]
forall a b. (a -> b) -> a -> b
$ Refs
prevRefs Refs -> Refs -> Refs
forall a. [a] -> [a] -> [a]
++ Refs
refs
  Int -> MD m Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> MD m Int) -> Int -> MD m Int
forall a b. (a -> b) -> a -> b
$ [Text] -> Int -> Int
findUsableIndex [Text]
refLbls Int
i

-- | Get reference for target; if none exists, create unique one and return.
--   Prefer label if possible; otherwise, generate a unique key.
getReference :: PandocMonad m => Attr -> Doc Text -> Target -> MD m Text
getReference :: Attr -> Doc Text -> (Text, Text) -> MD m Text
getReference Attr
attr Doc Text
label (Text, Text)
target = do
  Refs
refs <- (WriterState -> Refs)
-> ReaderT WriterEnv (StateT WriterState m) Refs
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Refs
stRefs
  case ((Text, (Text, Text), Attr) -> Bool)
-> Refs -> Maybe (Text, (Text, Text), Attr)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\(Text
_,(Text, Text)
t,Attr
a) -> (Text, Text)
t (Text, Text) -> (Text, Text) -> Bool
forall a. Eq a => a -> a -> Bool
== (Text, Text)
target Bool -> Bool -> Bool
&& Attr
a Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
attr) Refs
refs of
    Just (Text
ref, (Text, Text)
_, Attr
_) -> Text -> MD m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
ref
    Maybe (Text, (Text, Text), Attr)
Nothing       -> do
      Map Key (Map ((Text, Text), Attr) Int)
keys <- (WriterState -> Map Key (Map ((Text, Text), Attr) Int))
-> ReaderT
     WriterEnv
     (StateT WriterState m)
     (Map Key (Map ((Text, Text), Attr) Int))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Key (Map ((Text, Text), Attr) Int)
stKeys
      let key :: Key
key = Doc Text -> Key
getKey Doc Text
label
      let rawkey :: Text
rawkey = Key -> Text
coerce Key
key
      case Key
-> Map Key (Map ((Text, Text), Attr) Int)
-> Maybe (Map ((Text, Text), Attr) Int)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Key
key Map Key (Map ((Text, Text), Attr) Int)
keys of
           Maybe (Map ((Text, Text), Attr) Int)
Nothing -> do -- no other refs with this label
             (Text
lab', Int
idx) <- if Text -> Bool
T.null Text
rawkey Bool -> Bool -> Bool
||
                                 Text -> Int
T.length Text
rawkey Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
999 Bool -> Bool -> Bool
||
                                 (Char -> Bool) -> Text -> Bool
T.any (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'[' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
']') Text
rawkey
                               then do
                                 Int
i <- MD m Int
forall (m :: * -> *). PandocMonad m => MD m Int
getNextIndex
                                 (Text, Int) -> ReaderT WriterEnv (StateT WriterState m) (Text, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Text
forall a. Show a => a -> Text
tshow Int
i, Int
i)
                               else
                                 (Text, Int) -> ReaderT WriterEnv (StateT WriterState m) (Text, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing Doc Text
label, Int
0)
             (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
s -> WriterState
s{
               stRefs :: Refs
stRefs = (Text
lab', (Text, Text)
target, Attr
attr) (Text, (Text, Text), Attr) -> Refs -> Refs
forall a. a -> [a] -> [a]
: Refs
refs,
               stKeys :: Map Key (Map ((Text, Text), Attr) Int)
stKeys = Key
-> Map ((Text, Text), Attr) Int
-> Map Key (Map ((Text, Text), Attr) Int)
-> Map Key (Map ((Text, Text), Attr) Int)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Doc Text -> Key
getKey Doc Text
label)
                           (((Text, Text), Attr)
-> Int
-> Map ((Text, Text), Attr) Int
-> Map ((Text, Text), Attr) Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ((Text, Text)
target, Attr
attr) Int
idx Map ((Text, Text), Attr) Int
forall a. Monoid a => a
mempty)
                                 (WriterState -> Map Key (Map ((Text, Text), Attr) Int)
stKeys WriterState
s) })
             Text -> MD m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
lab'

           Just Map ((Text, Text), Attr) Int
km ->    -- we have refs with this label
             case ((Text, Text), Attr) -> Map ((Text, Text), Attr) Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ((Text, Text)
target, Attr
attr) Map ((Text, Text), Attr) Int
km of
                  Just Int
i -> do
                    let lab' :: Text
lab' = 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 -> Text
forall a b. (a -> b) -> a -> b
$
                               Doc Text
label Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
                                           then Doc Text
forall a. Monoid a => a
mempty
                                           else Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Int -> Text
forall a. Show a => a -> Text
tshow Int
i)
                    -- make sure it's in stRefs; it may be
                    -- a duplicate that was printed in a previous
                    -- block:
                    Bool
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Text
lab', (Text, Text)
target, Attr
attr) (Text, (Text, Text), Attr) -> Refs -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Refs
refs) (ReaderT WriterEnv (StateT WriterState m) ()
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$
                       (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
s -> WriterState
s{
                         stRefs :: Refs
stRefs = (Text
lab', (Text, Text)
target, Attr
attr) (Text, (Text, Text), Attr) -> Refs -> Refs
forall a. a -> [a] -> [a]
: Refs
refs })
                    Text -> MD m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
lab'
                  Maybe Int
Nothing -> do -- but this one is to a new target
                    Int
i <- MD m Int
forall (m :: * -> *). PandocMonad m => MD m Int
getNextIndex
                    let lab' :: Text
lab' = Int -> Text
forall a. Show a => a -> Text
tshow Int
i
                    (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
s -> WriterState
s{
                       stRefs :: Refs
stRefs = (Text
lab', (Text, Text)
target, Attr
attr) (Text, (Text, Text), Attr) -> Refs -> Refs
forall a. a -> [a] -> [a]
: Refs
refs,
                       stKeys :: Map Key (Map ((Text, Text), Attr) Int)
stKeys = Key
-> Map ((Text, Text), Attr) Int
-> Map Key (Map ((Text, Text), Attr) Int)
-> Map Key (Map ((Text, Text), Attr) Int)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Key
key
                                   (((Text, Text), Attr)
-> Int
-> Map ((Text, Text), Attr) Int
-> Map ((Text, Text), Attr) Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ((Text, Text)
target, Attr
attr) Int
i Map ((Text, Text), Attr) Int
km)
                                         (WriterState -> Map Key (Map ((Text, Text), Attr) Int)
stKeys WriterState
s) })
                    Text -> MD m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
lab'

-- | Convert list of Pandoc inline elements to markdown.
inlineListToMarkdown :: PandocMonad m => WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown :: WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst = do
  Bool
inlist <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envInList
  [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
[Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
go (if Bool
inlist then [Inline] -> [Inline]
avoidBadWrapsInList [Inline]
lst else [Inline]
lst)
  where go :: [Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
go [] = Doc Text -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
        go (x :: Inline
x@Math{}:y :: Inline
y@(Str Text
t):[Inline]
zs)
          | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit (Int -> Text -> Text
T.take Int
1 Text
t) -- starts with digit -- see #7058
          = (Doc Text -> Doc Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
(<>) (WriterOptions
-> Inline -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts Inline
x)
              ([Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
go (Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"html") Text
"<!-- -->" Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
y Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
zs))
        go (Inline
i:[Inline]
is) = case Inline
i of
            Link {} -> case [Inline]
is of
                -- If a link is followed by another link, or '[', '(' or ':'
                -- then we don't shortcut
                Link {}:[Inline]
_                                       -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
Space:Link {}:[Inline]
_                                 -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
Space:(Str(Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_                -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
Space:(RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_       -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
Space:(Cite [Citation]
_ [Inline]
_):[Inline]
_                              -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
SoftBreak:Link {}:[Inline]
_                             -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
SoftBreak:(Str(Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_            -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
SoftBreak:(RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_   -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
SoftBreak:(Cite [Citation]
_ [Inline]
_):[Inline]
_                          -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
LineBreak:Link {}:[Inline]
_                             -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
LineBreak:(Str(Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_            -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
LineBreak:(RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_   -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Inline
LineBreak:(Cite [Citation]
_ [Inline]
_):[Inline]
_                          -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                (Cite [Citation]
_ [Inline]
_):[Inline]
_                                    -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Str (Text -> Maybe Char
thead -> Just Char
'['):[Inline]
_                       -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Str (Text -> Maybe Char
thead -> Just Char
'('):[Inline]
_                       -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                Str (Text -> Maybe Char
thead -> Just Char
':'):[Inline]
_                       -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                (RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
'[')):[Inline]
_             -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                (RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
'(')):[Inline]
_             -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                (RawInline Format
_ (Text -> Maybe Char
thead -> Just Char
':')):[Inline]
_             -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                (RawInline Format
_ (Text -> Text -> Maybe Text
T.stripPrefix Text
" [" -> Just Text
_ )):[Inline]
_ -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable
                [Inline]
_                                               -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
shortcutable
            Inline
_ -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
shortcutable
          where shortcutable :: ReaderT WriterEnv (StateT WriterState m) (Doc Text)
shortcutable = (Doc Text -> Doc Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
(<>) (WriterOptions
-> Inline -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts Inline
i) ([Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
go [Inline]
is)
                unshortcutable :: ReaderT WriterEnv (StateT WriterState m) (Doc Text)
unshortcutable = do
                    Doc Text
iMark <- (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local
                             (\WriterEnv
env -> WriterEnv
env { envRefShortcutable :: Bool
envRefShortcutable = Bool
False })
                             (WriterOptions
-> Inline -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts Inline
i)
                    (Doc Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Doc Text
iMark Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>) ([Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
go [Inline]
is)
                thead :: Text -> Maybe Char
thead = ((Char, Text) -> Char) -> Maybe (Char, Text) -> Maybe Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Char, Text) -> Char
forall a b. (a, b) -> a
fst (Maybe (Char, Text) -> Maybe Char)
-> (Text -> Maybe (Char, Text)) -> Text -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe (Char, Text)
T.uncons

isSp :: Inline -> Bool
isSp :: Inline -> Bool
isSp Inline
Space     = Bool
True
isSp Inline
SoftBreak = Bool
True
isSp Inline
_         = Bool
False

avoidBadWrapsInList :: [Inline] -> [Inline]
avoidBadWrapsInList :: [Inline] -> [Inline]
avoidBadWrapsInList [] = []
avoidBadWrapsInList (Inline
s:Str (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'>',Text
cs)):[Inline]
xs) | Inline -> Bool
isSp Inline
s =
  Text -> Inline
Str (Text
" >" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
avoidBadWrapsInList [Inline]
xs
avoidBadWrapsInList [Inline
s, Str (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
c, Text
cs))]
  | Text -> Bool
T.null Text
cs Bool -> Bool -> Bool
&& Inline -> Bool
isSp Inline
s Bool -> Bool -> Bool
&& Char
c Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'-',Char
'*',Char
'+'] = [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
' ', Char
c]]
avoidBadWrapsInList (Inline
s:Str (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
c, Text
cs)):Inline
Space:[Inline]
xs)
  | Text -> Bool
T.null Text
cs Bool -> Bool -> Bool
&& Inline -> Bool
isSp Inline
s Bool -> Bool -> Bool
&& Char
c Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'-',Char
'*',Char
'+'] =
    Text -> Inline
Str (String -> Text
T.pack [Char
' ', Char
c]) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
Space Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
avoidBadWrapsInList [Inline]
xs
avoidBadWrapsInList (Inline
s:Str Text
cs:Inline
Space:[Inline]
xs)
  | Inline -> Bool
isSp Inline
s Bool -> Bool -> Bool
&& Text -> Bool
isOrderedListMarker Text
cs =
    Text -> Inline
Str (Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
Space Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
avoidBadWrapsInList [Inline]
xs
avoidBadWrapsInList [Inline
s, Str Text
cs]
  | Inline -> Bool
isSp Inline
s Bool -> Bool -> Bool
&& Text -> Bool
isOrderedListMarker Text
cs = [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs]
avoidBadWrapsInList (Inline
x:[Inline]
xs) = Inline
x Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
avoidBadWrapsInList [Inline]
xs

isOrderedListMarker :: Text -> Bool
isOrderedListMarker :: Text -> Bool
isOrderedListMarker Text
xs = Bool -> Bool
not (Text -> Bool
T.null Text
xs) Bool -> Bool -> Bool
&& (Text -> Char
T.last Text
xs Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'.',Char
')']) Bool -> Bool -> Bool
&&
              Either ParseError () -> Bool
forall a b. Either a b -> Bool
isRight (Parsec Text ParserState ()
-> ParserState -> String -> Text -> Either ParseError ()
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
runParser (ParserT Text ParserState Identity ListAttributes
forall s (m :: * -> *).
Stream s m Char =>
ParserT s ParserState m ListAttributes
anyOrderedListMarker ParserT Text ParserState Identity ListAttributes
-> Parsec Text ParserState () -> Parsec Text ParserState ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parsec Text ParserState ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
                       ParserState
defaultParserState String
"" Text
xs)
 where
  isRight :: Either a b -> Bool
isRight (Right b
_) = Bool
True
  isRight (Left  a
_) = Bool
False

-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: PandocMonad m => WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown :: WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts (Span (Text
"",[Text
"emoji"],[(Text, Text)]
kvs) [Str Text
s]) =
  case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"data-emoji" [(Text, Text)]
kvs of
       Just Text
emojiname | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_emoji WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
emojiname Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
":"
       Maybe Text
_ -> WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts (Text -> Inline
Str Text
s)
inlineToMarkdown WriterOptions
opts (Span Attr
attrs [Inline]
ils) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
ils
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case Attr
attrs of
             (Text
_,[Text
"csl-block"],[(Text, Text)]
_) -> (Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>)
             (Text
_,[Text
"csl-left-margin"],[(Text, Text)]
_) -> (Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>)
             (Text
_,[Text
"csl-indent"],[(Text, Text)]
_) -> (Doc Text
forall a. Doc a
cr Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>)
             Attr
_ -> Doc Text -> Doc Text
forall a. a -> a
id
         (Doc Text -> Doc Text) -> Doc Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ case MarkdownVariant
variant of
                MarkdownVariant
PlainText -> Doc Text
contents
                MarkdownVariant
_     | Attr
attrs Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
nullAttr -> Doc Text
contents
                      | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_bracketed_spans WriterOptions
opts ->
                        let attrs' :: Doc Text
attrs' = if Attr
attrs Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
nullAttr
                                        then Attr -> Doc Text
attrsToMarkdown Attr
attrs
                                        else Doc Text
forall a. Doc a
empty
                        in 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
"]" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
attrs'
                      | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts Bool -> Bool -> Bool
||
                        Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_native_spans WriterOptions
opts ->
                        Text -> Attr -> Doc Text
forall a. HasChars a => Text -> Attr -> Doc a
tagWithAttrs Text
"span" Attr
attrs 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
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"</span>"
                      | Bool
otherwise -> Doc Text
contents
inlineToMarkdown WriterOptions
_ (Emph []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Emph [Inline]
lst) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case MarkdownVariant
variant of
             MarkdownVariant
PlainText
               | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_gutenberg WriterOptions
opts -> 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
"_"
               | Bool
otherwise ->  Doc Text
contents
             MarkdownVariant
_ -> 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
"*"
inlineToMarkdown WriterOptions
_ (Underline []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Underline [Inline]
lst) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  case MarkdownVariant
variant of
    MarkdownVariant
PlainText -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
contents
    MarkdownVariant
_     | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_bracketed_spans WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
"]" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"{.ul}"
          | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_native_spans WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Attr -> Doc Text
forall a. HasChars a => Text -> Attr -> Doc a
tagWithAttrs Text
"span" (Text
"", [Text
"underline"], [])
              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
<> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"</span>"
          | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"<u>" 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
"</u>"
          | Bool
otherwise -> WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts ([Inline] -> Inline
Emph [Inline]
lst)
inlineToMarkdown WriterOptions
_ (Strong []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Strong [Inline]
lst) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  case MarkdownVariant
variant of
    MarkdownVariant
PlainText ->
             WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts ([Inline] -> MD m (Doc Text)) -> [Inline] -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$
               if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_gutenberg WriterOptions
opts
                  then [Inline] -> [Inline]
forall a. Walkable Inline a => a -> a
capitalize [Inline]
lst
                  else [Inline]
lst
    MarkdownVariant
_ -> do
       Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
       Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
"**"
inlineToMarkdown WriterOptions
_ (Strikeout []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Strikeout [Inline]
lst) = do
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_strikeout WriterOptions
opts
              then 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
"~~"
              else if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts
                       then Doc Text
"<s>" 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
"</s>"
                       else Doc Text
contents
inlineToMarkdown WriterOptions
_ (Superscript []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Superscript [Inline]
lst) =
  (WriterEnv -> WriterEnv) -> MD m (Doc Text) -> MD m (Doc Text)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env {envEscapeSpaces :: Bool
envEscapeSpaces = WriterEnv -> MarkdownVariant
envVariant WriterEnv
env MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
== MarkdownVariant
Markdown}) (MD m (Doc Text) -> MD m (Doc Text))
-> MD m (Doc Text) -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ do
    Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
    if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_superscript WriterOptions
opts
       then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
"^"
       else if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts
                then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"<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
<> Doc Text
"</sup>"
                else
                  case (Inline -> Maybe Inline) -> [Inline] -> Maybe [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Inline -> Maybe Inline
toSuperscriptInline [Inline]
lst of
                    Just [Inline]
xs' | Bool -> Bool
not (WriterOptions -> Bool
writerPreferAscii WriterOptions
opts)
                      -> WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
xs'
                    Maybe [Inline]
_ -> do
                      let rendered :: Text
rendered = 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
                      Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$
                        case (Char -> Maybe Char) -> String -> Maybe String
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Char -> Maybe Char
toSuperscript (Text -> String
T.unpack Text
rendered) of
                           Just String
r  -> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
r
                           Maybe String
Nothing -> 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 -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rendered Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
inlineToMarkdown WriterOptions
_ (Subscript []) = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
empty
inlineToMarkdown WriterOptions
opts (Subscript [Inline]
lst) =
  (WriterEnv -> WriterEnv) -> MD m (Doc Text) -> MD m (Doc Text)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env {envEscapeSpaces :: Bool
envEscapeSpaces = WriterEnv -> MarkdownVariant
envVariant WriterEnv
env MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
== MarkdownVariant
Markdown}) (MD m (Doc Text) -> MD m (Doc Text))
-> MD m (Doc Text) -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ do
    Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
    if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_subscript WriterOptions
opts
       then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
"~"
       else if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts
                then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
"<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
<> Doc Text
"</sub>"
                else
                  case (Inline -> Maybe Inline) -> [Inline] -> Maybe [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Inline -> Maybe Inline
toSubscriptInline [Inline]
lst of
                    Just [Inline]
xs' | Bool -> Bool
not (WriterOptions -> Bool
writerPreferAscii WriterOptions
opts)
                      -> WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
xs'
                    Maybe [Inline]
_ -> do
                      let rendered :: Text
rendered = 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
                      Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$
                        case (Char -> Maybe Char) -> String -> Maybe String
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Char -> Maybe Char
toSuperscript (Text -> String
T.unpack Text
rendered) of
                           Just String
r  -> Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
r
                           Maybe String
Nothing -> 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 -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rendered Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
inlineToMarkdown WriterOptions
opts (SmallCaps [Inline]
lst) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  if MarkdownVariant
variant MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
/= MarkdownVariant
PlainText Bool -> Bool -> Bool
&&
     (Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts Bool -> Bool -> Bool
|| Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_native_spans WriterOptions
opts)
     then WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts (Attr -> [Inline] -> Inline
Span (Text
"",[Text
"smallcaps"],[]) [Inline]
lst)
     else WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts ([Inline] -> MD m (Doc Text)) -> [Inline] -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
forall a. Walkable Inline a => a -> a
capitalize [Inline]
lst
inlineToMarkdown WriterOptions
opts (Quoted QuoteType
SingleQuote [Inline]
lst) = do
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts
              then 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
"'"
              else
                if WriterOptions -> Bool
writerPreferAscii WriterOptions
opts
                   then Doc Text
"&lsquo;" 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
"&rsquo;"
                   else 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
"’"
inlineToMarkdown WriterOptions
opts (Quoted QuoteType
DoubleQuote [Inline]
lst) = do
  Doc Text
contents <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts
              then 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
"\""
              else
                if WriterOptions -> Bool
writerPreferAscii WriterOptions
opts
                   then Doc Text
"&ldquo;" 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
"&rdquo;"
                   else 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
"”"
inlineToMarkdown WriterOptions
opts (Code Attr
attr Text
str) = do
  let tickGroups :: [Text]
tickGroups = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'`')) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.group Text
str
  let longest :: Int
longest    = Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 NonEmpty Int -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Maybe (NonEmpty Int) -> Int) -> Maybe (NonEmpty Int) -> Int
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Int] -> Maybe (NonEmpty Int)) -> [Int] -> Maybe (NonEmpty Int)
forall a b. (a -> b) -> a -> b
$ (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
T.length [Text]
tickGroups
  let marker :: Text
marker     = Int -> Text -> Text
T.replicate (Int
longest Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Text
"`"
  let spacer :: Text
spacer     = if Int
longest Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Text
"" else Text
" "
  let attrs :: Doc Text
attrs      = if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_inline_code_attributes WriterOptions
opts Bool -> Bool -> Bool
&& Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
nullAttr
                      then Attr -> Doc Text
attrsToMarkdown Attr
attr
                      else Doc Text
forall a. Doc a
empty
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  case MarkdownVariant
variant of
     MarkdownVariant
PlainText -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
     MarkdownVariant
_     ->  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal
                  (Text
marker Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
spacer Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
spacer Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
marker) Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
attrs
inlineToMarkdown WriterOptions
opts (Str Text
str) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  let str' :: Text
str' = (if WriterOptions -> Bool
writerPreferAscii WriterOptions
opts
                 then Text -> Text
toHtml5Entities
                 else Text -> Text
forall a. a -> a
id) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
             (if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_smart WriterOptions
opts
                 then WriterOptions -> Text -> Text
unsmartify WriterOptions
opts
                 else Text -> Text
forall a. a -> a
id) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
             (if MarkdownVariant
variant MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
== MarkdownVariant
PlainText
                 then Text -> Text
forall a. a -> a
id
                 else WriterOptions -> Text -> Text
escapeText WriterOptions
opts) (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
str
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str'
inlineToMarkdown WriterOptions
opts (Math MathType
InlineMath Text
str) =
  case WriterOptions -> HTMLMathMethod
writerHTMLMathMethod WriterOptions
opts of
       WebTeX Text
url -> WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts
                       (Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
nullAttr [Text -> Inline
Str Text
str] (Text
url Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> String
urlEncode (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
str), Text
str))
       HTMLMathMethod
_ | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_dollars WriterOptions
opts ->
             Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"$"
         | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_single_backslash WriterOptions
opts ->
             Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\)"
         | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_double_backslash WriterOptions
opts ->
             Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\\\)"
         | Bool
otherwise -> do
             MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
             MathType
-> Text -> ReaderT WriterEnv (StateT WriterState m) [Inline]
forall (m :: * -> *).
PandocMonad m =>
MathType -> Text -> m [Inline]
texMathToInlines MathType
InlineMath Text
str ReaderT WriterEnv (StateT WriterState m) [Inline]
-> ([Inline] -> MD m (Doc Text)) -> MD m (Doc Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
               WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts ([Inline] -> MD m (Doc Text))
-> ([Inline] -> [Inline]) -> [Inline] -> MD m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                 (if MarkdownVariant
variant MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
== MarkdownVariant
PlainText then [Inline] -> [Inline]
makeMathPlainer else [Inline] -> [Inline]
forall a. a -> a
id)
inlineToMarkdown WriterOptions
opts (Math MathType
DisplayMath Text
str) =
  case WriterOptions -> HTMLMathMethod
writerHTMLMathMethod WriterOptions
opts of
      WebTeX Text
url -> (\Doc Text
x -> Doc Text
forall a. Doc a
blankline 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
forall a. Doc a
blankline) (Doc Text -> Doc Text) -> MD m (Doc Text) -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
             WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts (Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
nullAttr [Text -> Inline
Str Text
str]
                    (Text
url Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> String
urlEncode (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
str), Text
str))
      HTMLMathMethod
_ | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_dollars WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"$$"
        | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_single_backslash WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\]"
        | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_tex_math_double_backslash WriterOptions
opts ->
            Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
str Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"\\\\]"
        | Bool
otherwise -> (\Doc Text
x -> Doc Text
forall a. Doc a
cr 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
forall a. Doc a
cr) (Doc Text -> Doc Text) -> MD m (Doc Text) -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
            (MathType
-> Text -> ReaderT WriterEnv (StateT WriterState m) [Inline]
forall (m :: * -> *).
PandocMonad m =>
MathType -> Text -> m [Inline]
texMathToInlines MathType
DisplayMath Text
str ReaderT WriterEnv (StateT WriterState m) [Inline]
-> ([Inline] -> MD m (Doc Text)) -> MD m (Doc Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts)
inlineToMarkdown WriterOptions
opts il :: Inline
il@(RawInline Format
f Text
str) = do
  let tickGroups :: [Text]
tickGroups = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'`')) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.group Text
str
  let numticks :: Int
numticks   = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 NonEmpty Int -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ((Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
T.length [Text]
tickGroups))
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  let Format Text
fmt = Format
f
  let rawAttribInline :: MD m (Doc Text)
rawAttribInline = Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$
         Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Int -> Text -> Text
T.replicate Int
numticks 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
<>
         Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Int -> Text -> Text
T.replicate Int
numticks 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
"{=" 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
fmt 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
"}"
  let renderEmpty :: MD m (Doc Text)
renderEmpty = Doc Text
forall a. Monoid a => a
mempty Doc Text
-> ReaderT WriterEnv (StateT WriterState m) () -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Inline -> LogMessage
InlineNotRendered Inline
il)
  case MarkdownVariant
variant of
    MarkdownVariant
PlainText -> MD m (Doc Text)
renderEmpty
    MarkdownVariant
Commonmark
      | Format
f Format -> [Format] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Format
"gfm", Format
"commonmark", Format
"commonmark_x", Format
"markdown"]
         -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
    MarkdownVariant
Markdown
      | Format
f Format -> [Format] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Format
"markdown", Format
"markdown_github", Format
"markdown_phpextra",
                  Format
"markdown_mmd", Format
"markdown_strict"]
         -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
    MarkdownVariant
_ | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_attribute WriterOptions
opts -> MD m (Doc Text)
rawAttribInline
      | Format
f Format -> [Format] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Format
"html", Format
"html5", Format
"html4"]
      , Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts
         -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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 (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Format
"latex", Format
"tex"]
      , Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_tex WriterOptions
opts
         -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
str
    MarkdownVariant
_ -> MD m (Doc Text)
renderEmpty


inlineToMarkdown WriterOptions
opts Inline
LineBreak = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  if MarkdownVariant
variant MarkdownVariant -> MarkdownVariant -> Bool
forall a. Eq a => a -> a -> Bool
== MarkdownVariant
PlainText Bool -> Bool -> Bool
|| Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_hard_line_breaks WriterOptions
opts
     then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Doc a
cr
     else Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$
          if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_escaped_line_breaks WriterOptions
opts
             then Doc Text
"\\" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
             else Doc Text
"  " Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
forall a. Doc a
cr
inlineToMarkdown WriterOptions
_ Inline
Space = do
  Bool
escapeSpaces <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envEscapeSpaces
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ if Bool
escapeSpaces then Doc Text
"\\ " else Doc Text
forall a. Doc a
space
inlineToMarkdown WriterOptions
opts Inline
SoftBreak = do
  Bool
escapeSpaces <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envEscapeSpaces
  let space' :: Doc Text
space' = if Bool
escapeSpaces then Doc Text
"\\ " else Doc Text
forall a. Doc a
space
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case WriterOptions -> WrapOption
writerWrapText WriterOptions
opts of
                WrapOption
WrapNone     -> Doc Text
space'
                WrapOption
WrapAuto     -> Doc Text
space'
                WrapOption
WrapPreserve -> Doc Text
forall a. Doc a
cr
inlineToMarkdown WriterOptions
opts (Cite [] [Inline]
lst) = WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
inlineToMarkdown WriterOptions
opts (Cite (Citation
c:[Citation]
cs) [Inline]
lst)
  | Bool -> Bool
not (Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_citations WriterOptions
opts) = WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
lst
  | Bool
otherwise =
      if Citation -> CitationMode
citationMode Citation
c CitationMode -> CitationMode -> Bool
forall a. Eq a => a -> a -> Bool
== CitationMode
AuthorInText
         then do
           Doc Text
suffs <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts ([Inline] -> MD m (Doc Text)) -> [Inline] -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Citation -> [Inline]
citationSuffix Citation
c
           [Doc Text]
rest <- (Citation -> MD m (Doc Text))
-> [Citation]
-> ReaderT WriterEnv (StateT WriterState m) [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Citation -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Citation -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
convertOne [Citation]
cs
           let inbr :: Doc Text
inbr = Doc Text
suffs Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
<+> [Doc Text] -> Doc Text
joincits [Doc Text]
rest
               br :: Doc Text
br   = if Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty Doc Text
inbr then Doc Text
forall a. Doc a
empty else 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
inbr 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
']'
           Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Citation -> Text
citationId Citation
c) Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
<+> Doc Text
br
         else do
           [Doc Text]
cits <- (Citation -> MD m (Doc Text))
-> [Citation]
-> ReaderT WriterEnv (StateT WriterState m) [Doc Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Citation -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
Citation -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
convertOne (Citation
cCitation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
:[Citation]
cs)
           Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"[" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> [Doc Text] -> Doc Text
joincits [Doc Text]
cits 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
"]"
  where
        joincits :: [Doc Text] -> Doc Text
joincits = [Doc Text] -> Doc Text
forall a. [Doc a] -> Doc a
hcat ([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 (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
"; ") ([Doc Text] -> [Doc Text])
-> ([Doc Text] -> [Doc Text]) -> [Doc Text] -> [Doc Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc Text -> Bool) -> [Doc Text] -> [Doc Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Doc Text -> Bool) -> Doc Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc Text -> Bool
forall a. Doc a -> Bool
isEmpty)
        convertOne :: Citation -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
convertOne Citation { citationId :: Citation -> Text
citationId      = Text
k
                            , citationPrefix :: Citation -> [Inline]
citationPrefix  = [Inline]
pinlines
                            , citationSuffix :: Citation -> [Inline]
citationSuffix  = [Inline]
sinlines
                            , citationMode :: Citation -> CitationMode
citationMode    = CitationMode
m }
                               = do
           Doc Text
pdoc <- WriterOptions
-> [Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
pinlines
           Doc Text
sdoc <- WriterOptions
-> [Inline] -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
sinlines
           let k' :: Doc Text
k' = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (CitationMode -> Text
forall p. IsString p => CitationMode -> p
modekey CitationMode
m Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
k)
               r :: Doc Text
r = case [Inline]
sinlines of
                        Str (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
y,Text
_)):[Inline]
_ | Char
y Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
",;]@" :: String) -> Doc Text
k' Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
sdoc
                        [Inline]
_                                         -> Doc Text
k' Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
<+> Doc Text
sdoc
           Doc Text -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> ReaderT WriterEnv (StateT WriterState m) (Doc Text))
-> Doc Text -> ReaderT WriterEnv (StateT WriterState m) (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
pdoc Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
<+> Doc Text
r
        modekey :: CitationMode -> p
modekey CitationMode
SuppressAuthor = p
"-"
        modekey CitationMode
_              = p
""
inlineToMarkdown WriterOptions
opts lnk :: Inline
lnk@(Link Attr
attr [Inline]
txt (Text
src, Text
tit)) = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  Doc Text
linktext <- WriterOptions -> [Inline] -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> MD m (Doc Text)
inlineListToMarkdown WriterOptions
opts [Inline]
txt
  let linktitle :: Doc Text
linktitle = if Text -> Bool
T.null Text
tit
                     then Doc Text
forall a. Doc a
empty
                     else 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 -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tit Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
  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 = Text -> Bool
isURI Text
src Bool -> Bool -> Bool
&&
                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
  let useRefLinks :: Bool
useRefLinks = WriterOptions -> Bool
writerReferenceLinks WriterOptions
opts Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
useAuto
  Bool
shortcutable <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envRefShortcutable
  let useShortcutRefLinks :: Bool
useShortcutRefLinks = Bool
shortcutable Bool -> Bool -> Bool
&&
                            Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_shortcut_reference_links WriterOptions
opts
  Doc Text
reftext <- if Bool
useRefLinks
                then Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) Text -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Attr
-> Doc Text
-> (Text, Text)
-> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *).
PandocMonad m =>
Attr -> Doc Text -> (Text, Text) -> MD m Text
getReference Attr
attr Doc Text
linktext (Text
src, Text
tit)
                else Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
forall a. Monoid a => a
mempty
  case MarkdownVariant
variant of
    MarkdownVariant
PlainText
      | Bool
useAuto -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal Text
srcSuffix
      | Bool
otherwise -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Doc Text
linktext
    MarkdownVariant
_ | Bool
useAuto -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
srcSuffix Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
">"
      | Bool
useRefLinks ->
           let first :: Doc Text
first  = 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
"]"
               second :: Doc Text
second = if Doc Text -> Key
getKey Doc Text
linktext Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Doc Text -> Key
getKey Doc Text
reftext
                           then if Bool
useShortcutRefLinks
                                   then Doc Text
""
                                   else Doc Text
"[]"
                           else Doc Text
"[" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
reftext Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"
           in  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ Doc Text
first Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
second
      | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts
      , Bool -> Bool
not (Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_link_attributes WriterOptions
opts)
      , Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
nullAttr -> -- use raw HTML to render attributes
          Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> (Text -> Text) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip (Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) Text -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            WriterOptions
-> Pandoc -> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeHtml5String WriterOptions
opts{ writerTemplate :: Maybe (Template Text)
writerTemplate = Maybe (Template Text)
forall a. Maybe a
Nothing }
            (Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta [[Inline] -> Block
Plain [Inline
lnk]])
      | Bool
otherwise -> Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
linktext 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
src 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
")" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<>
         WriterOptions -> Attr -> Doc Text
linkAttributes WriterOptions
opts Attr
attr
inlineToMarkdown WriterOptions
opts img :: Inline
img@(Image Attr
attr [Inline]
alternate (Text
source, Text
tit))
  | Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_raw_html WriterOptions
opts Bool -> Bool -> Bool
&&
    Bool -> Bool
not (Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_link_attributes WriterOptions
opts) Bool -> Bool -> Bool
&&
    Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
nullAttr = -- use raw HTML
    Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> (Text -> Text) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip (Text -> Doc Text)
-> ReaderT WriterEnv (StateT WriterState m) Text -> MD m (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      WriterOptions
-> Pandoc -> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeHtml5String WriterOptions
opts{ writerTemplate :: Maybe (Template Text)
writerTemplate = Maybe (Template Text)
forall a. Maybe a
Nothing } (Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta [[Inline] -> Block
Plain [Inline
img]])
  | Bool
otherwise = do
  MarkdownVariant
variant <- (WriterEnv -> MarkdownVariant)
-> ReaderT WriterEnv (StateT WriterState m) MarkdownVariant
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> MarkdownVariant
envVariant
  let txt :: [Inline]
txt = if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
alternate Bool -> Bool -> Bool
|| [Inline]
alternate [Inline] -> [Inline] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text -> Inline
Str Text
source]
                                 -- to prevent autolinks
               then [Text -> Inline
Str Text
""]
               else [Inline]
alternate
  Doc Text
linkPart <- WriterOptions -> Inline -> MD m (Doc Text)
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> MD m (Doc Text)
inlineToMarkdown WriterOptions
opts (Attr -> [Inline] -> (Text, Text) -> Inline
Link Attr
attr [Inline]
txt (Text
source, Text
tit))
  Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD m (Doc Text)
forall a b. (a -> b) -> a -> b
$ case MarkdownVariant
variant of
             MarkdownVariant
PlainText -> Doc Text
"[" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
linkPart Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"
             MarkdownVariant
_     -> Doc Text
"!" Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
linkPart
inlineToMarkdown WriterOptions
opts (Note [Block]
contents) = do
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
st -> WriterState
st{ stNotes :: Notes
stNotes = [Block]
contents [Block] -> Notes -> Notes
forall a. a -> [a] -> [a]
: WriterState -> Notes
stNotes WriterState
st })
  WriterState
st <- ReaderT WriterEnv (StateT WriterState m) WriterState
forall s (m :: * -> *). MonadState s m => m s
get
  let ref :: Doc Text
ref = Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Text
writerIdentifierPrefix WriterOptions
opts Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow (WriterState -> Int
stNoteNum WriterState
st Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Notes -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (WriterState -> Notes
stNotes WriterState
st) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
  if Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_footnotes WriterOptions
opts
     then Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
ref Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"
     else Doc Text -> MD m (Doc Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc Text -> MD m (Doc Text)) -> Doc Text -> MD 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
ref Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
<> Doc Text
"]"

makeMathPlainer :: [Inline] -> [Inline]
makeMathPlainer :: [Inline] -> [Inline]
makeMathPlainer = (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
go
  where
  go :: Inline -> Inline
go (Emph [Inline]
xs) = Attr -> [Inline] -> Inline
Span Attr
nullAttr [Inline]
xs
  go Inline
x         = Inline
x

toSubscriptInline :: Inline -> Maybe Inline
toSubscriptInline :: Inline -> Maybe Inline
toSubscriptInline Inline
Space = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
Space
toSubscriptInline (Span Attr
attr [Inline]
ils) = Attr -> [Inline] -> Inline
Span Attr
attr ([Inline] -> Inline) -> Maybe [Inline] -> Maybe Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Maybe Inline) -> [Inline] -> Maybe [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Inline -> Maybe Inline
toSubscriptInline [Inline]
ils
toSubscriptInline (Str Text
s) = Text -> Inline
Str (Text -> Inline) -> (String -> Text) -> String -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Inline) -> Maybe String -> Maybe Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Maybe Char) -> String -> Maybe String
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> Maybe Char
toSubscript (Text -> String
T.unpack Text
s)
toSubscriptInline Inline
LineBreak = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
LineBreak
toSubscriptInline Inline
SoftBreak = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
SoftBreak
toSubscriptInline Inline
_ = Maybe Inline
forall a. Maybe a
Nothing

toSuperscriptInline :: Inline -> Maybe Inline
toSuperscriptInline :: Inline -> Maybe Inline
toSuperscriptInline Inline
Space = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
Space
toSuperscriptInline (Span Attr
attr [Inline]
ils) = Attr -> [Inline] -> Inline
Span Attr
attr ([Inline] -> Inline) -> Maybe [Inline] -> Maybe Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Maybe Inline) -> [Inline] -> Maybe [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Inline -> Maybe Inline
toSuperscriptInline [Inline]
ils
toSuperscriptInline (Str Text
s) = Text -> Inline
Str (Text -> Inline) -> (String -> Text) -> String -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Inline) -> Maybe String -> Maybe Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Maybe Char) -> String -> Maybe String
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Char -> Maybe Char
toSuperscript (Text -> String
T.unpack Text
s)
toSuperscriptInline Inline
LineBreak = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
LineBreak
toSuperscriptInline Inline
SoftBreak = Inline -> Maybe Inline
forall a. a -> Maybe a
Just Inline
SoftBreak
toSuperscriptInline Inline
_ = Maybe Inline
forall a. Maybe a
Nothing