From 2b580600077b615bb66e3bf3b49785a7b8772d09 Mon Sep 17 00:00:00 2001
From: Matthew Pickering <matthewtpickering@gmail.com>
Date: Fri, 30 Jan 2015 12:32:12 +0000
Subject: [PATCH] Remove F monad from Parsing

---
 src/Text/Pandoc/Parsing.hs     | 26 ++------------------------
 src/Text/Pandoc/Readers/Org.hs |  3 +--
 2 files changed, 3 insertions(+), 26 deletions(-)

diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 2a1d61b97..8f1d1086d 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -104,10 +104,6 @@ module Text.Pandoc.Parsing ( anyLine,
                              applyMacros',
                              Parser,
                              ParserT,
-                             F(..),
-                             runF,
-                             askF,
-                             asksF,
                              token,
                              generalize,
                              -- * Re-exports from Text.Pandoc.Parsec
@@ -189,7 +185,7 @@ import Data.Default
 import qualified Data.Set as Set
 import Control.Monad.Reader
 import Control.Monad.Identity
-import Control.Applicative ((<$>), (<*>), (*>), (<*), (<$), Applicative)
+import Control.Applicative ((<$>), (<*>), (*>), (<*), (<$))
 import Data.Monoid
 import Data.Maybe (catMaybes)
 
@@ -197,22 +193,6 @@ type Parser t s = Parsec t s
 
 type ParserT = ParsecT
 
-newtype F a = F { unF :: Reader ParserState a } deriving (Monad, Applicative, 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
-
 -- | Parse any line of text
 anyLine :: Stream [Char] m Char => ParserT [Char] st m [Char]
 anyLine = do
@@ -914,7 +894,6 @@ data ParserState = ParserState
       stateNotes           :: NoteTable,     -- ^ List of notes (raw bodies)
       stateNotes'          :: NoteTable',    -- ^ List of notes (parsed bodies)
       stateMeta            :: Meta,          -- ^ Document metadata
-      stateMeta'           :: F Meta,        -- ^ Document metadata
       stateHeaderTable     :: [HeaderType],  -- ^ Ordered list of header types used
       stateHeaders         :: M.Map Inlines String, -- ^ List of headers and ids (used for implicit ref links)
       stateIdentifiers     :: [String],      -- ^ List of header identifiers used
@@ -1011,7 +990,6 @@ defaultParserState =
                   stateNotes           = [],
                   stateNotes'          = [],
                   stateMeta            = nullMeta,
-                  stateMeta'           = return nullMeta,
                   stateHeaderTable     = [],
                   stateHeaders         = M.empty,
                   stateIdentifiers     = [],
@@ -1063,7 +1041,7 @@ data QuoteContext
 
 type NoteTable = [(String, String)]
 
-type NoteTable' = [(String, F Blocks)]  -- used in markdown reader
+type NoteTable' = [(String, Blocks)]  -- used in markdown reader
 
 newtype Key = Key String deriving (Show, Read, Eq, Ord)
 
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 97a15576b..5cb66bfa7 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -37,8 +37,7 @@ import           Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..), (<>)
 import           Text.Pandoc.Definition
 import           Text.Pandoc.Options
 import qualified Text.Pandoc.Parsing as P
-import           Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
-                                            , newline, orderedListMarker
+import           Text.Pandoc.Parsing hiding ( newline, orderedListMarker
                                             , parseFromString, blanklines
                                             )
 import           Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)