blob: 2c88c7776e37d806a429fa56c589930afd8d20af (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
|
{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Readers.Org
Copyright : Copyright (C) 2014-2019 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 Prelude
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)
import Text.Pandoc.Definition
import Text.Pandoc.Error
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)
import qualified Data.Text as T
-- | 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 opts s = do
parsed <- flip runReaderT def $
readWithM parseOrg (optionsToParserState opts)
(T.unpack (crFilter s) ++ "\n\n")
case parsed of
Right result -> return result
Left _ -> throwError $ PandocParseError "problem parsing org"
--
-- Parser
--
parseOrg :: PandocMonad m => OrgParser m Pandoc
parseOrg = do
blocks' <- blockList
meta' <- meta
reportLogMessages
return $ Pandoc meta' blocks'
|