aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Parsing.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2012-08-02 17:12:20 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2012-08-02 17:12:20 -0700
commit33fd791ea10e6d2a2ef53a1be5c8d2459a37ba6e (patch)
treee37e2d837d24e8cdea9552d799bc76c4c8cd0319 /src/Text/Pandoc/Parsing.hs
parentebd72e7ba6c6c775074d4c89f7e84fe9be0c24a3 (diff)
downloadpandoc-33fd791ea10e6d2a2ef53a1be5c8d2459a37ba6e.tar.gz
Made F a newtype, moved definitions to Parser.
Parser now exports F(..), askF, asksF, runF.
Diffstat (limited to 'src/Text/Pandoc/Parsing.hs')
-rw-r--r--src/Text/Pandoc/Parsing.hs24
1 files changed, 23 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 7099ea3c5..2eb07beec 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@@ -85,6 +86,10 @@ module Text.Pandoc.Parsing ( (>>~),
macro,
applyMacros',
Parser,
+ F(..),
+ runF,
+ askF,
+ asksF,
-- * Re-exports from Text.Pandoc.Parsec
runParser,
parse,
@@ -154,9 +159,26 @@ import Text.HTML.TagSoup.Entity ( lookupEntity )
import Data.Default
import qualified Data.Set as Set
import Control.Monad.Reader
+import Data.Monoid
type Parser t s = Parsec t s
+newtype F a = F { unF :: Reader ParserState a } deriving (Monad, Functor)
+
+runF :: F a -> ParserState -> a
+runF = runReader . unF
+
+askF :: F ParserState
+askF = F ask
+
+asksF :: (ParserState -> a) -> F a
+asksF f = F $ asks f
+
+instance Monoid a => Monoid (F a) where
+ mempty = return mempty
+ mappend = liftM2 mappend
+ mconcat = liftM mconcat . sequence
+
-- | Like >>, but returns the operation on the left.
-- (Suggested by Tillmann Rendel on Haskell-cafe list.)
(>>~) :: (Monad m) => m a -> m b -> m a
@@ -767,7 +789,7 @@ data QuoteContext
type NoteTable = [(String, String)]
-type NoteTable' = [(String, Reader ParserState Blocks)] -- used in markdown reader
+type NoteTable' = [(String, F Blocks)] -- used in markdown reader
newtype Key = Key String deriving (Show, Read, Eq, Ord)