{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.Blocks
( blockList
, meta
) where
import Text.Pandoc.Readers.Org.BlockStarts
import Text.Pandoc.Readers.Org.DocumentTree (documentTree,
unprunedHeadlineToBlocks)
import Text.Pandoc.Readers.Org.Inlines
import Text.Pandoc.Readers.Org.Meta (metaExport, metaKey, metaLine)
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Readers.Org.Shared (cleanLinkText, isImageFilename,
originalLang, translateLang, exportsCode)
import Text.Pandoc.Builder (Blocks, Inlines)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared (compactify, compactifyDL, safeRead)
import Control.Monad (foldM, guard, mplus, mzero, void)
import Data.Char (isSpace)
import Data.Default (Default)
import Data.Functor (($>))
import Data.List (foldl', intersperse)
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Walk as Walk
blockList :: PandocMonad m => OrgParser m [Block]
blockList :: OrgParser m [Block]
blockList = do
F Headline
fHeadlineTree <- OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> OrgParser m (F Headline)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> OrgParser m (F Headline)
documentTree OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline
OrgParserState
st <- ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let headlineTree :: Headline
headlineTree = F Headline -> OrgParserState -> Headline
forall s a. Future s a -> s -> a
runF F Headline
fHeadlineTree OrgParserState
st
Headline -> OrgParserState -> OrgParser m [Block]
forall (m :: * -> *).
Monad m =>
Headline -> OrgParserState -> OrgParser m [Block]
unprunedHeadlineToBlocks Headline
headlineTree OrgParserState
st
meta :: Monad m => OrgParser m Meta
meta :: OrgParser m Meta
meta = do
F Meta
meta' <- OrgParser m (F Meta)
forall (m :: * -> *). Monad m => OrgParser m (F Meta)
metaExport
F Meta -> OrgParserState -> Meta
forall s a. Future s a -> s -> a
runF F Meta
meta' (OrgParserState -> Meta)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> OrgParser m Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
blocks :: PandocMonad m => OrgParser m (F Blocks)
blocks :: OrgParser m (F Blocks)
blocks = [F Blocks] -> F Blocks
forall a. Monoid a => [a] -> a
mconcat ([F Blocks] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F 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 OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
block (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
headerStart) ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
block :: PandocMonad m => OrgParser m (F Blocks)
block :: OrgParser m (F Blocks)
block = [OrgParser m (F Blocks)] -> OrgParser m (F Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ F Blocks
forall a. Monoid a => a
mempty F Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
blanklines
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
table
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
orgBlock
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
figure
, OrgParser m (F Blocks)
forall (m :: * -> *). Monad m => OrgParser m (F Blocks)
example
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
genericDrawer
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
include
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
specialLine
, OrgParser m (F Blocks)
forall (m :: * -> *). Monad m => OrgParser m (F Blocks)
horizontalRule
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
list
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
latexFragment
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
noteBlock
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
rawOrgLine
, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
paraOrPlain
] OrgParser m (F Blocks) -> String -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"block"
horizontalRule :: Monad m => OrgParser m (F Blocks)
horizontalRule :: OrgParser m (F Blocks)
horizontalRule = Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule F Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
hline
data BlockAttributes = BlockAttributes
{ BlockAttributes -> Maybe Text
blockAttrName :: Maybe Text
, BlockAttributes -> Maybe Text
blockAttrLabel :: Maybe Text
, BlockAttributes -> Maybe (F Inlines)
blockAttrCaption :: Maybe (F Inlines)
, BlockAttributes -> [(Text, Text)]
blockAttrKeyValues :: [(Text, Text)]
}
attrFromBlockAttributes :: BlockAttributes -> Attr
attrFromBlockAttributes :: BlockAttributes -> Attr
attrFromBlockAttributes BlockAttributes{[(Text, Text)]
Maybe Text
Maybe (F Inlines)
blockAttrKeyValues :: [(Text, Text)]
blockAttrCaption :: Maybe (F Inlines)
blockAttrLabel :: Maybe Text
blockAttrName :: Maybe Text
blockAttrKeyValues :: BlockAttributes -> [(Text, Text)]
blockAttrCaption :: BlockAttributes -> Maybe (F Inlines)
blockAttrLabel :: BlockAttributes -> Maybe Text
blockAttrName :: BlockAttributes -> Maybe Text
..} =
let
ident :: Text
ident = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [(Text, Text)]
blockAttrKeyValues
classes :: [Text]
classes = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [(Text, Text)]
blockAttrKeyValues
kv :: [(Text, Text)]
kv = ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text
"id", Text
"class"]) (Text -> Bool) -> ((Text, Text) -> Text) -> (Text, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst) [(Text, Text)]
blockAttrKeyValues
in (Text
ident, [Text]
classes, [(Text, Text)]
kv)
stringyMetaAttribute :: Monad m => OrgParser m (Text, Text)
stringyMetaAttribute :: OrgParser m (Text, Text)
stringyMetaAttribute = OrgParser m (Text, Text) -> OrgParser m (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Text, Text) -> OrgParser m (Text, Text))
-> OrgParser m (Text, Text) -> OrgParser m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart
Text
attrName <- Text -> Text
T.toLower (Text -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParserT s st m Char -> ParserT s st m end -> ParserT s st m Text
many1TillChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
nonspaceChar (Char -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':')
OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
Text
attrValue <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text
"" Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
(Text, Text) -> OrgParser m (Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
attrName, Text
attrValue)
blockAttributes :: PandocMonad m => OrgParser m BlockAttributes
blockAttributes :: OrgParser m BlockAttributes
blockAttributes = OrgParser m BlockAttributes -> OrgParser m BlockAttributes
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m BlockAttributes -> OrgParser m BlockAttributes)
-> OrgParser m BlockAttributes -> OrgParser m BlockAttributes
forall a b. (a -> b) -> a -> b
$ do
[(Text, Text)]
kv <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall (m :: * -> *). Monad m => OrgParser m (Text, Text)
stringyMetaAttribute
Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> Bool
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Bool) -> [(Text, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Text -> Bool
isBlockAttr (Text -> Bool) -> ((Text, Text) -> Text) -> (Text, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst) [(Text, Text)]
kv
let caption :: Maybe Text
caption = (Maybe Text -> (Text, Text) -> Maybe Text)
-> Maybe Text -> [(Text, Text)] -> Maybe Text
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Text -> Maybe Text -> (Text, Text) -> Maybe Text
appendValues Text
"caption") Maybe Text
forall a. Maybe a
Nothing [(Text, Text)]
kv
let kvAttrs :: Maybe Text
kvAttrs = (Maybe Text -> (Text, Text) -> Maybe Text)
-> Maybe Text -> [(Text, Text)] -> Maybe Text
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Text -> Maybe Text -> (Text, Text) -> Maybe Text
appendValues Text
"attr_html") Maybe Text
forall a. Maybe a
Nothing [(Text, Text)]
kv
let name :: Maybe Text
name = Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"name" [(Text, Text)]
kv
let label :: Maybe Text
label = Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"label" [(Text, Text)]
kv
Maybe (F Inlines)
caption' <- (Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Maybe Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe (F Inlines))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlines (Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> (Text -> Text)
-> Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n")) Maybe Text
caption
[(Text, Text)]
kvAttrs' <- ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
-> Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall (m :: * -> *). Monad m => OrgParser m [(Text, Text)]
keyValues (Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)])
-> (Text -> Text)
-> Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n") (Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)])
-> Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty Maybe Text
kvAttrs
BlockAttributes -> OrgParser m BlockAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return BlockAttributes :: Maybe Text
-> Maybe Text
-> Maybe (F Inlines)
-> [(Text, Text)]
-> BlockAttributes
BlockAttributes
{ blockAttrName :: Maybe Text
blockAttrName = Maybe Text
name
, blockAttrLabel :: Maybe Text
blockAttrLabel = Maybe Text
label
, blockAttrCaption :: Maybe (F Inlines)
blockAttrCaption = Maybe (F Inlines)
caption'
, blockAttrKeyValues :: [(Text, Text)]
blockAttrKeyValues = [(Text, Text)]
kvAttrs'
}
where
isBlockAttr :: Text -> Bool
isBlockAttr :: Text -> Bool
isBlockAttr = (Text -> [Text] -> Bool) -> [Text] -> Text -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem
[ Text
"name", Text
"label", Text
"caption"
, Text
"attr_html", Text
"attr_latex"
, Text
"results"
]
appendValues :: Text -> Maybe Text -> (Text, Text) -> Maybe Text
appendValues :: Text -> Maybe Text -> (Text, Text) -> Maybe Text
appendValues Text
attrName Maybe Text
accValue (Text
key, Text
value) =
if Text
key Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
attrName
then Maybe Text
accValue
else case Maybe Text
accValue of
Just Text
acc -> Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text
acc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
value
Maybe Text
Nothing -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
value
keyValues :: Monad m => OrgParser m [(Text, Text)]
keyValues :: OrgParser m [(Text, Text)]
keyValues = OrgParser m [(Text, Text)] -> OrgParser m [(Text, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m [(Text, Text)] -> OrgParser m [(Text, Text)])
-> OrgParser m [(Text, Text)] -> OrgParser m [(Text, Text)]
forall a b. (a -> b) -> a -> b
$
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m [(Text, Text)]
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 ((,) (Text -> Text -> (Text, Text))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Text -> (Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
key ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Text -> (Text, Text))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
value) ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
where
key :: Monad m => OrgParser m Text
key :: OrgParser m Text
key = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
nonspaceChar
value :: Monad m => OrgParser m Text
value :: OrgParser m Text
value = ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
anyChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
endOfValue
endOfValue :: Monad m => OrgParser m ()
endOfValue :: OrgParser m ()
endOfValue =
OrgParser m () -> OrgParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ (() ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
key))
OrgParser m () -> OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
orgBlock :: PandocMonad m => OrgParser m (F Blocks)
orgBlock :: OrgParser m (F Blocks)
orgBlock = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
BlockAttributes
blockAttrs <- OrgParser m BlockAttributes
forall (m :: * -> *). PandocMonad m => OrgParser m BlockAttributes
blockAttributes
Text
blkType <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
blockHeaderStart
((Text -> OrgParser m (F Blocks)) -> Text -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Text
blkType) ((Text -> OrgParser m (F Blocks)) -> OrgParser m (F Blocks))
-> (Text -> OrgParser m (F Blocks)) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$
case Text -> Text
T.toLower Text
blkType of
Text
"export" -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *). Monad m => Text -> OrgParser m (F Blocks)
exportBlock
Text
"comment" -> (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
Monad m =>
(Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines (F Blocks -> Text -> F Blocks
forall a b. a -> b -> a
const F Blocks
forall a. Monoid a => a
mempty)
Text
"html" -> (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
Monad m =>
(Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines (Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Blocks
B.rawBlock (Text -> Text
lowercase Text
blkType))
Text
"latex" -> (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
Monad m =>
(Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines (Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Blocks
B.rawBlock (Text -> Text
lowercase Text
blkType))
Text
"ascii" -> (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
Monad m =>
(Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines (Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Blocks
B.rawBlock (Text -> Text
lowercase Text
blkType))
Text
"example" -> BlockAttributes -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
BlockAttributes -> Text -> OrgParser m (F Blocks)
exampleBlock BlockAttributes
blockAttrs
Text
"quote" -> (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
(F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
parseBlockLines ((Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> Blocks
B.blockQuote)
Text
"verse" -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
Text -> OrgParser m (F Blocks)
verseBlock
Text
"src" -> BlockAttributes -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
BlockAttributes -> Text -> OrgParser m (F Blocks)
codeBlock BlockAttributes
blockAttrs
Text
_ -> (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
(F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
parseBlockLines ((F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks))
-> (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$
let (Text
ident, [Text]
classes, [(Text, Text)]
kv) = BlockAttributes -> Attr
attrFromBlockAttributes BlockAttributes
blockAttrs
in (Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Blocks -> Blocks) -> F Blocks -> F Blocks)
-> (Blocks -> Blocks) -> F Blocks -> F Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
ident, [Text]
classes [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
blkType], [(Text, Text)]
kv)
where
blockHeaderStart :: Monad m => OrgParser m Text
blockHeaderStart :: OrgParser m Text
blockHeaderStart = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> OrgParser m Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
stringAnyCase Text
"#+begin_" OrgParser m Text -> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgWord
lowercase :: Text -> Text
lowercase :: Text -> Text
lowercase = Text -> Text
T.toLower
exampleBlock :: PandocMonad m => BlockAttributes -> Text -> OrgParser m (F Blocks)
exampleBlock :: BlockAttributes -> Text -> OrgParser m (F Blocks)
exampleBlock BlockAttributes
blockAttrs Text
_label = do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
([Text]
classes, [(Text, Text)]
kv) <- OrgParser m ([Text], [(Text, Text)])
forall (m :: * -> *).
Monad m =>
OrgParser m ([Text], [(Text, Text)])
switchesAsAttributes
OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
Text
content <- Text -> OrgParser m Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
"example"
let id' :: Text
id' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe Text
blockAttrName BlockAttributes
blockAttrs
let codeBlck :: Blocks
codeBlck = Attr -> Text -> Blocks
B.codeBlockWith (Text
id', Text
"example"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
classes, [(Text, Text)]
kv) Text
content
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Blocks -> OrgParser m (F Blocks))
-> (Blocks -> F Blocks) -> Blocks -> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> OrgParser m (F Blocks))
-> Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks
codeBlck
rawBlockLines :: Monad m => (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines :: (Text -> F Blocks) -> Text -> OrgParser m (F Blocks)
rawBlockLines Text -> F Blocks
f Text
blockType = OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
ignHeaders OrgParser m () -> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Text -> F Blocks
f (Text -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
blockType)
parseBlockLines :: PandocMonad m => (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
parseBlockLines :: (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
parseBlockLines F Blocks -> F Blocks
f Text
blockType = OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
ignHeaders OrgParser m () -> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (F Blocks -> F Blocks
f (F Blocks -> F Blocks)
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
parsedBlockContent)
where
parsedBlockContent :: PandocMonad m => OrgParser m (F Blocks)
parsedBlockContent :: OrgParser m (F Blocks)
parsedBlockContent = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
raw <- Text -> OrgParser m Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
blockType
OrgParser m (F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks (Text
raw Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n")
rawBlockContent :: Monad m => Text -> OrgParser m Text
rawBlockContent :: Text -> OrgParser m Text
rawBlockContent Text
blockType = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ do
[Text]
blkLines <- OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
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 OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
rawLine ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
blockEnder
Int
tabLen <- (ReaderOptions -> Int)
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st m b
getOption ReaderOptions -> Int
readerTabStop
Bool
trimP <- OrgParserState -> Bool
orgStateTrimLeadBlkIndent (OrgParserState -> Bool)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let stripIndent :: [Text] -> [Text]
stripIndent [Text]
strs = if Bool
trimP then (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Text -> Text
T.drop ([Text] -> Int
shortestIndent [Text]
strs)) [Text]
strs else [Text]
strs
([Text] -> Text
T.unlines
([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
stripIndent
([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Text -> Text
tabsToSpaces Int
tabLen (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
commaEscaped)
([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
blkLines)
Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (OrgParserState -> OrgParserState)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\OrgParserState
s -> OrgParserState
s { orgStateTrimLeadBlkIndent :: Bool
orgStateTrimLeadBlkIndent = Bool
True })
where
rawLine :: Monad m => OrgParser m Text
rawLine :: OrgParser m Text
rawLine = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ (Text
"" Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline) OrgParser m Text -> OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
blockEnder :: Monad m => OrgParser m ()
blockEnder :: OrgParser m ()
blockEnder = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
stringAnyCase (Text
"#+end_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
blockType)
shortestIndent :: [Text] -> Int
shortestIndent :: [Text] -> Int
shortestIndent = (Text -> Int -> Int) -> Int -> [Text] -> Int
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int -> Int -> Int) -> (Text -> Int) -> Text -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
T.length (Text -> Int) -> (Text -> Text) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.takeWhile Char -> Bool
isSpace) Int
forall a. Bounded a => a
maxBound
([Text] -> Int) -> ([Text] -> [Text]) -> [Text] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null)
tabsToSpaces :: Int -> Text -> Text
tabsToSpaces :: Int -> Text -> Text
tabsToSpaces Int
tabStop Text
t =
let (Text
ind, Text
suff) = (Char -> Bool) -> Text -> (Text, Text)
T.span (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t') Text
t
tabNum :: Int
tabNum = Text -> Int
T.length (Text -> Int) -> Text -> Int
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
ind
spaceNum :: Int
spaceNum = Text -> Int
T.length Text
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
tabNum
in Int -> Text -> Text
T.replicate (Int
spaceNum Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
tabStop Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
tabNum) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
suff
commaEscaped :: Text -> Text
commaEscaped Text
t =
let (Text
ind, Text
suff) = (Char -> Bool) -> Text -> (Text, Text)
T.span (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t') Text
t
in case Text -> Maybe (Char, Text)
T.uncons Text
suff of
Just (Char
',', Text
cs)
| Text
"*" <- Int -> Text -> Text
T.take Int
1 Text
cs -> Text
ind Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs
| Text
"#+" <- Int -> Text -> Text
T.take Int
2 Text
cs -> Text
ind Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs
Maybe (Char, Text)
_ -> Text
t
ignHeaders :: Monad m => OrgParser m ()
= (() ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline) OrgParser m () -> OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (() ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine)
exportBlock :: Monad m => Text -> OrgParser m (F Blocks)
exportBlock :: Text -> OrgParser m (F Blocks)
exportBlock Text
blockType = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
exportType <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgWord ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
ignHeaders
Text
contents <- Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
blockType
Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Text -> Text -> Blocks
B.rawBlock (Text -> Text
T.toLower Text
exportType) Text
contents)
verseBlock :: PandocMonad m => Text -> OrgParser m (F Blocks)
verseBlock :: Text -> OrgParser m (F Blocks)
verseBlock Text
blockType = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
ignHeaders
Text
content <- Text -> OrgParser m Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
blockType
([Inlines] -> Blocks)
-> Future OrgParserState [Inlines] -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Inlines] -> Blocks
B.lineBlock (Future OrgParserState [Inlines] -> F Blocks)
-> ([F Inlines] -> Future OrgParserState [Inlines])
-> [F Inlines]
-> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> Future OrgParserState [Inlines]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([F Inlines] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> [Text]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Text -> OrgParser m (F Inlines)
parseVerseLine (Text -> [Text]
T.lines Text
content)
where
parseVerseLine :: PandocMonad m => Text -> OrgParser m (F Inlines)
parseVerseLine :: Text -> OrgParser m (F Inlines)
parseVerseLine Text
cs = do
let (Text
initialSpaces, Text
indentedLine) = (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
isSpace Text
cs
let nbspIndent :: Inlines
nbspIndent = if Text -> Bool
T.null Text
initialSpaces
then Inlines
forall a. Monoid a => a
mempty
else Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> Text -> Text
T.map (Char -> Char -> Char
forall a b. a -> b -> a
const Char
'\160') Text
initialSpaces
F Inlines
line <- OrgParser m (F Inlines) -> Text -> OrgParser m (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlines (Text
indentedLine Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n")
F Inlines -> OrgParser m (F Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines) -> F Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
nbspIndent F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
line)
codeBlock :: PandocMonad m => BlockAttributes -> Text -> OrgParser m (F Blocks)
codeBlock :: BlockAttributes -> Text -> OrgParser m (F Blocks)
codeBlock BlockAttributes
blockAttrs Text
blockType = do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
([Text]
classes, [(Text, Text)]
kv) <- OrgParser m ([Text], [(Text, Text)])
forall (m :: * -> *).
Monad m =>
OrgParser m ([Text], [(Text, Text)])
codeHeaderArgs OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (([Text], [(Text, Text)])
forall a. Monoid a => a
mempty ([Text], [(Text, Text)])
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m ([Text], [(Text, Text)])
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
ignHeaders)
Text
content <- Text -> OrgParser m Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
rawBlockContent Text
blockType
F Blocks
resultsContent <- F Blocks -> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option F Blocks
forall a. Monoid a => a
mempty OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
babelResultsBlock
let id' :: Text
id' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe Text
blockAttrName BlockAttributes
blockAttrs
let codeBlck :: Blocks
codeBlck = Attr -> Text -> Blocks
B.codeBlockWith ( Text
id', [Text]
classes, [(Text, Text)]
kv ) Text
content
let labelledBlck :: F Blocks
labelledBlck = F Blocks
-> (F Inlines -> F Blocks) -> Maybe (F Inlines) -> F Blocks
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Blocks -> F Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
codeBlck)
(Blocks -> F Inlines -> F Blocks
labelDiv Blocks
codeBlck)
(BlockAttributes -> Maybe (F Inlines)
blockAttrCaption BlockAttributes
blockAttrs)
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Blocks -> OrgParser m (F Blocks))
-> F Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$
(if [(Text, Text)] -> Bool
exportsCode [(Text, Text)]
kv then F Blocks
labelledBlck else F Blocks
forall a. Monoid a => a
mempty) F Blocks -> F Blocks -> F Blocks
forall a. Semigroup a => a -> a -> a
<>
(if [(Text, Text)] -> Bool
exportsResults [(Text, Text)]
kv then F Blocks
resultsContent else F Blocks
forall a. Monoid a => a
mempty)
where
labelDiv :: Blocks -> F Inlines -> F Blocks
labelDiv :: Blocks -> F Inlines -> F Blocks
labelDiv Blocks
blk F Inlines
value =
Attr -> Blocks -> Blocks
B.divWith Attr
nullAttr (Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Blocks -> Blocks -> Blocks
forall a. Monoid a => a -> a -> a
mappend (Blocks -> Blocks -> Blocks)
-> F Blocks -> Future OrgParserState (Blocks -> Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines -> F Blocks
labelledBlock F Inlines
value Future OrgParserState (Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Blocks -> F Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
blk)
labelledBlock :: F Inlines -> F Blocks
labelledBlock :: F Inlines -> F Blocks
labelledBlock = (Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Blocks
B.plain (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Inlines -> Inlines
B.spanWith (Text
"", [Text
"label"], []))
exportsResults :: [(Text, Text)] -> Bool
exportsResults :: [(Text, Text)] -> Bool
exportsResults = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"results", Text
"both"]) (Maybe Text -> Bool)
-> ([(Text, Text)] -> Maybe Text) -> [(Text, Text)] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"exports"
babelResultsBlock :: PandocMonad m => OrgParser m (F Blocks)
babelResultsBlock :: OrgParser m (F Blocks)
babelResultsBlock = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
blanklines
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall u. ParsecT Text u (ReaderT OrgParserLocal m) ()
resultsMarker ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text])
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$
OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
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 Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Text
forall (m :: * -> *) st. Monad m => ParserT Text st m Text
anyLineNewline) ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall u. ParsecT Text u (ReaderT OrgParserLocal m) ()
resultsMarker)
OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
block
where
resultsMarker :: ParsecT Text u (ReaderT OrgParserLocal m) ()
resultsMarker = ParsecT Text u (ReaderT OrgParserLocal m) ()
-> ParsecT Text u (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u (ReaderT OrgParserLocal m) ()
-> ParsecT Text u (ReaderT OrgParserLocal m) ())
-> (ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) ())
-> ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) ())
-> ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ Text -> ParserT Text u (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
stringAnyCase Text
"#+RESULTS:" ParserT Text u (ReaderT OrgParserLocal m) Text
-> ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text u (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline
codeHeaderArgs :: Monad m => OrgParser m ([Text], [(Text, Text)])
= OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)]))
-> OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
forall a b. (a -> b) -> a -> b
$ do
Text
language <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgWord
([Text]
switchClasses, [(Text, Text)]
switchKv) <- OrgParser m ([Text], [(Text, Text)])
forall (m :: * -> *).
Monad m =>
OrgParser m ([Text], [(Text, Text)])
switchesAsAttributes
[(Text, Text)]
parameters <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
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 Text OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall (m :: * -> *). Monad m => OrgParser m (Text, Text)
blockOption ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
([Text], [(Text, Text)]) -> OrgParser m ([Text], [(Text, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return ( Text -> Text
translateLang Text
language Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
switchClasses
, Text -> [(Text, Text)]
originalLang Text
language [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
switchKv [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
parameters
)
switchesAsAttributes :: Monad m => OrgParser m ([Text], [(Text, Text)])
switchesAsAttributes :: OrgParser m ([Text], [(Text, Text)])
switchesAsAttributes = OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)]))
-> OrgParser m ([Text], [(Text, Text)])
-> OrgParser m ([Text], [(Text, Text)])
forall a b. (a -> b) -> a -> b
$ do
[(Char, Maybe Text, SwitchPolarity)]
switches <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[(Char, Maybe Text, SwitchPolarity)]
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[(Char, Maybe Text, SwitchPolarity)]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[(Char, Maybe Text, SwitchPolarity)]
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[(Char, Maybe Text, SwitchPolarity)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *).
Monad m =>
OrgParser m (Char, Maybe Text, SwitchPolarity)
switch OrgParser m (Char, Maybe Text, SwitchPolarity)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[(Char, Maybe Text, SwitchPolarity)]
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 Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar)
([Text], [(Text, Text)]) -> OrgParser m ([Text], [(Text, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return (([Text], [(Text, Text)]) -> OrgParser m ([Text], [(Text, Text)]))
-> ([Text], [(Text, Text)]) -> OrgParser m ([Text], [(Text, Text)])
forall a b. (a -> b) -> a -> b
$ ((Char, Maybe Text, SwitchPolarity)
-> ([Text], [(Text, Text)]) -> ([Text], [(Text, Text)]))
-> ([Text], [(Text, Text)])
-> [(Char, Maybe Text, SwitchPolarity)]
-> ([Text], [(Text, Text)])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Char, Maybe Text, SwitchPolarity)
-> ([Text], [(Text, Text)]) -> ([Text], [(Text, Text)])
addToAttr ([], []) [(Char, Maybe Text, SwitchPolarity)]
switches
where
addToAttr :: (Char, Maybe Text, SwitchPolarity)
-> ([Text], [(Text, Text)])
-> ([Text], [(Text, Text)])
addToAttr :: (Char, Maybe Text, SwitchPolarity)
-> ([Text], [(Text, Text)]) -> ([Text], [(Text, Text)])
addToAttr (Char
'n', Maybe Text
lineNum, SwitchPolarity
pol) ([Text]
cls, [(Text, Text)]
kv) =
let kv' :: [(Text, Text)]
kv' = case Maybe Text
lineNum of
Just Text
num -> (Text
"startFrom", Text
num)(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
:[(Text, Text)]
kv
Maybe Text
Nothing -> [(Text, Text)]
kv
cls' :: [Text]
cls' = case SwitchPolarity
pol of
SwitchPolarity
SwitchPlus -> Text
"continuedSourceBlock"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
cls
SwitchPolarity
SwitchMinus -> [Text]
cls
in (Text
"numberLines"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
cls', [(Text, Text)]
kv')
addToAttr (Char, Maybe Text, SwitchPolarity)
_ ([Text], [(Text, Text)])
x = ([Text], [(Text, Text)])
x
data SwitchPolarity = SwitchPlus | SwitchMinus
deriving (Int -> SwitchPolarity -> ShowS
[SwitchPolarity] -> ShowS
SwitchPolarity -> String
(Int -> SwitchPolarity -> ShowS)
-> (SwitchPolarity -> String)
-> ([SwitchPolarity] -> ShowS)
-> Show SwitchPolarity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwitchPolarity] -> ShowS
$cshowList :: [SwitchPolarity] -> ShowS
show :: SwitchPolarity -> String
$cshow :: SwitchPolarity -> String
showsPrec :: Int -> SwitchPolarity -> ShowS
$cshowsPrec :: Int -> SwitchPolarity -> ShowS
Show, SwitchPolarity -> SwitchPolarity -> Bool
(SwitchPolarity -> SwitchPolarity -> Bool)
-> (SwitchPolarity -> SwitchPolarity -> Bool) -> Eq SwitchPolarity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchPolarity -> SwitchPolarity -> Bool
$c/= :: SwitchPolarity -> SwitchPolarity -> Bool
== :: SwitchPolarity -> SwitchPolarity -> Bool
$c== :: SwitchPolarity -> SwitchPolarity -> Bool
Eq)
switchPolarity :: Monad m => OrgParser m SwitchPolarity
switchPolarity :: OrgParser m SwitchPolarity
switchPolarity = (SwitchPolarity
SwitchMinus SwitchPolarity
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m SwitchPolarity
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'-') OrgParser m SwitchPolarity
-> OrgParser m SwitchPolarity -> OrgParser m SwitchPolarity
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (SwitchPolarity
SwitchPlus SwitchPolarity
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m SwitchPolarity
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'+')
switch :: Monad m => OrgParser m (Char, Maybe Text, SwitchPolarity)
switch :: OrgParser m (Char, Maybe Text, SwitchPolarity)
switch = OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity))
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall a b. (a -> b) -> a -> b
$ OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *).
Monad m =>
OrgParser m (Char, Maybe Text, SwitchPolarity)
lineNumberSwitch OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (Char, Maybe Text, SwitchPolarity)
labelSwitch
OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *).
Monad m =>
OrgParser m (Char, Maybe Text, SwitchPolarity)
whitespaceSwitch OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall a.
ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Char, Maybe a, SwitchPolarity)
simpleSwitch
where
simpleSwitch :: ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Char, Maybe a, SwitchPolarity)
simpleSwitch = (\SwitchPolarity
pol Char
c -> (Char
c, Maybe a
forall a. Maybe a
Nothing, SwitchPolarity
pol)) (SwitchPolarity -> Char -> (Char, Maybe a, SwitchPolarity))
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) SwitchPolarity
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Char -> (Char, Maybe a, SwitchPolarity))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) SwitchPolarity
forall (m :: * -> *). Monad m => OrgParser m SwitchPolarity
switchPolarity ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Char -> (Char, Maybe a, SwitchPolarity))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Char, Maybe a, SwitchPolarity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
letter
labelSwitch :: OrgParser m (Char, Maybe Text, SwitchPolarity)
labelSwitch = Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *).
Monad m =>
Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
genericSwitch Char
'l' (OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity))
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall a b. (a -> b) -> a -> b
$
Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParserT s st m Char -> ParserT s st m end -> ParserT s st m Text
many1TillChar ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
nonspaceChar (Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"')
whitespaceSwitch :: Monad m => OrgParser m (Char, Maybe Text, SwitchPolarity)
whitespaceSwitch :: OrgParser m (Char, Maybe Text, SwitchPolarity)
whitespaceSwitch = do
String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"-i"
(OrgParserState -> OrgParserState)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s -> OrgParserState
s { orgStateTrimLeadBlkIndent :: Bool
orgStateTrimLeadBlkIndent = Bool
False }
(Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
'i', Maybe Text
forall a. Maybe a
Nothing, SwitchPolarity
SwitchMinus)
genericSwitch :: Monad m
=> Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
genericSwitch :: Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
genericSwitch Char
c OrgParser m Text
p = OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity))
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall a b. (a -> b) -> a -> b
$ do
SwitchPolarity
polarity <- OrgParser m SwitchPolarity
forall (m :: * -> *). Monad m => OrgParser m SwitchPolarity
switchPolarity OrgParser m SwitchPolarity
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m SwitchPolarity
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c OrgParser m SwitchPolarity
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m SwitchPolarity
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
Maybe Text
arg <- OrgParser m Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal 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 OrgParser m Text
p
(Char, Maybe Text, SwitchPolarity)
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
c, Maybe Text
arg, SwitchPolarity
polarity)
lineNumberSwitch :: Monad m => OrgParser m (Char, Maybe Text, SwitchPolarity)
lineNumberSwitch :: OrgParser m (Char, Maybe Text, SwitchPolarity)
lineNumberSwitch = Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
forall (m :: * -> *).
Monad m =>
Char
-> OrgParser m Text
-> OrgParser m (Char, Maybe Text, SwitchPolarity)
genericSwitch Char
'n' (ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
digit)
blockOption :: Monad m => OrgParser m (Text, Text)
blockOption :: OrgParser m (Text, Text)
blockOption = OrgParser m (Text, Text) -> OrgParser m (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Text, Text) -> OrgParser m (Text, Text))
-> OrgParser m (Text, Text) -> OrgParser m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
Text
argKey <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgKey
Text
paramValue <- Text -> OrgParser m Text -> OrgParser 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
"yes" OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgParamValue
(Text, Text) -> OrgParser m (Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
argKey, Text
paramValue)
orgParamValue :: Monad m => OrgParser m Text
orgParamValue :: OrgParser m Text
orgParamValue = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ (String -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m Text
forall a b. (a -> b) -> a -> b
$
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgKey
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\n\r" ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
`many1Till` ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfValue
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
where
endOfValue :: ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfValue = ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"\n\r")
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
skipSpaces1 ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgKey)
genericDrawer :: PandocMonad m => OrgParser m (F Blocks)
genericDrawer :: OrgParser m (F Blocks)
genericDrawer = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
name <- Text -> Text
T.toUpper (Text -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
drawerStart
[Text]
content <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
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 Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
drawerLine (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
drawerEnd)
OrgParserState
state <- ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case ExportSettings -> Either [Text] [Text]
exportDrawers (ExportSettings -> Either [Text] [Text])
-> (OrgParserState -> ExportSettings)
-> OrgParserState
-> Either [Text] [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> ExportSettings
orgStateExportSettings (OrgParserState -> Either [Text] [Text])
-> OrgParserState -> Either [Text] [Text]
forall a b. (a -> b) -> a -> b
$ OrgParserState
state of
Either [Text] [Text]
_ | Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"PROPERTIES" -> F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return F Blocks
forall a. Monoid a => a
mempty
Left [Text]
names | Text
name Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
names -> F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return F Blocks
forall a. Monoid a => a
mempty
Right [Text]
names | Text
name Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text]
names -> F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return F Blocks
forall a. Monoid a => a
mempty
Either [Text] [Text]
_ -> Text -> F Blocks -> F Blocks
drawerDiv Text
name (F Blocks -> F Blocks)
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text] -> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
[Text] -> OrgParser m (F Blocks)
parseLines [Text]
content
where
parseLines :: PandocMonad m => [Text] -> OrgParser m (F Blocks)
parseLines :: [Text] -> OrgParser m (F Blocks)
parseLines = OrgParser m (F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks (Text -> OrgParser m (F Blocks))
-> ([Text] -> Text) -> [Text] -> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n") (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines
drawerDiv :: Text -> F Blocks -> F Blocks
drawerDiv :: Text -> F Blocks -> F Blocks
drawerDiv Text
drawerName = (Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Blocks -> Blocks) -> F Blocks -> F Blocks)
-> (Blocks -> Blocks) -> F Blocks -> F Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
forall a. Monoid a => a
mempty, [Text
drawerName, Text
"drawer"], [(Text, Text)]
forall a. Monoid a => a
mempty)
drawerLine :: Monad m => OrgParser m Text
drawerLine :: OrgParser m Text
drawerLine = OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
drawerEnd :: Monad m => OrgParser m Text
drawerEnd :: OrgParser m Text
drawerEnd = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> OrgParser m Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
stringAnyCase Text
":END:" OrgParser m Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
figure :: PandocMonad m => OrgParser m (F Blocks)
figure :: OrgParser m (F Blocks)
figure = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
BlockAttributes
figAttrs <- OrgParser m BlockAttributes
forall (m :: * -> *). PandocMonad m => OrgParser m BlockAttributes
blockAttributes
Text
src <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
selfTarget ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
endOfParagraph
case Text -> Maybe Text
cleanLinkText Text
src of
Maybe Text
Nothing -> OrgParser m (F Blocks)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Just Text
imgSrc -> do
Bool -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text -> Bool
isImageFilename Text
imgSrc)
let isFigure :: Bool
isFigure = Maybe (F Inlines) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (F Inlines) -> Bool) -> Maybe (F Inlines) -> Bool
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe (F Inlines)
blockAttrCaption BlockAttributes
figAttrs
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Blocks -> OrgParser m (F Blocks))
-> F Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Bool -> BlockAttributes -> Text -> F Blocks
imageBlock Bool
isFigure BlockAttributes
figAttrs Text
imgSrc
where
selfTarget :: PandocMonad m => OrgParser m Text
selfTarget :: OrgParser m Text
selfTarget = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
linkTarget OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']'
imageBlock :: Bool -> BlockAttributes -> Text -> F Blocks
imageBlock :: Bool -> BlockAttributes -> Text -> F Blocks
imageBlock Bool
isFigure BlockAttributes
figAttrs Text
imgSrc =
let
figName :: Text
figName = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe Text
blockAttrName BlockAttributes
figAttrs
figLabel :: Text
figLabel = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe Text
blockAttrLabel BlockAttributes
figAttrs
figCaption :: F Inlines
figCaption = F Inlines -> Maybe (F Inlines) -> F Inlines
forall a. a -> Maybe a -> a
fromMaybe F Inlines
forall a. Monoid a => a
mempty (Maybe (F Inlines) -> F Inlines) -> Maybe (F Inlines) -> F Inlines
forall a b. (a -> b) -> a -> b
$ BlockAttributes -> Maybe (F Inlines)
blockAttrCaption BlockAttributes
figAttrs
figKeyVals :: [(Text, Text)]
figKeyVals = BlockAttributes -> [(Text, Text)]
blockAttrKeyValues BlockAttributes
figAttrs
attr :: Attr
attr = (Text
figLabel, [Text]
forall a. Monoid a => a
mempty, [(Text, Text)]
figKeyVals)
figTitle :: Text
figTitle = (if Bool
isFigure then Text -> Text
withFigPrefix else Text -> Text
forall a. a -> a
id) Text
figName
in
Inlines -> Blocks
B.para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr Text
imgSrc Text
figTitle (Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
figCaption
withFigPrefix :: Text -> Text
withFigPrefix :: Text -> Text
withFigPrefix Text
cs =
if Text
"fig:" Text -> Text -> Bool
`T.isPrefixOf` Text
cs
then Text
cs
else Text
"fig:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cs
endOfParagraph :: Monad m => OrgParser m ()
endOfParagraph :: OrgParser m ()
endOfParagraph = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m () -> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
endOfBlock
example :: Monad m => OrgParser m (F Blocks)
example :: OrgParser m (F Blocks)
example = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Blocks -> OrgParser m (F Blocks))
-> ([Text] -> Blocks) -> [Text] -> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Blocks
exampleCode (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> OrgParser m (F Blocks))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> OrgParser m (F Blocks)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
exampleLine
where
exampleLine :: Monad m => OrgParser m Text
exampleLine :: OrgParser m Text
exampleLine = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
exampleLineStart OrgParser m () -> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
exampleCode :: Text -> Blocks
exampleCode :: Text -> Blocks
exampleCode = Attr -> Text -> Blocks
B.codeBlockWith (Text
"", [Text
"example"], [])
specialLine :: PandocMonad m => OrgParser m (F Blocks)
specialLine :: OrgParser m (F Blocks)
specialLine = (Blocks -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> OrgParser m (F Blocks))
-> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> OrgParser m (F Blocks))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall (m :: * -> *). PandocMonad m => OrgParser m Blocks
rawExportLine ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall (m :: * -> *). PandocMonad m => OrgParser m Blocks
metaLine ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Blocks
forall (m :: * -> *). Monad m => OrgParser m Blocks
commentLine
include :: PandocMonad m => OrgParser m (F Blocks)
include :: OrgParser m (F Blocks)
include = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
stringAnyCase Text
"include:" OrgParser m () -> OrgParser m () -> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
String
filename <- OrgParser m String
forall (m :: * -> *). PandocMonad m => OrgParser m String
includeTarget
[Text]
includeArgs <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
alphaNum)
[(Text, Text)]
params <- OrgParser m [(Text, Text)]
forall (m :: * -> *). Monad m => OrgParser m [(Text, Text)]
keyValues
OrgParser m (F Blocks)
blocksParser <- case [Text]
includeArgs of
(Text
"example" : [Text]
_) -> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall a b. (a -> b) -> a -> b
$ Blocks -> F Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Blocks
B.codeBlock (Text -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
parseRaw
[Text
"export"] -> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> (Blocks -> OrgParser m (F Blocks))
-> Blocks
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Blocks
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> Blocks
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall a b. (a -> b) -> a -> b
$ [Block] -> Blocks
forall a. [a] -> Many a
B.fromList []
[Text
"export", Text
format] -> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall a b. (a -> b) -> a -> b
$ Blocks -> F Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Blocks
B.rawBlock Text
format (Text -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
parseRaw
(Text
"src" : [Text]
rest) -> do
let attr :: Attr
attr = case [Text]
rest of
[Text
lang] -> (Text
forall a. Monoid a => a
mempty, [Text
lang], [(Text, Text)]
forall a. Monoid a => a
mempty)
[Text]
_ -> Attr
nullAttr
OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall a b. (a -> b) -> a -> b
$ Blocks -> F Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> F Blocks) -> (Text -> Blocks) -> Text -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Blocks
B.codeBlockWith Attr
attr (Text -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
parseRaw
[Text]
_ -> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks)))
-> OrgParser m (F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(OrgParser m (F Blocks))
forall a b. (a -> b) -> a -> b
$ Blocks -> F Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> F Blocks) -> ([Block] -> Blocks) -> [Block] -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Blocks
forall a. [a] -> Many a
B.fromList ([Block] -> Blocks) -> ([Block] -> [Block]) -> [Block] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Text)] -> [Block] -> [Block]
blockFilter [(Text, Text)]
params ([Block] -> F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Block]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Block]
forall (m :: * -> *). PandocMonad m => OrgParser m [Block]
blockList
OrgParser m (F Blocks)
-> [String] -> String -> OrgParser m (F Blocks)
forall (m :: * -> *) st.
(PandocMonad m, HasIncludeFiles st) =>
ParserT Text st m (Future st Blocks)
-> [String] -> String -> ParserT Text st m (Future st Blocks)
insertIncludedFileF OrgParser m (F Blocks)
blocksParser [String
"."] String
filename
where
includeTarget :: PandocMonad m => OrgParser m FilePath
includeTarget :: OrgParser m String
includeTarget = do
Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m String
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 (String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\n\r\t") (Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"')
parseRaw :: PandocMonad m => OrgParser m Text
parseRaw :: OrgParser m Text
parseRaw = ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
anyChar
blockFilter :: [(Text, Text)] -> [Block] -> [Block]
blockFilter :: [(Text, Text)] -> [Block] -> [Block]
blockFilter [(Text, Text)]
params [Block]
blks =
let minlvl :: Maybe Text
minlvl = Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"minlevel" [(Text, Text)]
params
in case (Maybe Text
minlvl Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead :: Maybe Int) of
Maybe Int
Nothing -> [Block]
blks
Just Int
lvl -> let levels :: [Int]
levels = (Block -> [Int]) -> [Block] -> [Int]
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
Walk.query Block -> [Int]
headerLevel [Block]
blks
curMin :: Int
curMin = if [Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
levels then Int
0 else [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Int]
levels
in (Block -> Block) -> [Block] -> [Block]
forall a b. Walkable a b => (a -> a) -> b -> b
Walk.walk (Int -> Block -> Block
shiftHeader (Int
curMin Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lvl)) [Block]
blks
headerLevel :: Block -> [Int]
headerLevel :: Block -> [Int]
headerLevel (Header Int
lvl Attr
_attr [Inline]
_content) = [Int
lvl]
headerLevel Block
_ = []
shiftHeader :: Int -> Block -> Block
shiftHeader :: Int -> Block -> Block
shiftHeader Int
shift Block
blk =
case Block
blk of
(Header Int
lvl Attr
attr [Inline]
content)
| Int
lvl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
shift Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 -> Int -> Attr -> [Inline] -> Block
Header (Int
lvl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
shift) Attr
attr [Inline]
content
| Bool
otherwise -> [Inline] -> Block
Para [Inline]
content
Block
_ -> Block
blk
rawExportLine :: PandocMonad m => OrgParser m Blocks
rawExportLine :: OrgParser m Blocks
rawExportLine = OrgParser m Blocks -> OrgParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Blocks -> OrgParser m Blocks)
-> OrgParser m Blocks -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart
Text
key <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
metaKey
if Text
key Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"latex", Text
"html", Text
"texinfo", Text
"beamer"]
then Text -> Text -> Blocks
B.rawBlock Text
key (Text -> Blocks) -> OrgParser m Text -> OrgParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
else OrgParser m Blocks
forall (m :: * -> *) a. MonadPlus m => m a
mzero
rawOrgLine :: PandocMonad m => OrgParser m (F Blocks)
rawOrgLine :: OrgParser m (F Blocks)
rawOrgLine = do
Text
line <- OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Blocks -> OrgParser m (F Blocks))
-> Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
B.rawBlock Text
"org" (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text
"#+" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
line
commentLine :: Monad m => OrgParser m Blocks
= OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
commentLineStart OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> Blocks -> OrgParser m Blocks
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Blocks
forall a. Monoid a => a
mempty
data ColumnProperty = ColumnProperty
{ ColumnProperty -> Maybe Alignment
columnAlignment :: Maybe Alignment
, ColumnProperty -> Maybe Int
columnRelWidth :: Maybe Int
} deriving (Int -> ColumnProperty -> ShowS
[ColumnProperty] -> ShowS
ColumnProperty -> String
(Int -> ColumnProperty -> ShowS)
-> (ColumnProperty -> String)
-> ([ColumnProperty] -> ShowS)
-> Show ColumnProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnProperty] -> ShowS
$cshowList :: [ColumnProperty] -> ShowS
show :: ColumnProperty -> String
$cshow :: ColumnProperty -> String
showsPrec :: Int -> ColumnProperty -> ShowS
$cshowsPrec :: Int -> ColumnProperty -> ShowS
Show, ColumnProperty -> ColumnProperty -> Bool
(ColumnProperty -> ColumnProperty -> Bool)
-> (ColumnProperty -> ColumnProperty -> Bool) -> Eq ColumnProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnProperty -> ColumnProperty -> Bool
$c/= :: ColumnProperty -> ColumnProperty -> Bool
== :: ColumnProperty -> ColumnProperty -> Bool
$c== :: ColumnProperty -> ColumnProperty -> Bool
Eq)
instance Default ColumnProperty where
def :: ColumnProperty
def = Maybe Alignment -> Maybe Int -> ColumnProperty
ColumnProperty Maybe Alignment
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing
data OrgTableRow = OrgContentRow (F [Blocks])
| OrgAlignRow [ColumnProperty]
| OrgHlineRow
data OrgTable = OrgTable
{ OrgTable -> [ColumnProperty]
orgTableColumnProperties :: [ColumnProperty]
, :: [Blocks]
, OrgTable -> [[Blocks]]
orgTableRows :: [[Blocks]]
}
table :: PandocMonad m => OrgParser m (F Blocks)
table :: OrgParser m (F Blocks)
table = do
Bool
withTables <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithTables
F Blocks
tbl <- OrgParser m (F Blocks) -> Bool -> OrgParser m (F Blocks)
forall s (m :: * -> *) st (mf :: * -> *).
(Stream s m Char, HasReaderOptions st, HasLastStrPosition st,
Monad mf, IsString s) =>
ParserT s st m (mf Blocks) -> Bool -> ParserT s st m (mf Blocks)
gridTableWith OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks Bool
True OrgParser m (F Blocks)
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
orgTable
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Blocks -> OrgParser m (F Blocks))
-> F Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ if Bool
withTables then F Blocks
tbl else F Blocks
forall a. Monoid a => a
mempty
orgTable :: PandocMonad m => OrgParser m (F Blocks)
orgTable :: OrgParser m (F Blocks)
orgTable = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
let isFirstInListItem :: OrgParserState -> Bool
isFirstInListItem OrgParserState
st = OrgParserState -> ParserContext
orgStateParserContext OrgParserState
st ParserContext -> ParserContext -> Bool
forall a. Eq a => a -> a -> Bool
== ParserContext
ListItemState Bool -> Bool -> Bool
&&
Maybe SourcePos -> Bool
forall a. Maybe a -> Bool
isNothing (OrgParserState -> Maybe SourcePos
orgStateLastPreCharPos OrgParserState
st)
Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> Bool)
-> OrgParserState
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not (Bool -> Bool)
-> (OrgParserState -> Bool) -> OrgParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> Bool
isFirstInListItem (OrgParserState
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
BlockAttributes
blockAttrs <- OrgParser m BlockAttributes
forall (m :: * -> *). PandocMonad m => OrgParser m BlockAttributes
blockAttributes
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
tableStart
[OrgTableRow]
rows <- OrgParser m [OrgTableRow]
forall (m :: * -> *). PandocMonad m => OrgParser m [OrgTableRow]
tableRows
let caption :: F Inlines
caption = F Inlines -> Maybe (F Inlines) -> F Inlines
forall a. a -> Maybe a -> a
fromMaybe F Inlines
forall a. Monoid a => a
mempty (BlockAttributes -> Maybe (F Inlines)
blockAttrCaption BlockAttributes
blockAttrs)
let orgTbl :: Future OrgParserState OrgTable
orgTbl = OrgTable -> OrgTable
normalizeTable (OrgTable -> OrgTable)
-> Future OrgParserState OrgTable -> Future OrgParserState OrgTable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [OrgTableRow] -> Future OrgParserState OrgTable
rowsToTable [OrgTableRow]
rows
let identMb :: Maybe Text
identMb = BlockAttributes -> Maybe Text
blockAttrName BlockAttributes
blockAttrs Maybe Text -> Maybe Text -> Maybe Text
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` BlockAttributes -> Maybe Text
blockAttrLabel BlockAttributes
blockAttrs
let wrap :: Blocks -> Blocks
wrap = case Maybe Text
identMb of
Just Text
ident -> Attr -> Blocks -> Blocks
B.divWith (Text
ident, [Text]
forall a. Monoid a => a
mempty, [(Text, Text)]
forall a. Monoid a => a
mempty)
Maybe Text
Nothing -> Blocks -> Blocks
forall a. a -> a
id
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Blocks -> OrgParser m (F Blocks))
-> (F Blocks -> F Blocks) -> F Blocks -> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Blocks -> Blocks) -> F Blocks -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> Blocks
wrap (F Blocks -> OrgParser m (F Blocks))
-> F Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ (OrgTable -> Inlines -> Blocks
orgToPandocTable (OrgTable -> Inlines -> Blocks)
-> Future OrgParserState OrgTable
-> Future OrgParserState (Inlines -> Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future OrgParserState OrgTable
orgTbl Future OrgParserState (Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> F Inlines
caption)
orgToPandocTable :: OrgTable
-> Inlines
-> Blocks
orgToPandocTable :: OrgTable -> Inlines -> Blocks
orgToPandocTable (OrgTable [ColumnProperty]
colProps [Blocks]
heads [[Blocks]]
lns) Inlines
caption =
let totalWidth :: Maybe Int
totalWidth = if (ColumnProperty -> Bool) -> [ColumnProperty] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Int -> Bool)
-> (ColumnProperty -> Maybe Int) -> ColumnProperty -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnProperty -> Maybe Int
columnRelWidth) [ColumnProperty]
colProps
then Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> ([Int] -> Int) -> [Int] -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Maybe Int) -> [Int] -> Maybe Int
forall a b. (a -> b) -> a -> b
$ (ColumnProperty -> Int) -> [ColumnProperty] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int)
-> (ColumnProperty -> Maybe Int) -> ColumnProperty -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnProperty -> Maybe Int
columnRelWidth) [ColumnProperty]
colProps
else Maybe Int
forall a. Maybe a
Nothing
in Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Blocks
B.table (Blocks -> Caption
B.simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
caption)
((ColumnProperty -> ColSpec) -> [ColumnProperty] -> [ColSpec]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Int -> ColumnProperty -> ColSpec
convertColProp Maybe Int
totalWidth) [ColumnProperty]
colProps)
(Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Row]
toHeaderRow [Blocks]
heads)
[Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([Blocks] -> Row) -> [[Blocks]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Blocks] -> Row
toRow [[Blocks]]
lns]
(Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
where
toRow :: [Blocks] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Blocks] -> [Cell]) -> [Blocks] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Blocks -> Cell) -> [Blocks] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Cell
B.simpleCell
toHeaderRow :: [Blocks] -> [Row]
toHeaderRow [Blocks]
l = [[Blocks] -> Row
toRow [Blocks]
l | Bool -> Bool
not ([Blocks] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Blocks]
l)]
convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth)
convertColProp :: Maybe Int -> ColumnProperty -> ColSpec
convertColProp Maybe Int
totalWidth ColumnProperty
colProp =
let
align' :: Alignment
align' = Alignment -> Maybe Alignment -> Alignment
forall a. a -> Maybe a -> a
fromMaybe Alignment
AlignDefault (Maybe Alignment -> Alignment) -> Maybe Alignment -> Alignment
forall a b. (a -> b) -> a -> b
$ ColumnProperty -> Maybe Alignment
columnAlignment ColumnProperty
colProp
width' :: Maybe Double
width' = (\Int
w Int
t -> Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
t)
(Int -> Int -> Double) -> Maybe Int -> Maybe (Int -> Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnProperty -> Maybe Int
columnRelWidth ColumnProperty
colProp
Maybe (Int -> Double) -> Maybe Int -> Maybe Double
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Int
totalWidth
in (Alignment
align', ColWidth -> (Double -> ColWidth) -> Maybe Double -> ColWidth
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ColWidth
ColWidthDefault Double -> ColWidth
ColWidth Maybe Double
width')
tableRows :: PandocMonad m => OrgParser m [OrgTableRow]
tableRows :: OrgParser m [OrgTableRow]
tableRows = OrgParser m [OrgTableRow] -> OrgParser m [OrgTableRow]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m [OrgTableRow] -> OrgParser m [OrgTableRow])
-> OrgParser m [OrgTableRow] -> OrgParser m [OrgTableRow]
forall a b. (a -> b) -> a -> b
$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
-> OrgParser m [OrgTableRow]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
forall (m :: * -> *). Monad m => OrgParser m OrgTableRow
tableAlignRow ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
forall (m :: * -> *). Monad m => OrgParser m OrgTableRow
tableHline ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) OrgTableRow
forall (m :: * -> *). PandocMonad m => OrgParser m OrgTableRow
tableContentRow)
tableContentRow :: PandocMonad m => OrgParser m OrgTableRow
tableContentRow :: OrgParser m OrgTableRow
tableContentRow = OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m OrgTableRow -> OrgParser m OrgTableRow)
-> OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall a b. (a -> b) -> a -> b
$
F [Blocks] -> OrgTableRow
OrgContentRow (F [Blocks] -> OrgTableRow)
-> ([F Blocks] -> F [Blocks]) -> [F Blocks] -> OrgTableRow
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Blocks] -> F [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([F Blocks] -> OrgTableRow)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> OrgParser m OrgTableRow
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
tableStart OrgParser m Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks)
-> OrgParser m Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till ParserT Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
tableContentCell OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
tableContentCell :: PandocMonad m => OrgParser m (F Blocks)
tableContentCell :: OrgParser m (F Blocks)
tableContentCell = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$
(Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Blocks
B.plain (F Inlines -> F Blocks)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F 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 Text OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
endOfCell
tableAlignRow :: Monad m => OrgParser m OrgTableRow
tableAlignRow :: OrgParser m OrgTableRow
tableAlignRow = OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m OrgTableRow -> OrgParser m OrgTableRow)
-> OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall a b. (a -> b) -> a -> b
$ do
OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
tableStart
[ColumnProperty]
colProps <- ParserT
Text OrgParserState (ReaderT OrgParserLocal m) ColumnProperty
-> OrgParser m Char
-> ParserT
Text OrgParserState (ReaderT OrgParserLocal m) [ColumnProperty]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till ParserT
Text OrgParserState (ReaderT OrgParserLocal m) ColumnProperty
forall (m :: * -> *). Monad m => OrgParser m ColumnProperty
columnPropertyCell OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ())
-> Bool
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ (ColumnProperty -> Bool) -> [ColumnProperty] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (ColumnProperty -> ColumnProperty -> Bool
forall a. Eq a => a -> a -> Bool
/= ColumnProperty
forall a. Default a => a
def) [ColumnProperty]
colProps
OrgTableRow -> OrgParser m OrgTableRow
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgTableRow -> OrgParser m OrgTableRow)
-> OrgTableRow -> OrgParser m OrgTableRow
forall a b. (a -> b) -> a -> b
$ [ColumnProperty] -> OrgTableRow
OrgAlignRow [ColumnProperty]
colProps
columnPropertyCell :: Monad m => OrgParser m ColumnProperty
columnPropertyCell :: OrgParser m ColumnProperty
columnPropertyCell = OrgParser m ColumnProperty
emptyOrgCell OrgParser m ColumnProperty
-> OrgParser m ColumnProperty -> OrgParser m ColumnProperty
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m ColumnProperty
propCell OrgParser m ColumnProperty -> String -> OrgParser m ColumnProperty
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"alignment info"
where
emptyOrgCell :: OrgParser m ColumnProperty
emptyOrgCell = Maybe Alignment -> Maybe Int -> ColumnProperty
ColumnProperty Maybe Alignment
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing ColumnProperty
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ColumnProperty
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
endOfCell)
propCell :: OrgParser m ColumnProperty
propCell = OrgParser m ColumnProperty -> OrgParser m ColumnProperty
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m ColumnProperty -> OrgParser m ColumnProperty)
-> OrgParser m ColumnProperty -> OrgParser m ColumnProperty
forall a b. (a -> b) -> a -> b
$ Maybe Alignment -> Maybe Int -> ColumnProperty
ColumnProperty
(Maybe Alignment -> Maybe Int -> ColumnProperty)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Alignment)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Maybe Int -> ColumnProperty)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Alignment)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Alignment)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Alignment
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Alignment)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Alignment
forall (m :: * -> *). Monad m => OrgParser m Alignment
tableAlignFromChar)
ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Maybe Int -> ColumnProperty)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
-> OrgParser m ColumnProperty
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
digit ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> (Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead)
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'>'
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
-> OrgParser m ColumnProperty
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ColumnProperty
emptyOrgCell)
tableAlignFromChar :: Monad m => OrgParser m Alignment
tableAlignFromChar :: OrgParser m Alignment
tableAlignFromChar = OrgParser m Alignment -> OrgParser m Alignment
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Alignment -> OrgParser m Alignment)
-> OrgParser m Alignment -> OrgParser m Alignment
forall a b. (a -> b) -> a -> b
$
[OrgParser m Alignment] -> OrgParser m Alignment
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'l' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> Alignment -> OrgParser m Alignment
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Alignment
AlignLeft
, Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'c' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> Alignment -> OrgParser m Alignment
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Alignment
AlignCenter
, Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'r' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> Alignment -> OrgParser m Alignment
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Alignment
AlignRight
]
tableHline :: Monad m => OrgParser m OrgTableRow
tableHline :: OrgParser m OrgTableRow
tableHline = OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m OrgTableRow -> OrgParser m OrgTableRow)
-> OrgParser m OrgTableRow -> OrgParser m OrgTableRow
forall a b. (a -> b) -> a -> b
$
OrgTableRow
OrgHlineRow OrgTableRow
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m OrgTableRow
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
tableStart OrgParser m Char -> OrgParser m Char -> OrgParser m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> OrgParser m Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'-' OrgParser m Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine)
endOfCell :: Monad m => OrgParser m Char
endOfCell :: OrgParser m Char
endOfCell = OrgParser m Char -> OrgParser m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Char -> OrgParser m Char)
-> OrgParser m Char -> OrgParser m Char
forall a b. (a -> b) -> a -> b
$ Char -> OrgParser m Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'|' OrgParser m Char -> OrgParser m Char -> OrgParser m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m Char -> OrgParser m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
rowsToTable :: [OrgTableRow]
-> F OrgTable
rowsToTable :: [OrgTableRow] -> Future OrgParserState OrgTable
rowsToTable = (OrgTable -> OrgTableRow -> Future OrgParserState OrgTable)
-> OrgTable -> [OrgTableRow] -> Future OrgParserState OrgTable
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM OrgTable -> OrgTableRow -> Future OrgParserState OrgTable
rowToContent OrgTable
emptyTable
where emptyTable :: OrgTable
emptyTable = [ColumnProperty] -> [Blocks] -> [[Blocks]] -> OrgTable
OrgTable [ColumnProperty]
forall a. Monoid a => a
mempty [Blocks]
forall a. Monoid a => a
mempty [[Blocks]]
forall a. Monoid a => a
mempty
normalizeTable :: OrgTable -> OrgTable
normalizeTable :: OrgTable -> OrgTable
normalizeTable (OrgTable [ColumnProperty]
colProps [Blocks]
heads [[Blocks]]
rows) =
[ColumnProperty] -> [Blocks] -> [[Blocks]] -> OrgTable
OrgTable [ColumnProperty]
colProps' [Blocks]
heads [[Blocks]]
rows
where
refRow :: [Blocks]
refRow = if [Blocks]
heads [Blocks] -> [Blocks] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Blocks]
forall a. Monoid a => a
mempty
then [Blocks]
heads
else case [[Blocks]]
rows of
([Blocks]
r:[[Blocks]]
_) -> [Blocks]
r
[[Blocks]]
_ -> [Blocks]
forall a. Monoid a => a
mempty
cols :: Int
cols = [Blocks] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Blocks]
refRow
fillColumns :: [a] -> a -> [a]
fillColumns [a]
base a
padding = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
cols ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ [a]
base [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ a -> [a]
forall a. a -> [a]
repeat a
padding
colProps' :: [ColumnProperty]
colProps' = [ColumnProperty] -> ColumnProperty -> [ColumnProperty]
forall a. [a] -> a -> [a]
fillColumns [ColumnProperty]
colProps ColumnProperty
forall a. Default a => a
def
rowToContent :: OrgTable
-> OrgTableRow
-> F OrgTable
rowToContent :: OrgTable -> OrgTableRow -> Future OrgParserState OrgTable
rowToContent OrgTable
tbl OrgTableRow
row =
case OrgTableRow
row of
OrgTableRow
OrgHlineRow -> OrgTable -> Future OrgParserState OrgTable
forall (m :: * -> *) a. Monad m => a -> m a
return OrgTable
singleRowPromotedToHeader
OrgAlignRow [ColumnProperty]
props -> OrgTable -> Future OrgParserState OrgTable
forall (m :: * -> *) a. Monad m => a -> m a
return (OrgTable -> Future OrgParserState OrgTable)
-> ([ColumnProperty] -> OrgTable)
-> [ColumnProperty]
-> Future OrgParserState OrgTable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ColumnProperty] -> OrgTable
setProperties ([ColumnProperty] -> Future OrgParserState OrgTable)
-> [ColumnProperty] -> Future OrgParserState OrgTable
forall a b. (a -> b) -> a -> b
$ [ColumnProperty]
props
OrgContentRow F [Blocks]
cs -> F [Blocks] -> Future OrgParserState OrgTable
appendToBody F [Blocks]
cs
where
singleRowPromotedToHeader :: OrgTable
singleRowPromotedToHeader :: OrgTable
singleRowPromotedToHeader = case OrgTable
tbl of
OrgTable{ orgTableHeader :: OrgTable -> [Blocks]
orgTableHeader = [], orgTableRows :: OrgTable -> [[Blocks]]
orgTableRows = [[Blocks]
b] } ->
OrgTable
tbl{ orgTableHeader :: [Blocks]
orgTableHeader = [Blocks]
b , orgTableRows :: [[Blocks]]
orgTableRows = [] }
OrgTable
_ -> OrgTable
tbl
setProperties :: [ColumnProperty] -> OrgTable
setProperties :: [ColumnProperty] -> OrgTable
setProperties [ColumnProperty]
ps = OrgTable
tbl{ orgTableColumnProperties :: [ColumnProperty]
orgTableColumnProperties = [ColumnProperty]
ps }
appendToBody :: F [Blocks] -> F OrgTable
appendToBody :: F [Blocks] -> Future OrgParserState OrgTable
appendToBody F [Blocks]
frow = do
[Blocks]
newRow <- F [Blocks]
frow
let oldRows :: [[Blocks]]
oldRows = OrgTable -> [[Blocks]]
orgTableRows OrgTable
tbl
OrgTable -> Future OrgParserState OrgTable
forall (m :: * -> *) a. Monad m => a -> m a
return OrgTable
tbl{ orgTableRows :: [[Blocks]]
orgTableRows = [[Blocks]]
oldRows [[Blocks]] -> [[Blocks]] -> [[Blocks]]
forall a. [a] -> [a] -> [a]
++ [[Blocks]
newRow] }
latexFragment :: PandocMonad m => OrgParser m (F Blocks)
latexFragment :: OrgParser m (F Blocks)
latexFragment = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
envName <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
latexEnvStart
TeXExport
texOpt <- (ExportSettings -> TeXExport) -> OrgParser m TeXExport
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> TeXExport
exportWithLatex
let envStart :: Text
envStart = Text
"\\begin{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
envName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
let envEnd :: Text
envEnd = Text
"\\end{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
envName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
[Text]
envLines <- do
[Text]
content <- OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
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 OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine (Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
latexEnd Text
envName)
[Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text])
-> [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall a b. (a -> b) -> a -> b
$ Text
envStart Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
content [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
envEnd]
Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Blocks -> OrgParser m (F Blocks))
-> Blocks -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ case TeXExport
texOpt of
TeXExport
TeXExport -> Text -> Text -> Blocks
B.rawBlock Text
"latex" (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> Blocks) -> [Text] -> Blocks
forall a b. (a -> b) -> a -> b
$ [Text]
envLines
TeXExport
TeXIgnore -> Blocks
forall a. Monoid a => a
mempty
TeXExport
TeXVerbatim -> Inlines -> Blocks
B.para (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [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.softbreak ([Inlines] -> Blocks) -> [Inlines] -> Blocks
forall a b. (a -> b) -> a -> b
$
(Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
B.str [Text]
envLines
where
latexEnd :: Monad m => Text -> OrgParser m ()
latexEnd :: Text -> OrgParser m ()
latexEnd Text
envName = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m () -> OrgParser m ())
-> (OrgParser m () -> OrgParser m ())
-> OrgParser m ()
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParser m () -> OrgParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
(OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Text -> ParserT s st m Text
textStr (Text
"\\end{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
envName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}")
OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline
noteBlock :: PandocMonad m => OrgParser m (F Blocks)
noteBlock :: OrgParser m (F Blocks)
noteBlock = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
ref <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
noteMarker OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
F Blocks
content <- [F Blocks] -> F Blocks
forall a. Monoid a => [a] -> a
mconcat ([F Blocks] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Blocks)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
block ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfFootnote
OrgNoteRecord
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *).
PandocMonad m =>
OrgNoteRecord -> OrgParser m ()
addToNotesTable (Text
ref, F Blocks
content)
F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return F Blocks
forall a. Monoid a => a
mempty
where
endOfFootnote :: ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfFootnote = ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ OrgParser m Text -> OrgParser m Text
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
noteMarker
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
headerStart
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline)
paraOrPlain :: PandocMonad m => OrgParser m (F Blocks)
paraOrPlain :: OrgParser m (F Blocks)
paraOrPlain = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
headerStart
F Inlines
ils <- OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlines
Bool
nl <- Bool
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline OrgParser m Char
-> Bool
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
True)
OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Bool -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
nl
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
inList ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
orderedListStart ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart))
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> F Blocks -> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (Inlines -> Blocks
B.para (Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
ils))
OrgParser m (F Blocks)
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Blocks -> OrgParser m (F Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Blocks
B.plain (Inlines -> Blocks) -> F Inlines -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
ils)
list :: PandocMonad m => OrgParser m (F Blocks)
list :: OrgParser m (F Blocks)
list = [OrgParser m (F Blocks)] -> OrgParser m (F Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
definitionList, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
bulletList, OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
orderedList ] OrgParser m (F Blocks) -> String -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"list"
definitionList :: PandocMonad m => OrgParser m (F Blocks)
definitionList :: OrgParser m (F Blocks)
definitionList = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int
indent <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart
([(Inlines, [Blocks])] -> Blocks)
-> Future OrgParserState [(Inlines, [Blocks])] -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([(Inlines, [Blocks])] -> Blocks
B.definitionList ([(Inlines, [Blocks])] -> Blocks)
-> ([(Inlines, [Blocks])] -> [(Inlines, [Blocks])])
-> [(Inlines, [Blocks])]
-> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
compactifyDL) (Future OrgParserState [(Inlines, [Blocks])] -> F Blocks)
-> ([Future OrgParserState (Inlines, [Blocks])]
-> Future OrgParserState [(Inlines, [Blocks])])
-> [Future OrgParserState (Inlines, [Blocks])]
-> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Future OrgParserState (Inlines, [Blocks])]
-> Future OrgParserState [(Inlines, [Blocks])]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([Future OrgParserState (Inlines, [Blocks])] -> F Blocks)
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[Future OrgParserState (Inlines, [Blocks])]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState (Inlines, [Blocks]))
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
[Future OrgParserState (Inlines, [Blocks])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState (Inlines, [Blocks]))
forall (m :: * -> *).
PandocMonad m =>
OrgParser m Int
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
definitionListItem (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). OrgParser m Int -> Int -> OrgParser m Int
`indented` Int
indent))
bulletList :: PandocMonad m => OrgParser m (F Blocks)
bulletList :: OrgParser m (F Blocks)
bulletList = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int
indent <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart
([Blocks] -> Blocks) -> F [Blocks] -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> [Blocks]
compactify) (F [Blocks] -> F Blocks)
-> ([F Blocks] -> F [Blocks]) -> [F Blocks] -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Blocks] -> F [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([F Blocks] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m Int -> OrgParser m (F Blocks)
listItem (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). OrgParser m Int -> Int -> OrgParser m Int
`indented` Int
indent))
indented :: OrgParser m Int -> Int -> OrgParser m Int
indented :: OrgParser m Int -> Int -> OrgParser m Int
indented OrgParser m Int
indentedMarker Int
minIndent = OrgParser m Int -> OrgParser m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Int -> OrgParser m Int)
-> OrgParser m Int -> OrgParser m Int
forall a b. (a -> b) -> a -> b
$ do
Int
n <- OrgParser m Int
indentedMarker
Bool -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int
minIndent Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n)
Int -> OrgParser m Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
orderedList :: PandocMonad m => OrgParser m (F Blocks)
orderedList :: OrgParser m (F Blocks)
orderedList = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int
indent <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
orderedListStart
([Blocks] -> Blocks) -> F [Blocks] -> F Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Blocks] -> Blocks
B.orderedList ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> [Blocks]
compactify) (F [Blocks] -> F Blocks)
-> ([F Blocks] -> F [Blocks]) -> [F Blocks] -> F Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Blocks] -> F [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
([F Blocks] -> F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
-> OrgParser m (F Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> OrgParser m (F Blocks)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m Int -> OrgParser m (F Blocks)
listItem (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
orderedListStart ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). OrgParser m Int -> Int -> OrgParser m Int
`indented` Int
indent))
definitionListItem :: PandocMonad m
=> OrgParser m Int
-> OrgParser m (F (Inlines, [Blocks]))
definitionListItem :: OrgParser m Int
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
definitionListItem OrgParser m Int
parseIndentedMarker = OrgParser m (Future OrgParserState (Inlines, [Blocks]))
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Future OrgParserState (Inlines, [Blocks]))
-> OrgParser m (Future OrgParserState (Inlines, [Blocks])))
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
forall a b. (a -> b) -> a -> b
$ do
Int
markerLength <- OrgParser m Int
parseIndentedMarker
Text
term <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar (String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\n\r") (ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
definitionMarker)
Text
line1 <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) st. Monad m => ParserT Text st m Text
anyLineNewline
Text
blank <- Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal 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
"" (Text
"\n" Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline)
Text
cont <- [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Int -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Int -> OrgParser m Text
listContinuation Int
markerLength)
F Inlines
term' <- OrgParser m (F Inlines) -> Text -> OrgParser m (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlines Text
term
F Blocks
contents' <- OrgParser m (F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks (Text -> OrgParser m (F Blocks)) -> Text -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Text
line1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
blank Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cont
Future OrgParserState (Inlines, [Blocks])
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
forall (m :: * -> *) a. Monad m => a -> m a
return (Future OrgParserState (Inlines, [Blocks])
-> OrgParser m (Future OrgParserState (Inlines, [Blocks])))
-> Future OrgParserState (Inlines, [Blocks])
-> OrgParser m (Future OrgParserState (Inlines, [Blocks]))
forall a b. (a -> b) -> a -> b
$ (,) (Inlines -> [Blocks] -> (Inlines, [Blocks]))
-> F Inlines
-> Future OrgParserState ([Blocks] -> (Inlines, [Blocks]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
term' Future OrgParserState ([Blocks] -> (Inlines, [Blocks]))
-> F [Blocks] -> Future OrgParserState (Inlines, [Blocks])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Blocks -> [Blocks]) -> F Blocks -> F [Blocks]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
:[]) F Blocks
contents'
where
definitionMarker :: ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
definitionMarker =
ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"::" ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
spaceChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
listItem :: PandocMonad m
=> OrgParser m Int
-> OrgParser m (F Blocks)
listItem :: OrgParser m Int -> OrgParser m (F Blocks)
listItem OrgParser m Int
parseIndentedMarker = OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks)
-> OrgParser m (F Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserContext -> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall (m :: * -> *) a.
Monad m =>
ParserContext -> OrgParser m a -> OrgParser m a
withContext ParserContext
ListItemState (OrgParser m (F Blocks) -> OrgParser m (F Blocks))
-> OrgParser m (F Blocks) -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int
markerLength <- OrgParser m Int -> OrgParser m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try OrgParser m Int
parseIndentedMarker
Text
firstLine <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) st. Monad m => ParserT Text st m Text
anyLineNewline
Text
blank <- Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal 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
"" (Text
"\n" Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline)
Text
rest <- [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Int -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Int -> OrgParser m Text
listContinuation Int
markerLength)
OrgParser m (F Blocks) -> Text -> OrgParser m (F Blocks)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString OrgParser m (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
blocks (Text -> OrgParser m (F Blocks)) -> Text -> OrgParser m (F Blocks)
forall a b. (a -> b) -> a -> b
$ Text
firstLine Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
blank Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rest
listContinuation :: PandocMonad m => Int -> OrgParser m Text
listContinuation :: Int -> OrgParser m Text
listContinuation Int
markerLength = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline
Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend (Text -> Text -> Text)
-> OrgParser m Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> OrgParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Int -> OrgParser m Text
forall (m :: * -> *). PandocMonad m => Int -> OrgParser m Text
listContinuation' Int
markerLength))
ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
-> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
blankline
where
listContinuation' :: Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
listContinuation' Int
indentation =
Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Int -> OrgParser m Text
blockLines Int
indentation ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) u.
(Monad m, HasReaderOptions u) =>
Int -> ParsecT Text u m Text
listLine Int
indentation
listLine :: Int -> ParsecT Text u m Text
listLine Int
indentation = ParsecT Text u m Text -> ParsecT Text u m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u m Text -> ParsecT Text u m Text)
-> ParsecT Text u m Text -> ParsecT Text u m Text
forall a b. (a -> b) -> a -> b
$ Int -> ParsecT Text u m Text
forall s (m :: * -> *) st.
(Stream s m Char, HasReaderOptions st) =>
Int -> ParserT s st m Text
indentWith Int
indentation ParsecT Text u m Text
-> ParsecT Text u m Text -> ParsecT Text u m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text u m Text
forall (m :: * -> *) st. Monad m => ParserT Text st m Text
anyLineNewline
blockLines :: Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
blockLines Int
indentation =
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
(Stream s m Char, HasReaderOptions st) =>
Int -> ParserT s st m Text
indentWith Int
indentation
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) BlockAttributes
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) BlockAttributes
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) BlockAttributes
forall (m :: * -> *). PandocMonad m => OrgParser m BlockAttributes
blockAttributes
ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) BlockAttributes
-> (BlockAttributes
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\BlockAttributes
blockAttrs ->
case BlockAttributes -> Attr
attrFromBlockAttributes BlockAttributes
blockAttrs of
(Text
"", [], []) -> Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
(Stream s m Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m Char
anyChar
Attr
_ -> Int -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
(Stream s m Char, HasReaderOptions st) =>
Int -> ParserT s st m Text
indentWith Int
indentation))
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ((F Blocks, Text) -> Text
forall a b. (a, b) -> b
snd ((F Blocks, Text) -> Text)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks, Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Text st m a -> ParsecT Text st m (a, Text)
withRaw ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Blocks)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Blocks)
orgBlock)