aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/ParserState.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2017-04-27 21:48:32 +0200
committerAlbert Krewinkel <albert+github@zeitkraut.de>2017-04-30 10:59:20 +0200
commit31caa616a9353e073eb86be7889b7087e14a48ac (patch)
tree44be7b17210655bfc307e7b276e1b7829ce314ab /src/Text/Pandoc/Readers/Org/ParserState.hs
parent97addc2a17266b7d1c6cc712244f675bc0263595 (diff)
downloadpandoc-31caa616a9353e073eb86be7889b7087e14a48ac.tar.gz
Provide shared F monad functions for Markdown and Org readers
The `F` monads used for delayed evaluation of certain values in the Markdown and Org readers are based on a shared data type capturing the common pattern of both `F` types.
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/ParserState.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs46
1 files changed, 9 insertions, 37 deletions
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 6bed2a547..bdd1dc951 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -39,7 +39,7 @@ module Text.Pandoc.Readers.Org.ParserState
, TodoState (..)
, activeTodoMarkers
, registerTodoSequence
- , F(..)
+ , F
, askF
, asksF
, trimInlinesF
@@ -50,14 +50,13 @@ module Text.Pandoc.Readers.Org.ParserState
, optionsToParserState
) where
-import Control.Monad (liftM, liftM2)
-import Control.Monad.Reader (Reader, ReaderT, ask, asks, local, runReader)
+import Control.Monad.Reader (ReaderT, asks, local)
import Data.Default (Default (..))
import qualified Data.Map as M
import qualified Data.Set as Set
-import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import Text.Pandoc.Builder (Blocks, Inlines)
import Text.Pandoc.Definition (Meta (..), nullMeta)
import Text.Pandoc.Options (ReaderOptions (..))
import Text.Pandoc.Logging
@@ -65,7 +64,12 @@ import Text.Pandoc.Parsing (HasHeaderMap (..), HasIdentifierList (..),
HasLogMessages (..),
HasLastStrPosition (..), HasQuoteContext (..),
HasReaderOptions (..), ParserContext (..),
- QuoteContext (..), SourcePos)
+ QuoteContext (..), SourcePos, Future,
+ askF, asksF, returnF, runF, trimInlinesF)
+
+-- | This is used to delay evaluation until all relevant information has been
+-- parsed and made available in the parser state.
+type F = Future OrgParserState
-- | An inline note / footnote containing the note key and its (inline) value.
type OrgNoteRecord = (String, F Blocks)
@@ -229,35 +233,3 @@ defaultExportSettings = ExportSettings
, exportWithEmail = True
, exportWithTodoKeywords = True
}
-
-
---
--- Parser state reader
---
-
--- | Reader monad wrapping the parser state. This is used to delay evaluation
--- until all relevant information has been parsed and made available in the
--- parser state. See also the newtype of the same name in
--- Text.Pandoc.Parsing.
-newtype F a = F { unF :: Reader OrgParserState a
- } deriving (Functor, Applicative, Monad)
-
-instance Monoid a => Monoid (F a) where
- mempty = return mempty
- mappend = liftM2 mappend
- mconcat = fmap mconcat . sequence
-
-runF :: F a -> OrgParserState -> a
-runF = runReader . unF
-
-askF :: F OrgParserState
-askF = F ask
-
-asksF :: (OrgParserState -> a) -> F a
-asksF f = F $ asks f
-
-trimInlinesF :: F Inlines -> F Inlines
-trimInlinesF = liftM trimInlines
-
-returnF :: Monad m => a -> m (F a)
-returnF = return . return