{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Readers.Org
   Copyright   : Copyright (C) 2014-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>

Conversion of org-mode formatted plain text to 'Pandoc' document.
-}
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.Shared (crFilter)

import Control.Monad.Except (throwError)
import Control.Monad.Reader (runReaderT)

import Data.Text (Text)

-- | Parse org-mode string and return a Pandoc document.
readOrg :: PandocMonad m
        => ReaderOptions -- ^ Reader options
        -> Text          -- ^ String to parse (assuming @'\n'@ line endings)
        -> m Pandoc
readOrg :: ReaderOptions -> Text -> m Pandoc
readOrg ReaderOptions
opts Text
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
$
            ParserT Text OrgParserState (ReaderT OrgParserLocal m) Pandoc
-> OrgParserState
-> Text
-> ReaderT OrgParserLocal m (Either PandocError Pandoc)
forall (m :: * -> *) st a.
Monad m =>
ParserT Text st m a -> st -> Text -> m (Either PandocError a)
readWithM ParserT Text OrgParserState (ReaderT OrgParserLocal m) Pandoc
forall (m :: * -> *). PandocMonad m => OrgParser m Pandoc
parseOrg (ReaderOptions -> OrgParserState
optionsToParserState ReaderOptions
opts)
            (Text -> Text
crFilter Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n")
  case Either PandocError Pandoc
parsed of
    Right Pandoc
result -> Pandoc -> m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
    Left  PandocError
e      -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e

--
-- Parser
--
parseOrg :: PandocMonad m => OrgParser m Pandoc
parseOrg :: 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
  ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParserT s st m ()
reportLogMessages
  Pandoc -> OrgParser m Pandoc
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'