module Text.Pandoc.Readers.Org ( readOrg ) where
import Text.Pandoc.Readers.Org.Blocks (blockList, meta)
import Text.Pandoc.Readers.Org.ParserState (optionsToParserState)
import Text.Pandoc.Readers.Org.Parsing (OrgParser, readWithM)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Parsing (reportLogMessages)
import Text.Pandoc.Sources (ToSources(..), ensureFinalNewlines)
import Control.Monad.Except (throwError)
import Control.Monad.Reader (runReaderT)
readOrg :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readOrg :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readOrg ReaderOptions
opts a
s = do
Either PandocError Pandoc
parsed <- (ReaderT OrgParserLocal m (Either PandocError Pandoc)
-> OrgParserLocal -> m (Either PandocError Pandoc))
-> OrgParserLocal
-> ReaderT OrgParserLocal m (Either PandocError Pandoc)
-> m (Either PandocError Pandoc)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT OrgParserLocal m (Either PandocError Pandoc)
-> OrgParserLocal -> m (Either PandocError Pandoc)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT OrgParserLocal
forall a. Default a => a
def (ReaderT OrgParserLocal m (Either PandocError Pandoc)
-> m (Either PandocError Pandoc))
-> ReaderT OrgParserLocal m (Either PandocError Pandoc)
-> m (Either PandocError Pandoc)
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Pandoc
-> OrgParserState
-> Sources
-> ReaderT OrgParserLocal m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Pandoc
forall (m :: * -> *). PandocMonad m => OrgParser m Pandoc
parseOrg (ReaderOptions -> OrgParserState
optionsToParserState ReaderOptions
opts)
(Int -> Sources -> Sources
ensureFinalNewlines Int
2 (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s))
case Either PandocError Pandoc
parsed of
Right Pandoc
result -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
Left PandocError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
parseOrg :: PandocMonad m => OrgParser m Pandoc
parseOrg :: forall (m :: * -> *). PandocMonad m => OrgParser m Pandoc
parseOrg = do
[Block]
blocks' <- OrgParser m [Block]
forall (m :: * -> *). PandocMonad m => OrgParser m [Block]
blockList
Meta
meta' <- OrgParser m Meta
forall (m :: * -> *). Monad m => OrgParser m Meta
meta
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
Pandoc -> OrgParser m Pandoc
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> OrgParser m Pandoc) -> Pandoc -> OrgParser m Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta' [Block]
blocks'