{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.Mdoc (readMdoc) where
import Data.Char (isAsciiLower, toUpper)
import Data.Default (Default)
import Data.Either (fromRight)
import Data.Functor (($>))
import Data.Maybe (catMaybes)
import Control.Monad (mplus, guard, void, when, unless)
import Control.Monad.Except (throwError)
#if MIN_VERSION_base(4,19,0)
import Data.List (intersperse, unsnoc)
#else
import Data.List (intersperse)
#endif
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import Text.Pandoc.Definition (Pandoc(Pandoc), Meta)
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad(..))
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (uncons)
import Text.Pandoc.Logging
import Text.Pandoc.Readers.Mdoc.Lex
import Text.Pandoc.Readers.Mdoc.Standards
import Text.Parsec (modifyState)
import qualified Text.Pandoc.Parsing as P
import qualified Data.Foldable as Foldable
import Text.Pandoc.Shared (stringify)
#if !MIN_VERSION_base(4,19,0)
unsnoc :: [a] -> Maybe ([a], a)
unsnoc :: forall a. [a] -> Maybe ([a], a)
unsnoc = (a -> Maybe ([a], a) -> Maybe ([a], a))
-> Maybe ([a], a) -> [a] -> Maybe ([a], a)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x -> ([a], a) -> Maybe ([a], a)
forall a. a -> Maybe a
Just (([a], a) -> Maybe ([a], a))
-> (Maybe ([a], a) -> ([a], a)) -> Maybe ([a], a) -> Maybe ([a], a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a], a) -> (([a], a) -> ([a], a)) -> Maybe ([a], a) -> ([a], a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([], a
x) (\(~([a]
a, a
b)) -> (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
a, a
b))) Maybe ([a], a)
forall a. Maybe a
Nothing
#endif
data MdocSection
= ShName
| ShSynopsis
| ShAuthors
| ShSeeAlso
| ShOther
deriving (Int -> MdocSection -> ShowS
[MdocSection] -> ShowS
MdocSection -> String
(Int -> MdocSection -> ShowS)
-> (MdocSection -> String)
-> ([MdocSection] -> ShowS)
-> Show MdocSection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MdocSection -> ShowS
showsPrec :: Int -> MdocSection -> ShowS
$cshow :: MdocSection -> String
show :: MdocSection -> String
$cshowList :: [MdocSection] -> ShowS
showList :: [MdocSection] -> ShowS
Show, MdocSection -> MdocSection -> Bool
(MdocSection -> MdocSection -> Bool)
-> (MdocSection -> MdocSection -> Bool) -> Eq MdocSection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MdocSection -> MdocSection -> Bool
== :: MdocSection -> MdocSection -> Bool
$c/= :: MdocSection -> MdocSection -> Bool
/= :: MdocSection -> MdocSection -> Bool
Eq)
data ReferenceField =
Author
| ArticleTitle
| BookTitle
| Publisher
| Journal
| TechReportTitle
| IssueNumber
|
| Url
| Pages
| Institution
| PubLocation
| PubDate
| Optional
deriving (Int -> ReferenceField -> ShowS
[ReferenceField] -> ShowS
ReferenceField -> String
(Int -> ReferenceField -> ShowS)
-> (ReferenceField -> String)
-> ([ReferenceField] -> ShowS)
-> Show ReferenceField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceField -> ShowS
showsPrec :: Int -> ReferenceField -> ShowS
$cshow :: ReferenceField -> String
show :: ReferenceField -> String
$cshowList :: [ReferenceField] -> ShowS
showList :: [ReferenceField] -> ShowS
Show, ReferenceField -> ReferenceField -> Bool
(ReferenceField -> ReferenceField -> Bool)
-> (ReferenceField -> ReferenceField -> Bool) -> Eq ReferenceField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceField -> ReferenceField -> Bool
== :: ReferenceField -> ReferenceField -> Bool
$c/= :: ReferenceField -> ReferenceField -> Bool
/= :: ReferenceField -> ReferenceField -> Bool
Eq, Eq ReferenceField
Eq ReferenceField =>
(ReferenceField -> ReferenceField -> Ordering)
-> (ReferenceField -> ReferenceField -> Bool)
-> (ReferenceField -> ReferenceField -> Bool)
-> (ReferenceField -> ReferenceField -> Bool)
-> (ReferenceField -> ReferenceField -> Bool)
-> (ReferenceField -> ReferenceField -> ReferenceField)
-> (ReferenceField -> ReferenceField -> ReferenceField)
-> Ord ReferenceField
ReferenceField -> ReferenceField -> Bool
ReferenceField -> ReferenceField -> Ordering
ReferenceField -> ReferenceField -> ReferenceField
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ReferenceField -> ReferenceField -> Ordering
compare :: ReferenceField -> ReferenceField -> Ordering
$c< :: ReferenceField -> ReferenceField -> Bool
< :: ReferenceField -> ReferenceField -> Bool
$c<= :: ReferenceField -> ReferenceField -> Bool
<= :: ReferenceField -> ReferenceField -> Bool
$c> :: ReferenceField -> ReferenceField -> Bool
> :: ReferenceField -> ReferenceField -> Bool
$c>= :: ReferenceField -> ReferenceField -> Bool
>= :: ReferenceField -> ReferenceField -> Bool
$cmax :: ReferenceField -> ReferenceField -> ReferenceField
max :: ReferenceField -> ReferenceField -> ReferenceField
$cmin :: ReferenceField -> ReferenceField -> ReferenceField
min :: ReferenceField -> ReferenceField -> ReferenceField
Ord, Int -> ReferenceField
ReferenceField -> Int
ReferenceField -> [ReferenceField]
ReferenceField -> ReferenceField
ReferenceField -> ReferenceField -> [ReferenceField]
ReferenceField
-> ReferenceField -> ReferenceField -> [ReferenceField]
(ReferenceField -> ReferenceField)
-> (ReferenceField -> ReferenceField)
-> (Int -> ReferenceField)
-> (ReferenceField -> Int)
-> (ReferenceField -> [ReferenceField])
-> (ReferenceField -> ReferenceField -> [ReferenceField])
-> (ReferenceField -> ReferenceField -> [ReferenceField])
-> (ReferenceField
-> ReferenceField -> ReferenceField -> [ReferenceField])
-> Enum ReferenceField
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ReferenceField -> ReferenceField
succ :: ReferenceField -> ReferenceField
$cpred :: ReferenceField -> ReferenceField
pred :: ReferenceField -> ReferenceField
$ctoEnum :: Int -> ReferenceField
toEnum :: Int -> ReferenceField
$cfromEnum :: ReferenceField -> Int
fromEnum :: ReferenceField -> Int
$cenumFrom :: ReferenceField -> [ReferenceField]
enumFrom :: ReferenceField -> [ReferenceField]
$cenumFromThen :: ReferenceField -> ReferenceField -> [ReferenceField]
enumFromThen :: ReferenceField -> ReferenceField -> [ReferenceField]
$cenumFromTo :: ReferenceField -> ReferenceField -> [ReferenceField]
enumFromTo :: ReferenceField -> ReferenceField -> [ReferenceField]
$cenumFromThenTo :: ReferenceField
-> ReferenceField -> ReferenceField -> [ReferenceField]
enumFromThenTo :: ReferenceField
-> ReferenceField -> ReferenceField -> [ReferenceField]
Enum)
type MdocReference = M.Map ReferenceField [T.Text]
data MdocState = MdocState
{ MdocState -> ReaderOptions
readerOptions :: ReaderOptions
, MdocState -> Meta
metadata :: Meta
, MdocState -> Bool
tableCellsPlain :: Bool
, MdocState -> Bool
spacingMode :: Bool
, MdocState -> Bool
authorNameSplit :: Bool
, MdocState -> Bool
inLineEnclosure :: Bool
, MdocState -> Maybe Text
progName :: Maybe T.Text
, MdocState -> MdocSection
currentSection :: MdocSection
, MdocState -> MdocReference
currentReference :: MdocReference
, MdocState -> [LogMessage]
logMessages :: [LogMessage]
}
deriving (Int -> MdocState -> ShowS
[MdocState] -> ShowS
MdocState -> String
(Int -> MdocState -> ShowS)
-> (MdocState -> String)
-> ([MdocState] -> ShowS)
-> Show MdocState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MdocState -> ShowS
showsPrec :: Int -> MdocState -> ShowS
$cshow :: MdocState -> String
show :: MdocState -> String
$cshowList :: [MdocState] -> ShowS
showList :: [MdocState] -> ShowS
Show)
instance Default MdocState where
def :: MdocState
def =
MdocState
{ readerOptions :: ReaderOptions
readerOptions = ReaderOptions
forall a. Default a => a
def
, metadata :: Meta
metadata = Meta
B.nullMeta
, tableCellsPlain :: Bool
tableCellsPlain = Bool
True
, spacingMode :: Bool
spacingMode = Bool
True
, authorNameSplit :: Bool
authorNameSplit = Bool
False
, inLineEnclosure :: Bool
inLineEnclosure = Bool
False
, currentSection :: MdocSection
currentSection = MdocSection
ShOther
, currentReference :: MdocReference
currentReference = MdocReference
forall k a. Map k a
M.empty
, progName :: Maybe Text
progName = Maybe Text
forall a. Maybe a
Nothing
, logMessages :: [LogMessage]
logMessages = []
}
instance HasLogMessages MdocState where
addLogMessage :: LogMessage -> MdocState -> MdocState
addLogMessage LogMessage
msg MdocState
st = MdocState
st{ logMessages = msg : logMessages st }
getLogMessages :: MdocState -> [LogMessage]
getLogMessages MdocState
st = [LogMessage] -> [LogMessage]
forall a. [a] -> [a]
reverse ([LogMessage] -> [LogMessage]) -> [LogMessage] -> [LogMessage]
forall a b. (a -> b) -> a -> b
$ MdocState -> [LogMessage]
logMessages MdocState
st
type MdocParser m = P.ParsecT [MdocToken] MdocState m
readMdoc :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readMdoc :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readMdoc ReaderOptions
opts a
s = do
let Sources [(SourcePos, Text)]
inps = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s
MdocTokens
tokenz <- [MdocTokens] -> MdocTokens
forall a. Monoid a => [a] -> a
mconcat ([MdocTokens] -> MdocTokens) -> m [MdocTokens] -> m MdocTokens
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((SourcePos, Text) -> m MdocTokens)
-> [(SourcePos, Text)] -> m [MdocTokens]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((SourcePos -> Text -> m MdocTokens)
-> (SourcePos, Text) -> m MdocTokens
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry SourcePos -> Text -> m MdocTokens
forall (m :: * -> *).
PandocMonad m =>
SourcePos -> Text -> m MdocTokens
lexMdoc) [(SourcePos, Text)]
inps
let state :: MdocState
state = MdocState
forall a. Default a => a
def {readerOptions = opts} :: MdocState
Either ParseError Pandoc
eitherdoc <- ParsecT [MdocToken] MdocState m Pandoc
-> MdocState -> [MdocToken] -> m (Either ParseError Pandoc)
forall (m :: * -> *) a.
PandocMonad m =>
ParsecT [MdocToken] MdocState m a
-> MdocState -> [MdocToken] -> m (Either ParseError a)
readWithMTokens ParsecT [MdocToken] MdocState m Pandoc
forall (m :: * -> *). PandocMonad m => MdocParser m Pandoc
parseMdoc MdocState
state
(Seq MdocToken -> [MdocToken]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList (Seq MdocToken -> [MdocToken])
-> (MdocTokens -> Seq MdocToken) -> MdocTokens -> [MdocToken]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocTokens -> Seq MdocToken
unMdocTokens (MdocTokens -> [MdocToken]) -> MdocTokens -> [MdocToken]
forall a b. (a -> b) -> a -> b
$ MdocTokens
tokenz)
(ParseError -> m Pandoc)
-> (Pandoc -> m Pandoc) -> Either ParseError Pandoc -> m Pandoc
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc)
-> (ParseError -> PandocError) -> ParseError -> m Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sources -> ParseError -> PandocError
fromParsecError ([(SourcePos, Text)] -> Sources
Sources [(SourcePos, Text)]
inps)) Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Either ParseError Pandoc
eitherdoc
readWithMTokens :: PandocMonad m
=> ParsecT [MdocToken] MdocState m a
-> MdocState
-> [MdocToken]
-> m (Either ParseError a)
readWithMTokens :: forall (m :: * -> *) a.
PandocMonad m =>
ParsecT [MdocToken] MdocState m a
-> MdocState -> [MdocToken] -> m (Either ParseError a)
readWithMTokens ParsecT [MdocToken] MdocState m a
parser MdocState
state [MdocToken]
input =
ParsecT [MdocToken] MdocState m a
-> MdocState -> String -> [MdocToken] -> m (Either ParseError a)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT ParsecT [MdocToken] MdocState m a
parser MdocState
state String
"source" [MdocToken]
input
parseMdoc :: PandocMonad m => MdocParser m Pandoc
parseMdoc :: forall (m :: * -> *). PandocMonad m => MdocParser m Pandoc
parseMdoc = do
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePrologue
[Blocks]
bs <- ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBlock ParsecT [MdocToken] MdocState m [Blocks]
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [Blocks]
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
Meta
meta <- MdocState -> Meta
metadata (MdocState -> Meta)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let (Pandoc Meta
_ [Block]
blocks) = Blocks -> Pandoc
B.doc (Blocks -> Pandoc) -> Blocks -> Pandoc
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
bs
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
Pandoc -> MdocParser m Pandoc
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> MdocParser m Pandoc) -> Pandoc -> MdocParser m Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
blocks
msatisfy :: Monad m
=> (MdocToken -> Bool) -> P.ParsecT [MdocToken] st m MdocToken
msatisfy :: forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
predic = (MdocToken -> String)
-> (SourcePos -> MdocToken -> [MdocToken] -> SourcePos)
-> (MdocToken -> Maybe MdocToken)
-> ParsecT [MdocToken] st m MdocToken
forall s (m :: * -> *) t a u.
Stream s m t =>
(t -> String)
-> (SourcePos -> t -> s -> SourcePos)
-> (t -> Maybe a)
-> ParsecT s u m a
P.tokenPrim MdocToken -> String
forall a. Show a => a -> String
show SourcePos -> MdocToken -> [MdocToken] -> SourcePos
nextPos MdocToken -> Maybe MdocToken
testTok
where
testTok :: MdocToken -> Maybe MdocToken
testTok MdocToken
t = if MdocToken -> Bool
predic MdocToken
t then MdocToken -> Maybe MdocToken
forall a. a -> Maybe a
Just MdocToken
t else Maybe MdocToken
forall a. Maybe a
Nothing
nextPos :: SourcePos -> MdocToken -> [MdocToken] -> SourcePos
nextPos SourcePos
_ MdocToken
_ (Macro Text
_ SourcePos
pos':[MdocToken]
_) = SourcePos
pos'
nextPos SourcePos
_ MdocToken
_ (Lit Text
_ SourcePos
pos':[MdocToken]
_) = SourcePos
pos'
nextPos SourcePos
_ MdocToken
_ (Str Text
_ SourcePos
pos':[MdocToken]
_) = SourcePos
pos'
nextPos SourcePos
_ MdocToken
_ (Delim DelimSide
_ Text
_ SourcePos
pos':[MdocToken]
_) = SourcePos
pos'
nextPos SourcePos
_ MdocToken
_ (Blank SourcePos
pos':[MdocToken]
_) = SourcePos
pos'
nextPos SourcePos
a MdocToken
_ (Eol{}:MdocToken
x:[MdocToken]
xs) = SourcePos -> MdocToken -> [MdocToken] -> SourcePos
nextPos SourcePos
a MdocToken
x [MdocToken]
xs
nextPos SourcePos
pos MdocToken
_ [MdocToken
Eol] = SourcePos
pos
nextPos SourcePos
pos MdocToken
_ [] = SourcePos
pos
macro :: PandocMonad m => T.Text -> MdocParser m MdocToken
macro :: forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
name = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t (Macro Text
n SourcePos
_) = Text
n Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
name
t MdocToken
_ = Bool
False
anyMacro :: PandocMonad m => MdocParser m MdocToken
anyMacro :: forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
anyMacro = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t (Macro Text
_ SourcePos
_) = Bool
True
t MdocToken
_ = Bool
False
emptyMacro :: PandocMonad m => T.Text -> MdocParser m MdocToken
emptyMacro :: forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
n = Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
n MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m () -> MdocParser m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
delim :: PandocMonad m => DelimSide -> MdocParser m MdocToken
delim :: forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
side = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t (Delim DelimSide
s Text
_ SourcePos
_) = DelimSide
side DelimSide -> DelimSide -> Bool
forall a. Eq a => a -> a -> Bool
== DelimSide
s
t MdocToken
_ = Bool
False
str :: PandocMonad m => MdocParser m MdocToken
str :: forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
str = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t Str{} = Bool
True
t MdocToken
_ = Bool
False
lit :: PandocMonad m => MdocParser m MdocToken
lit :: forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t Lit{} = Bool
True
t MdocToken
_ = Bool
False
arg :: PandocMonad m => MdocParser m MdocToken
arg :: forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
arg = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t Lit{} = Bool
True
t Macro{} = Bool
True
t MdocToken
_ = Bool
False
literal :: PandocMonad m => T.Text -> MdocParser m MdocToken
literal :: forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
n = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t (Lit Text
n' SourcePos
_) = Text
n Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
n'
t MdocToken
_ = Bool
False
blank :: PandocMonad m => MdocParser m MdocToken
blank :: forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
blank = (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t Blank{} = Bool
True
t MdocToken
_ = Bool
False
eol :: PandocMonad m => MdocParser m ()
eol :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol = ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
t where
t :: MdocToken -> Bool
t Eol{} = Bool
True
t MdocToken
_ = Bool
False
newControlContext :: MdocToken -> Bool
newControlContext :: MdocToken -> Bool
newControlContext Eol{} = Bool
True
newControlContext Macro{} = Bool
True
newControlContext Str{} = Bool
True
newControlContext Blank{} = Bool
True
newControlContext Lit{} = Bool
False
newControlContext Delim{} = Bool
False
inlineContextEnd :: PandocMonad m => MdocParser m ()
inlineContextEnd :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
inlineContextEnd = ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken)
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ (MdocToken -> Bool) -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
newControlContext)
sectionEnd :: PandocMonad m => MdocParser m ()
sectionEnd :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
sectionEnd = ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken)
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Sh")
argsToInlines :: PandocMonad m => MdocParser m Inlines
argsToInlines :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
argsToInlines = do
[MdocToken]
ls <- ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
arg ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
let strs :: [Inlines]
strs = (MdocToken -> Inlines) -> [MdocToken] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Inlines
B.str (Text -> Inlines) -> (MdocToken -> Text) -> MdocToken -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString) [MdocToken]
ls
[Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify [Inlines]
strs
parsePrologue :: PandocMonad m => MdocParser m ()
parsePrologue :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePrologue = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Dd"
Inlines
date <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
argsToInlines
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Dt"
(Lit Text
title SourcePos
_) <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
(Lit Text
section SourcePos
_) <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Maybe Text
arch <- ParsecT [MdocToken] MdocState m Text
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit)
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Os"
let adjust :: Meta -> Meta
adjust = Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"title" (Text -> Inlines
B.str Text
title)
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"date" Inlines
date
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"section" (Text -> Inlines
B.str Text
section)
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Meta -> Meta)
-> (Text -> Meta -> Meta) -> Maybe Text -> Meta -> Meta
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Meta -> Meta
forall a. a -> a
id (Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"architecture" (Inlines -> Meta -> Meta)
-> (Text -> Inlines) -> Text -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str) Maybe Text
arch
(MdocState -> MdocState) -> MdocParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> MdocParser m ())
-> (MdocState -> MdocState) -> MdocParser m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{metadata = adjust $ metadata s}
shToSectionMode :: T.Text -> MdocSection
shToSectionMode :: Text -> MdocSection
shToSectionMode Text
"NAME" = MdocSection
ShName
shToSectionMode Text
"SYNOPSIS" = MdocSection
ShSynopsis
shToSectionMode Text
"AUTHORS" = MdocSection
ShAuthors
shToSectionMode Text
"SEE ALSO" = MdocSection
ShSeeAlso
shToSectionMode Text
_ = MdocSection
ShOther
parseHeader :: PandocMonad m => MdocParser m Blocks
= do
(Macro Text
m SourcePos
_) <- ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken)
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Sh" ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ss"
Inlines
txt <- Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
m Inlines -> Inlines
forall a. a -> a
id
let lvl :: Int
lvl = if Text
m Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"Sh" then Int
1 else Int
2
Bool
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
lvl Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1) (ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{currentSection = (shToSectionMode . stringify) txt}
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ Int -> Inlines -> Blocks
B.header Int
lvl Inlines
txt
parseNameSection :: PandocMonad m => MdocParser m Blocks
parseNameSection :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseNameSection = do
MdocSection
sec <- MdocState -> MdocSection
currentSection (MdocState -> MdocSection)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocSection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ MdocSection
sec MdocSection -> MdocSection -> Bool
forall a. Eq a => a -> a -> Bool
== MdocSection
ShName
Inlines
nms <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.space ([Inlines] -> Inlines)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> ParsecT [MdocToken] MdocState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m Inlines
nameNm
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Nd"
Inlines
desc <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
argsToInlines
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines
nms Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"—" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
desc
where
nameNm :: ParsecT [MdocToken] MdocState m Inlines
nameNm = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Nm"
[Inlines]
nms <- ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m Inlines
aNm
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT [MdocToken] MdocState m Inlines)
-> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.space [Inlines]
nms
comma :: ParsecT [MdocToken] st m MdocToken
comma = (MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy ((MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken)
-> (MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
forall a b. (a -> b) -> a -> b
$ \case
(Delim DelimSide
_ Text
"," SourcePos
_) -> Bool
True
MdocToken
_ -> Bool
False
aNm :: ParsecT [MdocToken] MdocState m Inlines
aNm = do
Text
nm <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Text
c <- Text
-> ParsecT [MdocToken] MdocState m Text
-> ParsecT [MdocToken] MdocState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall {st}. ParsecT [MdocToken] st m MdocToken
comma)
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{progName = mplus (progName s) (Just nm)}
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT [MdocToken] MdocState m Inlines)
-> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.code Text
nm Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
c
parseSynopsisSection :: PandocMonad m => MdocParser m Blocks
parseSynopsisSection :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseSynopsisSection = do
MdocSection
sec <- MdocState -> MdocSection
currentSection (MdocState -> MdocSection)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocSection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ MdocSection
sec MdocSection -> MdocSection -> Bool
forall a. Eq a => a -> a -> Bool
== MdocSection
ShSynopsis
ParsecT [MdocToken] MdocState m () -> MdocParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
MdocParser m () -> MdocParser m Blocks
parseSynopsis ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
sectionEnd
parseMiniSynopsis :: PandocMonad m => MdocParser m Blocks
parseMiniSynopsis :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseMiniSynopsis = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"nr"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"nS"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"1"
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
MdocParser m () -> MdocParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
MdocParser m () -> MdocParser m Blocks
parseSynopsis (MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
sectionEnd MdocParser m () -> MdocParser m () -> MdocParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m ()
end)
where
end :: MdocParser m ()
end = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"nr"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"nS"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"0"
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
() -> MdocParser m ()
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
parseSynopsis :: PandocMonad m => MdocParser m () -> MdocParser m Blocks
parseSynopsis :: forall (m :: * -> *).
PandocMonad m =>
MdocParser m () -> MdocParser m Blocks
parseSynopsis MdocParser m ()
end = do
[Blocks]
bs <- MdocParser m Blocks
-> MdocParser m () -> ParsecT [MdocToken] MdocState m [Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill MdocParser m Blocks
synopsisBlock MdocParser m ()
end
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
bs
where
synopsisGroup :: ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup ParsecT [MdocToken] MdocState m Inlines
p = [Inlines] -> Blocks
B.lineBlock ([Inlines] -> Blocks)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> ParsecT [MdocToken] MdocState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m Inlines
p ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Blocks
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp")
synopsisBlock :: MdocParser m Blocks
synopsisBlock = ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall {m :: * -> *}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup ParsecT [MdocToken] MdocState m Inlines
parseInvocation
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall {m :: * -> *}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseCd ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall {m :: * -> *}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseIn ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall {m :: * -> *}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFd ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall {m :: * -> *}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
synopsisGroup (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseVt ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try MdocParser m Blocks
parseSignature
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
parseWeirdSignature
MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock
parseInvocation :: ParsecT [MdocToken] MdocState m Inlines
parseInvocation = do
Inlines
nm <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNm
MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Inlines]
rest <- ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m Inlines
synopsisInline
[Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify (Inlines
nmInlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
:[Inlines]
rest)
parseSignature :: MdocParser m Blocks
parseSignature = do
Inlines
ft <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFt ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines
sig <- (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFn ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFo) ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Blocks
B.lineBlock [Inlines
ft, Inlines
sig Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
";"]
parseWeirdSignature :: MdocParser m Blocks
parseWeirdSignature = do
Inlines
ft <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFt ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Inlines]
rest <- ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m Inlines
synopsisInline
Inlines
line <- [Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify (Inlines
ftInlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
:[Inlines]
rest)
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Blocks
B.lineBlock [Inlines
line]
synopsisInline :: ParsecT [MdocToken] MdocState m Inlines
synopsisInline = ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseStrs ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT [MdocToken] MdocState m [Inlines]
controlLine ParsecT [MdocToken] MdocState m [Inlines]
-> ([Inlines] -> ParsecT [MdocToken] MdocState m Inlines)
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> (a -> ParsecT [MdocToken] MdocState m b)
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify) ParsecT [MdocToken] MdocState m Inlines
-> String -> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"synopsis inlines"
safeEol :: MdocParser m ()
safeEol = do
Bool
amNested <- MdocState -> Bool
inLineEnclosure (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> MdocParser m () -> MdocParser m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
amNested (MdocParser m () -> MdocParser m ())
-> MdocParser m () -> MdocParser m ()
forall a b. (a -> b) -> a -> b
$ MdocParser m () -> MdocParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
controlLine :: ParsecT [MdocToken] MdocState m [Inlines]
controlLine = ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 (([ParsecT [MdocToken] MdocState m Inlines]
-> ParsecT [MdocToken] MdocState m Inlines
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ParsecT [MdocToken] MdocState m Inlines]
forall (m :: * -> *). PandocMonad m => [MdocParser m Inlines]
otherInlineMacros ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines) ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m () -> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m ()
safeEol)
parseSeeAlsoSection :: PandocMonad m => MdocParser m Blocks
parseSeeAlsoSection :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseSeeAlsoSection = do
MdocSection
sec <- MdocState -> MdocSection
currentSection (MdocState -> MdocSection)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocSection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ MdocSection
sec MdocSection -> MdocSection -> Bool
forall a. Eq a => a -> a -> Bool
== MdocSection
ShSeeAlso
[Blocks]
blocks <- MdocParser m Blocks
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [Blocks]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till MdocParser m Blocks
parseSeeAlsoBlock ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
sectionEnd
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
blocks
where
parseSeeAlsoBlock :: MdocParser m Blocks
parseSeeAlsoBlock = MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Inlines -> Blocks
B.para (Inlines -> Blocks)
-> ParsecT [MdocToken] MdocState m Inlines -> MdocParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRs)
parseStr :: PandocMonad m => MdocParser m Inlines
parseStr :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseStr = do
(Str Text
txt SourcePos
_) <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
str
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text Text
txt
parseStrs :: PandocMonad m => MdocParser m Inlines
parseStrs :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseStrs = do
[Inlines]
txt <- MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseStr
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.space [Inlines]
txt
parseDelim :: PandocMonad m => DelimSide -> MdocParser m Inlines
parseDelim :: forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
pos = do
(Delim DelimSide
_ Text
txt SourcePos
_) <- DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
pos
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
txt
litsToText :: PandocMonad m => MdocParser m [T.Text]
litsToText :: forall (m :: * -> *). PandocMonad m => MdocParser m [Text]
litsToText = do
[MdocToken]
ls <- ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
[Text] -> MdocParser m [Text]
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> MdocParser m [Text]) -> [Text] -> MdocParser m [Text]
forall a b. (a -> b) -> a -> b
$ (MdocToken -> Text) -> [MdocToken] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map MdocToken -> Text
toString [MdocToken]
ls
litsToInlines :: PandocMonad m => MdocParser m Inlines
litsToInlines :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsToInlines = do
[MdocToken]
ls <- ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
let strs :: [Inlines]
strs = (MdocToken -> Inlines) -> [MdocToken] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Inlines
B.str (Text -> Inlines) -> (MdocToken -> Text) -> MdocToken -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString) [MdocToken]
ls
[Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify [Inlines]
strs
litsAndDelimsToInlines :: PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines = do
(Inlines
o, [MdocToken]
ls, Inlines
c) <- MdocParser m [MdocToken]
-> MdocParser m (Inlines, [MdocToken], Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (MdocParser m [MdocToken]
-> MdocParser m (Inlines, [MdocToken], Inlines))
-> MdocParser m [MdocToken]
-> MdocParser m (Inlines, [MdocToken], Inlines)
forall a b. (a -> b) -> a -> b
$ ParsecT [MdocToken] MdocState m MdocToken
-> MdocParser m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
o Bool -> Bool -> Bool
&& [MdocToken] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MdocToken]
ls Bool -> Bool -> Bool
&& Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
c)
Inlines
strs <- [Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify ([Inlines] -> MdocParser m Inlines)
-> [Inlines] -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ (MdocToken -> Inlines) -> [MdocToken] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Inlines
B.str (Text -> Inlines) -> (MdocToken -> Text) -> MdocToken -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString) [MdocToken]
ls
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
o Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
strs Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
c
openingDelimiters :: PandocMonad m => MdocParser m Inlines
openingDelimiters :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters = do
Inlines
openDelim <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> MdocParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (DelimSide -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
Open)
Inlines
omids <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
pipes
Bool
addSpace <- MdocState -> Bool
spacingMode (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let omid :: Inlines
omid | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
omids = Inlines
forall a. Monoid a => a
mempty
| Bool
addSpace = Inlines
omids Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
| Bool
otherwise = Inlines
omids
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
openDelim Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
omid
pipes :: PandocMonad m => MdocParser m Inlines
pipes :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
pipes = ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (DelimSide -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
Middle) ParsecT [MdocToken] MdocState m [Inlines]
-> ([Inlines] -> ParsecT [MdocToken] MdocState m Inlines)
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> (a -> ParsecT [MdocToken] MdocState m b)
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify
closingDelimiters :: PandocMonad m => MdocParser m Inlines
closingDelimiters :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters = do
Inlines
cmids <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
pipes
Bool
addSpace <- MdocState -> Bool
spacingMode (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let cmid :: Inlines
cmid | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
cmids = Inlines
forall a. Monoid a => a
mempty
| Bool
addSpace = Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
cmids
| Bool
otherwise = Inlines
cmids
Inlines
closeDelim <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> MdocParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (DelimSide -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
Close)
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
cmid Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
closeDelim
delimitedArgs :: PandocMonad m => MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs :: forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs MdocParser m x
p = do
Inlines
openDelim <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters
x
inlines <- MdocParser m x
p
Inlines
closeDelim <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
(Inlines, x, Inlines) -> MdocParser m (Inlines, x, Inlines)
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
openDelim, x
inlines, Inlines
closeDelim)
simpleInline :: PandocMonad m => T.Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline :: forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
nm Inlines -> Inlines
xform = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
nm
[Inlines]
segs <- MdocParser m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill MdocParser m Inlines
segment ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
inlineContextEnd
[Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify [Inlines]
segs
where
segment :: MdocParser m Inlines
segment = do
(Inlines
openDelim, Inlines
inlines, Inlines
closeDelim) <- MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines))
-> MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> MdocParser m Inlines -> MdocParser m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsToInlines
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
openDelim Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
xform Inlines
inlines Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
closeDelim
codeLikeInline' :: PandocMonad m => T.Text -> T.Text -> MdocParser m Inlines
codeLikeInline' :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
nm Text
cl = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
nm ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty (Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
cl) (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify))
codeLikeInline :: PandocMonad m => T.Text -> MdocParser m Inlines
codeLikeInline :: forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
nm = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
nm Text
nm
spanLikeInline :: PandocMonad m => T.Text -> MdocParser m Inlines
spanLikeInline :: forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
spanLikeInline Text
nm = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
nm ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty (Attr -> Inlines -> Inlines
B.spanWith (Text -> Attr
cls Text
nm)))
lineEnclosure :: PandocMonad m => T.Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure :: forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
nm Inlines -> Inlines
xform = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
nm
Bool
amNested <- MdocState -> Bool
inLineEnclosure (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = True}
Inlines
first <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters
[Inlines]
further <-
(ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill
(ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlineMacro
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol))
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsToInlines
ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters)
ParsecT [MdocToken] MdocState m ()
lineEnclosureContextEnd)
Inlines
further' <- [Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify [Inlines]
further
Inlines
finally <- if Bool
amNested then ParsecT [MdocToken] MdocState m Inlines
forall a. Monoid a => a
mempty else ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = amNested}
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT [MdocToken] MdocState m Inlines)
-> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
first Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
xform Inlines
further' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
finally
where
lineEnclosureContextEnd :: ParsecT [MdocToken] MdocState m ()
lineEnclosureContextEnd =
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$
MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MdocParser m MdocToken -> MdocParser m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ta"))
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ns" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Close) ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
noSpace :: Inlines
noSpace :: Inlines
noSpace = Text -> Text -> Inlines
B.rawInline Text
"mdoc" Text
"Ns"
apMacro :: Inlines
apMacro :: Inlines
apMacro = Text -> Text -> Inlines
B.rawInline Text
"mdoc" Text
"Ap"
smOff :: Inlines
smOff :: Inlines
smOff = Text -> Text -> Inlines
B.rawInline Text
"mdoc" Text
"Sm off"
smOn :: Inlines
smOn :: Inlines
smOn = Text -> Text -> Inlines
B.rawInline Text
"mdoc" Text
"Sm on"
data SpacifyState = SpacifyState
{ SpacifyState -> [Inlines]
accum :: [Inlines],
SpacifyState -> Inlines
prev :: Inlines,
SpacifyState -> Bool
ns :: Bool,
SpacifyState -> Bool
sm :: Bool
}
instance Default SpacifyState where
def :: SpacifyState
def = [Inlines] -> Inlines -> Bool -> Bool -> SpacifyState
SpacifyState [] Inlines
forall a. Monoid a => a
mempty Bool
False Bool
True
foldNoSpaces :: [Inlines] -> [Inlines]
foldNoSpaces :: [Inlines] -> [Inlines]
foldNoSpaces [Inlines]
xs = (SpacifyState -> [Inlines]
finalize (SpacifyState -> [Inlines])
-> ([Inlines] -> SpacifyState) -> [Inlines] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SpacifyState -> Inlines -> SpacifyState)
-> SpacifyState -> [Inlines] -> SpacifyState
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl SpacifyState -> Inlines -> SpacifyState
go SpacifyState
forall a. Default a => a
def) [Inlines]
xs
where
go :: SpacifyState -> Inlines -> SpacifyState
go :: SpacifyState -> Inlines -> SpacifyState
go SpacifyState
s Inlines
x
| SpacifyState -> Bool
ns SpacifyState
s Bool -> Bool -> Bool
&& Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
noSpace = SpacifyState
s
| Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
apMacro = SpacifyState
s{prev = prev s <> "'", ns = True}
| Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
noSpace = SpacifyState
s{ns = True}
| Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
smOn = SpacifyState
s{sm = True}
| SpacifyState -> Bool
sm SpacifyState
s Bool -> Bool -> Bool
&& Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
smOff = SpacifyState
s{accum = accum s <> [prev s], prev = mempty, sm = False}
| SpacifyState -> Bool
ns SpacifyState
s = SpacifyState
s{prev = prev s <> x, ns = False}
| Bool -> Bool
not (SpacifyState -> Bool
sm SpacifyState
s) = SpacifyState
s{prev = prev s <> x}
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SpacifyState -> Inlines
prev SpacifyState
s) = SpacifyState
s{prev = x}
| Bool
otherwise = SpacifyState
s{accum = accum s <> [prev s], prev = x}
finalize :: SpacifyState -> [Inlines]
finalize SpacifyState
s
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SpacifyState -> Inlines
prev SpacifyState
s) = SpacifyState -> [Inlines]
accum SpacifyState
s
| Bool
otherwise = SpacifyState -> [Inlines]
accum SpacifyState
s [Inlines] -> [Inlines] -> [Inlines]
forall a. Semigroup a => a -> a -> a
<> [SpacifyState -> Inlines
prev SpacifyState
s]
spacify :: PandocMonad m => [Inlines] -> MdocParser m Inlines
spacify :: forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify [Inlines]
x = do
Bool
mode <- MdocState -> Bool
spacingMode (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> [Inlines] -> Inlines
go Bool
mode [Inlines]
x)
where
go :: Bool -> [Inlines] -> Inlines
go Bool
True = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.space ([Inlines] -> [Inlines])
-> ([Inlines] -> [Inlines]) -> [Inlines] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> [Inlines]
foldNoSpaces
go Bool
False = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> [Inlines]
foldNoSpaces
multilineEnclosure :: PandocMonad m => T.Text -> T.Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
op Text
cl Inlines -> Inlines
xform = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
op
Bool
amNested <- MdocState -> Bool
inLineEnclosure (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = False}
Inlines
openDelim <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> ParsecT [MdocToken] MdocState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (DelimSide -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
Open)
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines
contents <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines
(Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
cl MdocParser m MdocToken -> String -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> Text -> String
forall a. Show a => a -> String
show Text
cl)
Inlines
closeDelim <-
if Bool
amNested
then ParsecT [MdocToken] MdocState m Inlines
forall a. Monoid a => a
mempty
else [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [MdocToken] MdocState m [Inlines]
-> ParsecT [MdocToken] MdocState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (DelimSide -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m Inlines
parseDelim DelimSide
Close) ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = amNested}
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT [MdocToken] MdocState m Inlines)
-> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
openDelim Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
xform Inlines
contents Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
closeDelim
parseEo :: PandocMonad m => MdocParser m Inlines
parseEo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEo = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Eo"
Inlines
odel <- MdocParser m Inlines
del
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines
inner <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ec"
Inlines
cdel <- MdocParser m Inlines
del
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
odel Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
inner Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
cdel
where
del :: MdocParser m Inlines
del = Text -> Inlines
B.str (Text -> Inlines) -> (MdocToken -> Text) -> MdocToken -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString (MdocToken -> Inlines)
-> MdocParser m MdocToken -> MdocParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
arg MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Open MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Middle MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Close)
eliminateEmpty :: (Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty :: (Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty Inlines -> Inlines
x Inlines
y = if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
y then Inlines
forall a. Monoid a => a
mempty else Inlines -> Inlines
x Inlines
y
cls :: T.Text -> B.Attr
cls :: Text -> Attr
cls Text
x = (Text
forall a. Monoid a => a
mempty, [Text
x], [(Text, Text)]
forall a. Monoid a => a
mempty)
parseSy :: PandocMonad m => MdocParser m Inlines
parseSy :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSy = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Sy" ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty Inlines -> Inlines
B.strong)
parseEm :: PandocMonad m => MdocParser m Inlines
parseEm :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEm = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Em" ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty Inlines -> Inlines
B.emph)
parseNo :: PandocMonad m => MdocParser m Inlines
parseNo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNo = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"No" ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty Inlines -> Inlines
forall a. a -> a
id)
parseTn :: PandocMonad m => MdocParser m Inlines
parseTn :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseTn = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Tn" ((Inlines -> Inlines) -> Inlines -> Inlines
eliminateEmpty Inlines -> Inlines
forall a. a -> a
id)
parseLi :: PandocMonad m => MdocParser m Inlines
parseLi :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLi = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Li"
parseEv :: PandocMonad m => MdocParser m Inlines
parseEv :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEv = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Ev"
parseDv :: PandocMonad m => MdocParser m Inlines
parseDv :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDv = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Dv"
parseAd :: PandocMonad m => MdocParser m Inlines
parseAd :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAd = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
spanLikeInline Text
"Ad"
parseVa :: PandocMonad m => MdocParser m Inlines
parseVa :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseVa = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
"Va" Text
"variable"
parseVt :: PandocMonad m => MdocParser m Inlines
parseVt :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseVt = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
"Vt" Text
"variable"
parseAn :: PandocMonad m => MdocParser m Inlines
parseAn :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAn = ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT [MdocToken] MdocState m Inlines
anSplit ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
anRegular
where
anSplit :: ParsecT [MdocToken] MdocState m Inlines
anSplit = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"An"
Bool
mode <- Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-split" MdocParser m MdocToken
-> Bool -> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
True ParsecT [MdocToken] MdocState m Bool
-> ParsecT [MdocToken] MdocState m Bool
-> ParsecT [MdocToken] MdocState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-nosplit" MdocParser m MdocToken
-> Bool -> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
False
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{authorNameSplit = mode}
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
anRegular :: ParsecT [MdocToken] MdocState m Inlines
anRegular = do
Inlines
an <- Text -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
spanLikeInline Text
"An"
Bool
spl <- MdocState -> Bool
authorNameSplit (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT [MdocToken] MdocState m Inlines)
-> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a b. (a -> b) -> a -> b
$ (if Bool
spl then Inlines
B.linebreak else Inlines
forall a. Monoid a => a
mempty) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
an
parseMs :: PandocMonad m => MdocParser m Inlines
parseMs :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseMs = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
spanLikeInline Text
"Ms"
parseSx :: PandocMonad m => MdocParser m Inlines
parseSx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSx = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
spanLikeInline Text
"Sx"
parseMt :: PandocMonad m => MdocParser m Inlines
parseMt :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseMt = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Mt" Inlines -> Inlines
mailto
where mailto :: Inlines -> Inlines
mailto Inlines
x | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
x = Text -> Text -> Inlines -> Inlines
B.link (Text
"mailto:~") Text
"" Inlines
"~"
| Bool
otherwise = Text -> Text -> Inlines -> Inlines
B.link (Text
"mailto:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify Inlines
x) Text
"" Inlines
x
parsePa :: PandocMonad m => MdocParser m Inlines
parsePa :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePa = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Pa" Inlines -> Inlines
p
where p :: Inlines -> Inlines
p Inlines
x | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
x = Attr -> Inlines -> Inlines
B.spanWith (Text -> Attr
cls Text
"Pa") Inlines
"~"
| Bool
otherwise = Attr -> Inlines -> Inlines
B.spanWith (Text -> Attr
cls Text
"Pa") Inlines
x
parseFl :: PandocMonad m => MdocParser m Inlines
parseFl :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFl = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Fl"
Inlines
start <- Inlines -> MdocParser m Inlines -> MdocParser m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty (MdocParser m Inlines
emptyWithDelim MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Inlines
flfl MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Inlines
emptyWithMacro MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Inlines
emptyEmpty)
[Inlines]
segs <- MdocParser m Inlines
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill MdocParser m Inlines
segment ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
inlineContextEnd
[Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify ([Inlines
start] [Inlines] -> [Inlines] -> [Inlines]
forall a. Semigroup a => a -> a -> a
<> [Inlines]
segs)
where
emptyWithDelim :: MdocParser m Inlines
emptyWithDelim = do
ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken])
-> ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall a b. (a -> b) -> a -> b
$ MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 (DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Middle MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Close)
Inlines
ds <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
fl Text
"-" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ds
flfl :: MdocParser m Inlines
flfl = do
MdocParser m MdocToken -> MdocParser m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Fl")
Inline
x:[Inline]
xs <- Inlines -> [Inline]
forall a. Many a -> [a]
B.toList (Inlines -> [Inline])
-> MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inline]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFl
let xx :: Inlines
xx = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Fl") (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Inline -> Text
forall a. Walkable Inline a => a -> Text
stringify Inline
x
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
xx Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList [Inline]
xs
emptyWithMacro :: MdocParser m Inlines
emptyWithMacro = do
MdocParser m MdocToken -> MdocParser m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
anyMacro
Inlines
rest <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
fl Text
"-" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
rest
emptyEmpty :: MdocParser m Inlines
emptyEmpty = ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol ParsecT [MdocToken] MdocState m ()
-> Inlines -> MdocParser m Inlines
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Text -> Inlines
fl Text
"-"
segment :: MdocParser m Inlines
segment = do
(Inlines
openDelim, [Text]
inlines, Inlines
closeDelim) <- MdocParser m [Text] -> MdocParser m (Inlines, [Text], Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (MdocParser m [Text] -> MdocParser m (Inlines, [Text], Inlines))
-> MdocParser m [Text] -> MdocParser m (Inlines, [Text], Inlines)
forall a b. (a -> b) -> a -> b
$ [Text] -> MdocParser m [Text] -> MdocParser m [Text]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [Text]
forall a. Monoid a => a
mempty MdocParser m [Text]
forall (m :: * -> *). PandocMonad m => MdocParser m [Text]
litsToText
Inlines
inner <- ([Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify ([Inlines] -> MdocParser m Inlines)
-> ([Text] -> [Inlines]) -> [Text] -> MdocParser m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
fl) ([Text] -> [Inlines]) -> ([Text] -> [Text]) -> [Text] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall {a}. (IsString a, Semigroup a) => [a] -> [a]
flags) [Text]
inlines
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
openDelim Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
inner Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
closeDelim
fl :: Text -> Inlines
fl = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Fl")
flags :: [a] -> [a]
flags [] = [a
"-"]
flags [a]
xs = (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a
"-" a -> a -> a
forall a. Semigroup a => a -> a -> a
<>) [a]
xs
parseAr :: PandocMonad m => MdocParser m Inlines
parseAr :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAr = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
simpleInline Text
"Ar" Inlines -> Inlines
forall {t :: * -> *} {a}.
(Foldable t, Walkable Inline (t a)) =>
t a -> Inlines
ar
where ar :: t a -> Inlines
ar t a
x | t a -> Bool
forall a. t a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null t a
x = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"variable") Text
"file ..."
| Bool
otherwise = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"variable") (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ t a -> Text
forall a. Walkable Inline a => a -> Text
stringify t a
x
parseCm :: PandocMonad m => MdocParser m Inlines
parseCm :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseCm = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Cm"
parseIc :: PandocMonad m => MdocParser m Inlines
parseIc :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseIc = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Ic"
parseEr :: PandocMonad m => MdocParser m Inlines
parseEr :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEr = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Er"
parseCd :: PandocMonad m => MdocParser m Inlines
parseCd :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseCd = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Cd"
parseQl :: PandocMonad m => MdocParser m Inlines
parseQl :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQl = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Ql" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Ql") (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify
parseDq :: PandocMonad m => MdocParser m Inlines
parseDq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Dq" Inlines -> Inlines
B.doubleQuoted
parseDo :: PandocMonad m => MdocParser m Inlines
parseDo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Do" Text
"Dc" Inlines -> Inlines
B.doubleQuoted
parseSq :: PandocMonad m => MdocParser m Inlines
parseSq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Sq" Inlines -> Inlines
B.singleQuoted
parseSo :: PandocMonad m => MdocParser m Inlines
parseSo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"So" Text
"Sc" Inlines -> Inlines
B.singleQuoted
parseQq :: PandocMonad m => MdocParser m Inlines
parseQq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Qq" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"\"" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"\""
parseQo :: PandocMonad m => MdocParser m Inlines
parseQo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Qo" Text
"Qc" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"\"" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"\""
parsePq :: PandocMonad m => MdocParser m Inlines
parsePq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Pq" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"(" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
")"
parsePo :: PandocMonad m => MdocParser m Inlines
parsePo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Po" Text
"Pc" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"(" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
")"
parseBq :: PandocMonad m => MdocParser m Inlines
parseBq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Bq" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"]"
parseBo :: PandocMonad m => MdocParser m Inlines
parseBo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Bo" Text
"Bc" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"]"
parseOp :: PandocMonad m => MdocParser m Inlines
parseOp :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOp = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Op" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"]"
parseOo :: PandocMonad m => MdocParser m Inlines
parseOo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Oo" Text
"Oc" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"]"
parseBrq :: PandocMonad m => MdocParser m Inlines
parseBrq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBrq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Brq" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"{" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"}"
parseBro :: PandocMonad m => MdocParser m Inlines
parseBro :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBro = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Bro" Text
"Brc" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"{" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"}"
parseAq :: PandocMonad m => MdocParser m Inlines
parseAq :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAq = Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Aq" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"⟨" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"⟩"
parseAo :: PandocMonad m => MdocParser m Inlines
parseAo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAo = Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> (Inlines -> Inlines) -> MdocParser m Inlines
multilineEnclosure Text
"Ao" Text
"Ac" ((Inlines -> Inlines) -> MdocParser m Inlines)
-> (Inlines -> Inlines) -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ \Inlines
x -> Inlines
"⟨" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"⟩"
parseDl :: PandocMonad m => MdocParser m Blocks
parseDl :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDl = do
Inlines
inner <- Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"Dl" Inlines -> Inlines
forall a. a -> a
id
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Blocks
B.codeBlock (Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify Inlines
inner)
parseD1 :: PandocMonad m => MdocParser m Blocks
parseD1 :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseD1 = do
Inlines
inner <- Text -> (Inlines -> Inlines) -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> MdocParser m Inlines
lineEnclosure Text
"D1" Inlines -> Inlines
forall a. a -> a
id
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text -> Attr
cls Text
"display") (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
inner
parseNm :: PandocMonad m => MdocParser m Inlines
parseNm :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNm = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Nm"
Maybe Text
mnm <- (MdocState -> Maybe Text
progName (MdocState -> Maybe Text)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState)
(Inlines
op, Inlines
rg, Inlines
cl) <- MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines))
-> MdocParser m Inlines -> MdocParser m (Inlines, Inlines, Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> MdocParser m Inlines -> MdocParser m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsToInlines
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ case (Maybe Text
mnm, Inlines
rg) of
(Just Text
nm, Inlines
x) | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
x ->
Inlines
op Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
ok Text
nm Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
cl
(Maybe Text
_, Inlines
x) ->
Inlines
op Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> (Text -> Inlines
ok (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify) Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
cl
where
ok :: Text -> Inlines
ok = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Nm")
parseXr :: PandocMonad m => MdocParser m Inlines
parseXr :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseXr = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Xr"
(Inlines
open, (Text
name, Text
section), Inlines
close) <- MdocParser m (Text, Text)
-> MdocParser m (Inlines, (Text, Text), Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs MdocParser m (Text, Text)
f
let ref :: Text
ref = Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
section Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
open Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Attr -> Inlines -> Inlines
B.spanWith (Text -> Attr
cls Text
"Xr") (Text -> Inlines
B.str Text
ref) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
close
where
f :: MdocParser m (Text, Text)
f = do
MdocToken
n <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit MdocParser m MdocToken -> String -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"Xr manual name"
MdocToken
s <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit MdocParser m MdocToken -> String -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"Xr manual section"
(Text, Text) -> MdocParser m (Text, Text)
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (MdocToken -> Text
toString MdocToken
n, MdocToken -> Text
toString MdocToken
s)
parseIn :: PandocMonad m => MdocParser m Inlines
parseIn :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseIn = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"In"
Inlines
openClose <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
Inlines
openOpen <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters
Text
header <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Inlines
close <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines -> Inlines
open Inlines
openClose Inlines
openOpen Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"In") (Text
"<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
header Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
close
where
open :: Inlines -> Inlines -> Inlines
open Inlines
a Inlines
b
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
a = Inlines
b
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
b = Inlines
a
| Bool
otherwise = Inlines
a Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
b
parseFd :: PandocMonad m => MdocParser m Inlines
parseFd :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFd = Text -> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m Inlines
codeLikeInline Text
"Fd"
parseFt :: PandocMonad m => MdocParser m Inlines
parseFt :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFt = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
"Ft" Text
"variable"
formatFunction :: T.Text -> [Inlines] -> Inlines
formatFunction :: Text -> [Inlines] -> Inlines
formatFunction Text
nm [Inlines]
args = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Fn") Text
nm Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"(" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
args' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
")"
where
args' :: Inlines
args' = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Inlines
", ") [Inlines]
args
parseFn :: PandocMonad m => MdocParser m Inlines
parseFn :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFn = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Fn"
(Inlines
op, (Text
nm, [Text]
args), Inlines
cl) <- MdocParser m (Text, [Text])
-> MdocParser m (Inlines, (Text, [Text]), Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs MdocParser m (Text, [Text])
f
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
op Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> [Inlines] -> Inlines
formatFunction Text
nm ((Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"variable")) [Text]
args) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
cl
where
f :: MdocParser m (Text, [Text])
f = do
Text
nm <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
[Text]
args <- [Text]
-> ParsecT [MdocToken] MdocState m [Text]
-> ParsecT [MdocToken] MdocState m [Text]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] ParsecT [MdocToken] MdocState m [Text]
forall (m :: * -> *). PandocMonad m => MdocParser m [Text]
litsToText
(Text, [Text]) -> MdocParser m (Text, [Text])
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
nm, [Text]
args)
parseFa :: PandocMonad m => MdocParser m Inlines
parseFa :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFa = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
codeLikeInline' Text
"Fa" Text
"variable"
parseFo :: PandocMonad m => MdocParser m Inlines
parseFo :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFo = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Fo"
Text
nm <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Inlines]
args <- MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFa MdocParser m Inlines -> MdocParser m () -> MdocParser m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Fc"
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> [Inlines] -> Inlines
formatFunction Text
nm [Inlines]
args
parseLk :: PandocMonad m => MdocParser m Inlines
parseLk :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLk = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Lk"
Inlines
openClose <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
Inlines
openOpen <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters
Text
url <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Inlines
inner <- MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m Inlines
segment ParsecT [MdocToken] MdocState m [Inlines]
-> ([Inlines] -> MdocParser m Inlines) -> MdocParser m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> (a -> ParsecT [MdocToken] MdocState m b)
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify
Inlines
close <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters
let label :: Inlines
label | Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
inner = Text -> Inlines
B.str Text
url
| Bool
otherwise = Inlines
inner
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines -> Inlines
open Inlines
openClose Inlines
openOpen Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> Inlines -> Inlines
B.link Text
url Text
"" Inlines
label Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
close
where
open :: Inlines -> Inlines -> Inlines
open Inlines
a Inlines
b
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
a = Inlines
b
| Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
b = Inlines
a
| Bool
otherwise = Inlines
a Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
b
end :: ParsecT [MdocToken] st m MdocToken
end = (MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
forall (m :: * -> *) st.
Monad m =>
(MdocToken -> Bool) -> ParsecT [MdocToken] st m MdocToken
msatisfy MdocToken -> Bool
newControlContext
segment :: MdocParser m Inlines
segment = do
Inlines
a <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
openingDelimiters
Inlines
m <- Inlines -> MdocParser m Inlines -> MdocParser m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsToInlines
Inlines
z <-
MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
closingDelimiters MdocParser m Inlines
-> ParsecT [MdocToken] MdocState m () -> MdocParser m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MdocParser m MdocToken
forall {st}. ParsecT [MdocToken] st m MdocToken
end)
MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> MdocParser m Inlines -> MdocParser m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
pipes
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Inlines -> Bool) -> [Inlines] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inlines
a, Inlines
m, Inlines
z]
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
a Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
m Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
z
parsebr :: PandocMonad m => MdocParser m Inlines
parsebr :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsebr = Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"br" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak
parseNs :: PandocMonad m => MdocParser m Inlines
parseNs :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNs = Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ns" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
noSpace
parsePf :: PandocMonad m => MdocParser m Inlines
parsePf :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePf = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Pf"
Text
t <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m t
anyToken
[MdocToken]
rest <- ParsecT [MdocToken] MdocState m [MdocToken]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
SourcePos
pos <- ParsecT [MdocToken] MdocState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
[MdocToken] -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([MdocToken] -> ParsecT [MdocToken] MdocState m ())
-> [MdocToken] -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ (Text -> SourcePos -> MdocToken
Macro Text
"Ns" SourcePos
pos)MdocToken -> [MdocToken] -> [MdocToken]
forall a. a -> [a] -> [a]
:[MdocToken]
rest
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
t
parseAp :: PandocMonad m => MdocParser m Inlines
parseAp :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAp = Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ap" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
apMacro
parseEx :: PandocMonad m => MdocParser m Inlines
parseEx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEx = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ex"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-std"
[Text]
args <- (MdocToken -> Text) -> [MdocToken] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MdocToken -> Text
toString ([MdocToken] -> [Text])
-> ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Maybe Text
pn <- MdocState -> Maybe Text
progName (MdocState -> Maybe Text)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
"The"
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Maybe Text -> [Text] -> Inlines
utils Maybe Text
pn [Text]
args
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"0 on success, and >0 if an error occurs."
where
nm :: Text -> Inlines
nm = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Nm")
sing :: Inlines
sing = Inlines
"utility exits"
plur :: Inlines
plur = Inlines
"utilities exit"
utils :: Maybe Text -> [Text] -> Inlines
utils (Just Text
x) [] = Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing
utils Maybe Text
_ [Text
x] = Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing
utils Maybe Text
_ [Text
x,Text
y] = Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"and" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
nm Text
y Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
plur
utils Maybe Text
pn [Text]
xs =
case (Maybe Text
pn, [Text] -> Maybe ([Text], Text)
forall a. [a] -> Maybe ([a], a)
unsnoc [Text]
xs) of
(Maybe Text
Nothing, Maybe ([Text], Text)
Nothing) -> Inlines
sing
(Maybe Text
_, Just ([Text]
hd, Text
end)) -> [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ((Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Inlines
", ") ([Inlines] -> [Inlines])
-> ([Text] -> [Inlines]) -> [Text] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
nm) [Text]
hd) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
", and " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
nm Text
end Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
plur
(Just Text
p, Maybe ([Text], Text)
Nothing) -> Text -> Inlines
nm Text
p Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing
parseRv :: (PandocMonad m) => MdocParser m Inlines
parseRv :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRv = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Rv"
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-std"
[Text]
args <- (MdocToken -> Text) -> [MdocToken] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MdocToken -> Text
toString ([MdocToken] -> [Text])
-> ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Maybe Text
pn <- MdocState -> Maybe Text
progName (MdocState -> Maybe Text)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Maybe Text -> [Text] -> Inlines
go Maybe Text
pn [Text]
args
where
nm :: Text -> Inlines
nm Text
a = Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"Fn") Text
a Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"()"
nothing :: Inlines
nothing = Inlines
"Upon successful completion, the value 0 is returned;"
sing :: Inlines
sing = Inlines
"function returns"
plur :: Inlines
plur = Inlines
"functions return"
success :: Inlines
success = Inlines
"the value 0 if successful;"
errno :: Inlines
errno =
Inlines
"otherwise the value -1 is returned and the global variable"
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Attr -> Text -> Inlines
B.codeWith (Text -> Attr
cls Text
"variable") Text
"errno"
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"is set to indicate the error."
message :: Inlines -> Inlines
message Inlines
conj =
Inlines
"The"
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
conj
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
success
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
errno
go :: Maybe Text -> [Text] -> Inlines
go (Just Text
x) [] = Inlines -> Inlines
message (Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing)
go Maybe Text
_ [Text
x] = Inlines -> Inlines
message (Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing)
go Maybe Text
_ [Text
x, Text
y] = Inlines -> Inlines
message (Text -> Inlines
nm Text
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"and" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
nm Text
y Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
plur)
go Maybe Text
pn [Text]
xs =
case (Maybe Text
pn, [Text] -> Maybe ([Text], Text)
forall a. [a] -> Maybe ([a], a)
unsnoc [Text]
xs) of
(Maybe Text
Nothing, Maybe ([Text], Text)
Nothing) -> Inlines
nothing Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
errno
(Maybe Text
_, Just ([Text]
hd, Text
end)) -> Inlines -> Inlines
message ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ((Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Inlines
", ") ([Inlines] -> [Inlines])
-> ([Text] -> [Inlines]) -> [Text] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
nm) [Text]
hd) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
", and " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
nm Text
end Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
plur)
(Just Text
p, Maybe ([Text], Text)
Nothing) -> Inlines -> Inlines
message (Text -> Inlines
nm Text
p Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sing)
parseSt :: PandocMonad m => MdocParser m Inlines
parseSt :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSt = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"St"
(Lit Text
std SourcePos
pos) <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
case Text -> Maybe Text
standard Text
std of
Maybe Text
Nothing -> do
LogMessage -> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> ParsecT [MdocToken] MdocState m ())
-> LogMessage -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent (Text
"unrecognized argument to St: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
std) SourcePos
pos
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
Just Text
t -> Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text Text
t
parseLb :: PandocMonad m => MdocParser m Inlines
parseLb :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLb = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Lb"
Text
library <- MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
"library" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
B.doubleQuoted (Text -> Inlines
B.str Text
library)
unixVersion :: PandocMonad m => T.Text -> T.Text -> MdocParser m Inlines
unixVersion :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
unixVersion Text
m Text
s = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
m
(Inlines
o, Text
v, Inlines
c) <- MdocParser m Text -> MdocParser m (Inlines, Text, Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (Text -> MdocParser m Text -> MdocParser m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (MdocToken -> Text
toString (MdocToken -> Text) -> MdocParser m MdocToken -> MdocParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit))
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
o Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
s Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
f Text
v Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
c
where
f :: Text -> Inlines
f Text
v | Text -> Bool
T.null Text
v = Inlines
forall a. Monoid a => a
mempty
| Bool
otherwise = Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
v
parseAt :: PandocMonad m => MdocParser m Inlines
parseAt :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAt = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"At"
(Inlines
o, Maybe Text
v, Inlines
c) <- MdocParser m (Maybe Text)
-> MdocParser m (Inlines, Maybe Text, Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (ParsecT [MdocToken] MdocState m Text -> MdocParser m (Maybe Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (MdocToken -> Text
toString (MdocToken -> Text)
-> MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit))
let v' :: Text
v' = Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"AT&T UNIX" Text -> Text
attVer Maybe Text
v
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
o Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.text Text
v' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
c
where
isVersion :: a -> Bool
isVersion a
x = a
x a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"1", a
"2", a
"3", a
"4", a
"5", a
"6", a
"7"]
isRelease :: a -> Bool
isRelease a
x = a
x a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"1", a
"2", a
"3", a
"4"]
attVer :: Text -> Text
attVer (Text -> Text -> Maybe Text
T.stripPrefix Text
"v" -> Just Text
ver)
| Text -> Bool
forall {a}. (Eq a, IsString a) => a -> Bool
isVersion Text
ver = Text
"Version " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" AT&T UNIX"
attVer Text
"32v" = Text
"Version 7 AT&T UNIX/32V"
attVer Text
"III" = Text
"AT&T System III UNIX"
attVer (Text -> Text -> Maybe Text
T.stripPrefix Text
"V." -> Just Text
release)
| Text -> Bool
forall {a}. (Eq a, IsString a) => a -> Bool
isRelease Text
release = Text
"AT&T System V Release " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
release Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" UNIX"
attVer Text
"V" = Text
"AT&T System V UNIX"
attVer Text
x = Text
"AT&T UNIX " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x
parseBsx :: PandocMonad m => MdocParser m Inlines
parseBsx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBsx = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
unixVersion Text
"Bsx" Text
"BSD/OS"
parseBx :: PandocMonad m => MdocParser m Inlines
parseBx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBx = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Bx"
(Inlines
o, [Text]
v, Inlines
c) <- MdocParser m [Text] -> MdocParser m (Inlines, [Text], Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs MdocParser m [Text]
zeroToTwoLits
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
o Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Text] -> Inlines
bsd [Text]
v Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
c
where
zeroToTwoLits :: MdocParser m [Text]
zeroToTwoLits = do
[MdocToken]
toks <- ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Int
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit) ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
1 MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
0 MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit
[Text] -> MdocParser m [Text]
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> MdocParser m [Text]) -> [Text] -> MdocParser m [Text]
forall a b. (a -> b) -> a -> b
$ MdocToken -> Text
toString (MdocToken -> Text) -> [MdocToken] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [MdocToken]
toks
bsd :: [Text] -> Inlines
bsd [] = Text -> Inlines
B.str Text
"BSD"
bsd [Text
x] = Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"BSD"
bsd (Text
x:Text
y:[Text]
_) = Text -> Inlines
B.str (Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"BSD" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
T.toTitle Text
y)
parseDx :: PandocMonad m => MdocParser m Inlines
parseDx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDx = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
unixVersion Text
"Dx" Text
"DragonFly"
parseFx :: PandocMonad m => MdocParser m Inlines
parseFx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFx = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
unixVersion Text
"Fx" Text
"FreeBSD"
parseNx :: PandocMonad m => MdocParser m Inlines
parseNx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNx = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Nx"
(Inlines
o, Text
v, Inlines
c) <- MdocParser m Text -> MdocParser m (Inlines, Text, Inlines)
forall (m :: * -> *) x.
PandocMonad m =>
MdocParser m x -> MdocParser m (Inlines, x, Inlines)
delimitedArgs (Text -> MdocParser m Text -> MdocParser m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (MdocToken -> Text
toString (MdocToken -> Text) -> MdocParser m MdocToken -> MdocParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit))
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
o Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
"NetBSD" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
f Text
v Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
c
where
f :: Text -> Inlines
f Text
v | Text -> Bool
T.null Text
v = Inlines
forall a. Monoid a => a
mempty
| Bool
otherwise = Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str (Text -> Either PandocError Text -> Text
forall b a. b -> Either a b -> b
fromRight Text
v (Either PandocError Text -> Text)
-> Either PandocError Text -> Text
forall a b. (a -> b) -> a -> b
$ Parsec Sources () Text -> () -> Text -> Either PandocError Text
forall t st a.
ToSources t =>
Parsec Sources st a -> st -> t -> Either PandocError a
readWith Parsec Sources () Text
forall {u}. ParsecT Sources u Identity Text
earlyNetBSDVersion () Text
v)
earlyNetBSDVersion :: ParsecT Sources u Identity Text
earlyNetBSDVersion = do
Char
major <- String -> ParsecT Sources u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
"01"
Char
dot <- Char -> ParsecT Sources u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.'
Char
minor <- ParsecT Sources u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
Char
ltr <- (Char -> Bool) -> ParsecT Sources u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isAsciiLower
Text -> ParsecT Sources u Identity Text
forall a. a -> ParsecT Sources u Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources u Identity Text)
-> Text -> ParsecT Sources u Identity Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
major, Char
dot, Char
minor, Char -> Char
toUpper Char
ltr]
parseOx :: PandocMonad m => MdocParser m Inlines
parseOx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOx = Text -> Text -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> MdocParser m Inlines
unixVersion Text
"Ox" Text
"OpenBSD"
parseUx :: PandocMonad m => MdocParser m Inlines
parseUx :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseUx = Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ux" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str Text
"UNIX")
parseInlineMacro :: PandocMonad m => MdocParser m Inlines
parseInlineMacro :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlineMacro = [ParsecT [MdocToken] MdocState m Inlines]
-> ParsecT [MdocToken] MdocState m Inlines
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT [MdocToken] MdocState m Inlines]
forall (m :: * -> *). PandocMonad m => [MdocParser m Inlines]
synopsisTopicMacros [ParsecT [MdocToken] MdocState m Inlines]
-> [ParsecT [MdocToken] MdocState m Inlines]
-> [ParsecT [MdocToken] MdocState m Inlines]
forall a. Semigroup a => a -> a -> a
<> [ParsecT [MdocToken] MdocState m Inlines]
forall (m :: * -> *). PandocMonad m => [MdocParser m Inlines]
otherInlineMacros) ParsecT [MdocToken] MdocState m Inlines
-> String -> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"inline macro"
synopsisTopicMacros :: PandocMonad m => [MdocParser m Inlines]
synopsisTopicMacros :: forall (m :: * -> *). PandocMonad m => [MdocParser m Inlines]
synopsisTopicMacros =
[MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNm, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseCd, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFd, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFn, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFo, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseIn, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseVt, MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFt]
otherInlineMacros :: PandocMonad m => [MdocParser m Inlines]
otherInlineMacros :: forall (m :: * -> *). PandocMonad m => [MdocParser m Inlines]
otherInlineMacros =
[ MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSy,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEm,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLk,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLi,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEv,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDv,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseMt,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePa,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFl,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseCm,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseIc,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEr,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAd,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseVa,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAn,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseMs,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAr,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFa,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseTn,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseXr,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQl,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOp,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBrq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAq,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseQo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBro,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOo,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBf,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRsInline,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseEx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRv,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSt,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseLb,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAt,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBsx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseDx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseFx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseOx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseUx,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsebr,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseAp,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parsePf,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseNs,
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
skipUnsupportedInlines
]
parseInline :: PandocMonad m => MdocParser m Inlines
parseInline :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline = MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseStrs MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT [MdocToken] MdocState m [Inlines]
controlLine ParsecT [MdocToken] MdocState m [Inlines]
-> ([Inlines] -> MdocParser m Inlines) -> MdocParser m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> (a -> ParsecT [MdocToken] MdocState m b)
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Inlines] -> MdocParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify) MdocParser m Inlines -> String -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"text lines or inline macros"
where
safeEol :: ParsecT [MdocToken] MdocState m ()
safeEol = do
Bool
amNested <- MdocState -> Bool
inLineEnclosure (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
amNested (ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
controlLine :: ParsecT [MdocToken] MdocState m [Inlines]
controlLine = MdocParser m Inlines -> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ((MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlineMacro MdocParser m Inlines
-> MdocParser m Inlines -> MdocParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines) MdocParser m Inlines
-> ParsecT [MdocToken] MdocState m () -> MdocParser m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
safeEol)
parseInlines :: PandocMonad m => MdocParser m Inlines
parseInlines :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines = ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline) ParsecT [MdocToken] MdocState m [Inlines]
-> ([Inlines] -> ParsecT [MdocToken] MdocState m Inlines)
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> (a -> ParsecT [MdocToken] MdocState m b)
-> ParsecT [MdocToken] MdocState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify
parsePara :: PandocMonad m => MdocParser m Blocks
parsePara :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parsePara = Inlines -> Blocks
B.para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Blocks)
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Blocks
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp" ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Lp")
parseDisplay :: PandocMonad m => MdocParser m Blocks
parseDisplay :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDisplay = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-filled" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-ragged" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-centered"
MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken])
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall a b. (a -> b) -> a -> b
$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-offset" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit) MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-compact")
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Attr -> Blocks -> Blocks
B.divWith (Text -> Attr
cls Text
"display") (Blocks -> Blocks) -> ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m [Blocks] -> MdocParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m Blocks -> ParsecT [MdocToken] MdocState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock
parseUnfilled :: PandocMonad m => MdocParser m Blocks
parseUnfilled :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseUnfilled = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-unfilled"
MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken])
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall a b. (a -> b) -> a -> b
$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-offset" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit) MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-compact")
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Maybe Inlines]
lns <- ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m [Maybe Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m [Maybe Inlines])
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m [Maybe Inlines]
forall a b. (a -> b) -> a -> b
$ Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines)
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
parseStrPreserveSpace
ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Inlines
forall a. Maybe a
Nothing Maybe Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle
ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines)
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline
ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just Inlines
"" Maybe Inlines
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Maybe Inlines)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp"
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Blocks
B.lineBlock ([Maybe Inlines] -> [Inlines]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Inlines]
lns)
where
parseStrPreserveSpace :: ParsecT [MdocToken] MdocState m Inlines
parseStrPreserveSpace = (Text -> Inlines
B.str (Text -> Inlines) -> (MdocToken -> Text) -> MdocToken -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString) (MdocToken -> Inlines)
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
str ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
blank MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m Inlines
forall a. Monoid a => a
mempty)
parseCodeBlock :: PandocMonad m => MdocParser m Blocks
parseCodeBlock :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseCodeBlock = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-literal"
MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken])
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall a b. (a -> b) -> a -> b
$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-offset" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit) MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-compact")
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Maybe Text]
lns <- ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m [Maybe Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m [Maybe Text])
-> ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m [Maybe Text]
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> (MdocToken -> Text) -> MdocToken -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MdocToken -> Text
toString (MdocToken -> Maybe Text)
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
str MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
blank)
ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Text
forall a. Maybe a
Nothing Maybe Text
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle
ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> (Inlines -> Text) -> Inlines -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify (Inlines -> Maybe Text)
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline
ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"" Maybe Text
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Maybe Text)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp"
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Blocks
B.codeBlock ([Text] -> Text
T.unlines ([Maybe Text] -> [Text]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Text]
lns))
parseBd :: PandocMonad m => MdocParser m Blocks
parseBd :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBd = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Bd"
Blocks
blk <- MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseCodeBlock MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDisplay MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseUnfilled
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Ed"
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
blk
parseBf :: PandocMonad m => MdocParser m Inlines
parseBf :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseBf = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Bf"
Inlines -> Inlines
xform <- Inlines -> Inlines
B.strong (Inlines -> Inlines)
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"Sy" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-symbolic")
ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> Inlines
B.emph (Inlines -> Inlines)
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"Em" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-emphasis")
ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> Inlines
code (Inlines -> Inlines)
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m (Inlines -> Inlines)
forall a b.
a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"Li" MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-literal")
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
Inlines
ins <- MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Ef"
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
xform Inlines
ins
where
code :: Inlines -> Inlines
code = Text -> Inlines
B.code (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify
skipListArgument :: (PandocMonad m) => MdocParser m ()
skipListArgument :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
skipListArgument =
ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ [ParsecT [MdocToken] MdocState m MdocToken]
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-width" ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit,
Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-offset" ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
lit,
Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-compact"
]
parseItemList :: PandocMonad m => MdocParser m Blocks
parseItemList :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseItemList = do
[Blocks] -> Blocks
f <- ([ParsecT [MdocToken] MdocState m MdocToken]
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ((Text -> ParsecT [MdocToken] MdocState m MdocToken)
-> [Text] -> [ParsecT [MdocToken] MdocState m MdocToken]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal [Text
"-bullet", Text
"-dash", Text
"-hyphen", Text
"-item"]) ParsecT [MdocToken] MdocState m MdocToken
-> ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m ([Blocks] -> Blocks)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> [Blocks] -> Blocks
B.bulletList)
ParsecT [MdocToken] MdocState m ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m ([Blocks] -> Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-enum" ParsecT [MdocToken] MdocState m MdocToken
-> ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m ([Blocks] -> Blocks)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> [Blocks] -> Blocks
B.orderedList
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
skipListArgument
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Blocks]
items <- MdocParser m Blocks -> ParsecT [MdocToken] MdocState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m Blocks
bulletItem
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
f [Blocks]
items
where
bulletItem :: MdocParser m Blocks
bulletItem = do
Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"It"
[Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m [Blocks] -> MdocParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MdocParser m Blocks -> ParsecT [MdocToken] MdocState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock
parseDefinitionList :: PandocMonad m => MdocParser m Blocks
parseDefinitionList :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDefinitionList = do
ParsecT [MdocToken] MdocState m Inlines
headParser <- ([ParsecT [MdocToken] MdocState m MdocToken]
-> ParsecT [MdocToken] MdocState m MdocToken
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT [MdocToken] MdocState m MdocToken]
-> ParsecT [MdocToken] MdocState m MdocToken)
-> ([Text] -> [ParsecT [MdocToken] MdocState m MdocToken])
-> [Text]
-> ParsecT [MdocToken] MdocState m MdocToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ParsecT [MdocToken] MdocState m MdocToken)
-> [Text] -> [ParsecT [MdocToken] MdocState m MdocToken]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal) [Text
"-hang", Text
"-inset", Text
"-ohang", Text
"-tag"] ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT
[MdocToken] MdocState m (ParsecT [MdocToken] MdocState m Inlines)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ParsecT [MdocToken] MdocState m Inlines
parsedHead ParsecT
[MdocToken] MdocState m (ParsecT [MdocToken] MdocState m Inlines)
-> ParsecT
[MdocToken] MdocState m (ParsecT [MdocToken] MdocState m Inlines)
-> ParsecT
[MdocToken] MdocState m (ParsecT [MdocToken] MdocState m Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-diag" ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT
[MdocToken] MdocState m (ParsecT [MdocToken] MdocState m Inlines)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ParsecT [MdocToken] MdocState m Inlines
diagHead
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
skipListArgument
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[(Inlines, [Blocks])]
items <- ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
-> ParsecT [MdocToken] MdocState m [(Inlines, [Blocks])]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
-> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
forall a. Monoid a => a
mempty ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
-> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
-> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m (Inlines, [Blocks])
forall {m :: * -> *} {a}.
PandocMonad m =>
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m (a, [Blocks])
dlItem ParsecT [MdocToken] MdocState m Inlines
headParser)
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList [(Inlines, [Blocks])]
items
where
parsedHead :: ParsecT [MdocToken] MdocState m Inlines
parsedHead = ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT [MdocToken] MdocState m Inlines
xoListHead ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [MdocToken] MdocState m Inlines
eolListHead
eolListHead :: ParsecT [MdocToken] MdocState m Inlines
eolListHead = do
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = True}
Inlines
inner <- ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{inLineEnclosure = False}
Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
inner
diagHead :: ParsecT [MdocToken] MdocState m Inlines
diagHead = ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
argsToInlines
dlItem :: ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m (a, [Blocks])
dlItem ParsecT [MdocToken] MdocState m a
hed = do
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m ())
-> (Text -> ParsecT [MdocToken] MdocState m MdocToken)
-> Text
-> ParsecT [MdocToken] MdocState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro) Text
"Pp" ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m ()
skipUnsupportedMacro Text
"Tg")
Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"It"
a
dt <- ParsecT [MdocToken] MdocState m a
hed
Blocks
dd <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [MdocToken] MdocState m [Blocks]
-> ParsecT [MdocToken] MdocState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock
(a, [Blocks]) -> ParsecT [MdocToken] MdocState m (a, [Blocks])
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
dt, [Blocks
dd])
xoListHead :: ParsecT [MdocToken] MdocState m Inlines
xoListHead = do
Inlines
before <- Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInline
Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Xo"
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[Inlines]
after <- ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines (Text -> ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Xc")
[Inlines] -> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *).
PandocMonad m =>
[Inlines] -> MdocParser m Inlines
spacify (Inlines
beforeInlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
:[Inlines]
after)
parseColumnList :: PandocMonad m => MdocParser m Blocks
parseColumnList :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseColumnList = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"-column"
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
skipListArgument
MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken])
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall a b. (a -> b) -> a -> b
$ MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
arg MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Open MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Middle MdocParser m MdocToken
-> MdocParser m MdocToken -> MdocParser m MdocToken
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DelimSide -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
DelimSide -> MdocParser m MdocToken
delim DelimSide
Close
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
[[Blocks]]
rows <- ParsecT [MdocToken] MdocState m [Blocks]
-> ParsecT [MdocToken] MdocState m [[Blocks]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [MdocToken] MdocState m [Blocks]
listRow
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MdocParser m Blocks) -> Blocks -> MdocParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [[Blocks]] -> Blocks
B.simpleTable [] [[Blocks]]
rows
where
listRow :: ParsecT [MdocToken] MdocState m [Blocks]
listRow = do
MdocParser m MdocToken -> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp")
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"It"
(Inlines -> Blocks) -> [Inlines] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Blocks
B.plain ([Inlines] -> [Blocks])
-> ParsecT [MdocToken] MdocState m [Inlines]
-> ParsecT [MdocToken] MdocState m [Blocks]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
-> MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepBy (ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseInlines ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inlines -> ParsecT [MdocToken] MdocState m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
forall a. Monoid a => a
mempty) (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Ta" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m () -> MdocParser m MdocToken
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol)
parseBl :: PandocMonad m => MdocParser m Blocks
parseBl :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBl = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Bl"
Blocks
blk <- MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseItemList MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDefinitionList MdocParser m Blocks -> MdocParser m Blocks -> MdocParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MdocParser m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseColumnList
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"El"
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
blk
referenceField :: PandocMonad m => T.Text -> ReferenceField -> MdocParser m ()
referenceField :: forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
m ReferenceField
field = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
m
MdocReference
reference <- MdocState -> MdocReference
currentReference (MdocState -> MdocReference)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocReference
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Text
contents <- Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify (Inlines -> Text)
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
litsAndDelimsToInlines
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
(MdocState -> MdocState) -> MdocParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> MdocParser m ())
-> (MdocState -> MdocState) -> MdocParser m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{currentReference = M.insertWith (++) field [contents] reference}
() -> MdocParser m ()
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
parsePercentA :: PandocMonad m => MdocParser m ()
parsePercentA :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentA = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%A" ReferenceField
Author
parsePercentB :: PandocMonad m => MdocParser m ()
parsePercentB :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentB = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%B" ReferenceField
BookTitle
parsePercentC :: PandocMonad m => MdocParser m ()
parsePercentC :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentC = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%C" ReferenceField
PubLocation
parsePercentD :: PandocMonad m => MdocParser m ()
parsePercentD :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentD = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%D" ReferenceField
PubDate
parsePercentI :: PandocMonad m => MdocParser m ()
parsePercentI :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentI = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%I" ReferenceField
Publisher
parsePercentJ :: PandocMonad m => MdocParser m ()
parsePercentJ :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentJ = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%J" ReferenceField
Journal
parsePercentN :: PandocMonad m => MdocParser m ()
parsePercentN :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentN = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%N" ReferenceField
IssueNumber
parsePercentO :: PandocMonad m => MdocParser m ()
parsePercentO :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentO = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%O" ReferenceField
Optional
parsePercentP :: PandocMonad m => MdocParser m ()
parsePercentP :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentP = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%P" ReferenceField
Pages
parsePercentQ :: PandocMonad m => MdocParser m ()
parsePercentQ :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentQ = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%Q" ReferenceField
Institution
parsePercentR :: PandocMonad m => MdocParser m ()
parsePercentR :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentR = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%R" ReferenceField
TechReportTitle
parsePercentT :: PandocMonad m => MdocParser m ()
parsePercentT :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentT = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%T" ReferenceField
ArticleTitle
parsePercentU :: PandocMonad m => MdocParser m ()
parsePercentU :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentU = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%U" ReferenceField
Url
parsePercentV :: PandocMonad m => MdocParser m ()
parsePercentV :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentV = Text -> ReferenceField -> MdocParser m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> ReferenceField -> MdocParser m ()
referenceField Text
"%V" ReferenceField
VolumeNumber
parseReferenceField :: PandocMonad m => MdocParser m ()
parseReferenceField :: forall (m :: * -> *). PandocMonad m => MdocParser m ()
parseReferenceField =
[ParsecT [MdocToken] MdocState m ()]
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentA,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentB,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentC,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentD,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentI,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentJ,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentN,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentO,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentP,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentQ,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentR,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentT,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentU,
ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parsePercentV
]
parseRsInline :: PandocMonad m => MdocParser m Inlines
parseRsInline :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRsInline = do
MdocSection
sec <- MdocState -> MdocSection
currentSection (MdocState -> MdocSection)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocSection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT [MdocToken] MdocState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [MdocToken] MdocState m ())
-> Bool -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ MdocSection
sec MdocSection -> MdocSection -> Bool
forall a. Eq a => a -> a -> Bool
/= MdocSection
ShSeeAlso
MdocParser m Inlines
forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRs
parseRs :: PandocMonad m => MdocParser m Inlines
parseRs :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseRs = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Rs"
(MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ())
-> (MdocState -> MdocState) -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{currentReference = M.empty}
ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
parseReferenceField
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Re"
MdocReference
ref <- MdocState -> MdocReference
currentReference (MdocState -> MdocReference)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m MdocReference
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ ((Text -> [Text] -> Text) -> Text -> MdocReference -> Text
forall a b k. (a -> b -> a) -> a -> Map k b -> a
M.foldl Text -> [Text] -> Text
f Text
forall a. Monoid a => a
mempty MdocReference
ref) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"."
where join :: [Text] -> Text
join [Text]
v = [Text] -> Text
T.concat (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
", " [Text]
v)
f :: Text -> [Text] -> Text
f Text
a [Text]
v | Text -> Bool
T.null Text
a = [Text] -> Text
join [Text]
v
| Bool
otherwise = Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
join [Text]
v
skipBlanks :: PandocMonad m => MdocParser m Blocks
skipBlanks :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
skipBlanks = ParsecT [MdocToken] MdocState m MdocToken
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [MdocToken] MdocState m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
blank ParsecT [MdocToken] MdocState m [MdocToken]
-> ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m Blocks
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m Blocks
forall a. Monoid a => a
mempty
parseSmToggle :: PandocMonad m => MdocParser m Inlines
parseSmToggle :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
parseSmToggle = do
Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
"Sm"
Bool
cur <- MdocState -> Bool
spacingMode (MdocState -> Bool)
-> ParsecT [MdocToken] MdocState m MdocState
-> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [MdocToken] MdocState m MdocState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Maybe Bool
mode <- ParsecT [MdocToken] MdocState m Bool
-> ParsecT [MdocToken] MdocState m (Maybe Bool)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"on" MdocParser m MdocToken
-> Bool -> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
True ParsecT [MdocToken] MdocState m Bool
-> ParsecT [MdocToken] MdocState m Bool
-> ParsecT [MdocToken] MdocState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
literal Text
"off" MdocParser m MdocToken
-> Bool -> ParsecT [MdocToken] MdocState m Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
False)
MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
let newMode :: Bool
newMode = Maybe Bool -> Bool -> Bool
update Maybe Bool
mode Bool
cur
(MdocState -> MdocState) -> MdocParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
modifyState ((MdocState -> MdocState) -> MdocParser m ())
-> (MdocState -> MdocState) -> MdocParser m ()
forall a b. (a -> b) -> a -> b
$ \MdocState
s -> MdocState
s{spacingMode = newMode}
Inlines -> MdocParser m Inlines
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> MdocParser m Inlines)
-> Inlines -> MdocParser m Inlines
forall a b. (a -> b) -> a -> b
$ if Bool
newMode then Inlines
smOn else Inlines
smOff
where
update :: Maybe Bool -> Bool -> Bool
update = \case
Maybe Bool
Nothing -> Bool -> Bool
not
Just Bool
x -> Bool -> Bool -> Bool
forall a b. a -> b -> a
const Bool
x
skipUnsupportedMacro :: PandocMonad m => T.Text -> MdocParser m ()
skipUnsupportedMacro :: forall (m :: * -> *). PandocMonad m => Text -> MdocParser m ()
skipUnsupportedMacro Text
nm = do
(Macro Text
_ SourcePos
pos) <- Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
macro Text
nm
MdocParser m MdocToken
-> MdocParser m () -> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill MdocParser m MdocToken
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m t
anyToken MdocParser m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
LogMessage -> MdocParser m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> MdocParser m ()) -> LogMessage -> MdocParser m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent (Text
"unsupported macro: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
nm) SourcePos
pos
skipUnsupportedInlines :: PandocMonad m => MdocParser m Inlines
skipUnsupportedInlines :: forall (m :: * -> *). PandocMonad m => MdocParser m Inlines
skipUnsupportedInlines = [ParsecT [MdocToken] MdocState m ()]
-> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ Text -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m ()
skipUnsupportedMacro Text
"Tg",
Text -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m ()
skipUnsupportedMacro Text
"Bk",
Text -> ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => Text -> MdocParser m ()
skipUnsupportedMacro Text
"Ek"
] ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m Inlines
-> ParsecT [MdocToken] MdocState m Inlines
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m Inlines
forall a. Monoid a => a
mempty
skipUnknownMacro :: PandocMonad m => MdocParser m Blocks
skipUnknownMacro :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
skipUnknownMacro = do
SourcePos
pos <- ParsecT [MdocToken] MdocState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
MdocToken
m <- MdocParser m MdocToken
forall (m :: * -> *). PandocMonad m => MdocParser m MdocToken
anyMacro
MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m ()
-> ParsecT [MdocToken] MdocState m [MdocToken]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill MdocParser m MdocToken
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m t
anyToken ParsecT [MdocToken] MdocState m ()
forall (m :: * -> *). PandocMonad m => MdocParser m ()
eol
LogMessage -> ParsecT [MdocToken] MdocState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> ParsecT [MdocToken] MdocState m ())
-> LogMessage -> ParsecT [MdocToken] MdocState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent (Text
"unsupported macro: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> MdocToken -> Text
toString MdocToken
m) SourcePos
pos
Blocks -> MdocParser m Blocks
forall a. a -> ParsecT [MdocToken] MdocState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
parseRegularBlock :: PandocMonad m => MdocParser m Blocks
parseRegularBlock :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock =
[ParsecT [MdocToken] MdocState m Blocks]
-> ParsecT [MdocToken] MdocState m Blocks
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseDl
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseD1
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parsePara
, Text -> MdocParser m MdocToken
forall (m :: * -> *).
PandocMonad m =>
Text -> MdocParser m MdocToken
emptyMacro Text
"Pp" MdocParser m MdocToken
-> ParsecT [MdocToken] MdocState m Blocks
-> ParsecT [MdocToken] MdocState m Blocks
forall a b.
ParsecT [MdocToken] MdocState m a
-> ParsecT [MdocToken] MdocState m b
-> ParsecT [MdocToken] MdocState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [MdocToken] MdocState m Blocks
forall a. Monoid a => a
mempty
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBd
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBl
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
skipBlanks
]
parseBlock :: (PandocMonad m) => MdocParser m Blocks
parseBlock :: forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseBlock =
[ParsecT [MdocToken] MdocState m Blocks]
-> ParsecT [MdocToken] MdocState m Blocks
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseHeader
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseNameSection
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseSynopsisSection
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseSeeAlsoSection
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseMiniSynopsis
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
parseRegularBlock
, ParsecT [MdocToken] MdocState m Blocks
forall (m :: * -> *). PandocMonad m => MdocParser m Blocks
skipUnknownMacro
]