aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-03-20 10:41:55 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-03-20 15:58:32 -0700
commitce418667ae8a3e6e5bbf2523eef43edf4f803bcf (patch)
treec488d055ff31fe49de81cd36a5a35718964287cc /src/Text
parent4d041953f56b85d4db241cea11c764856ccbeebe (diff)
downloadpandoc-ce418667ae8a3e6e5bbf2523eef43edf4f803bcf.tar.gz
Text.Pandoc.Parsing: remove F type synonym.
Muse and Org were defining their own F anyway, with their own state. We therefore move this definition to the Markdown reader.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/App/Opt.hs3
-rw-r--r--src/Text/Pandoc/Parsing.hs7
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs2
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Parsing.hs4
5 files changed, 9 insertions, 9 deletions
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index e5aaec9c5..c72f63464 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -686,7 +686,8 @@ yamlToMeta (Mapping _ _ m) =
either (fail . show) return $ runEverything (yamlMap pMetaString m)
where
pMetaString = pure . MetaString <$> P.manyChar P.anyChar
- runEverything p = runPure (P.readWithM p def "")
+ runEverything p =
+ runPure (P.readWithM p (def :: P.ParserState) "")
>>= fmap (Meta . flip P.runF def)
yamlToMeta _ = return mempty
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 10a08d410..44e6af59e 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -112,7 +112,6 @@ module Text.Pandoc.Parsing ( take1WhileP,
citeKey,
Parser,
ParserT,
- F,
Future(..),
runF,
askF,
@@ -229,8 +228,6 @@ type ParserT = ParsecT
newtype Future s a = Future { runDelayed :: Reader s a }
deriving (Monad, Applicative, Functor)
-type F = Future ParserState
-
runF :: Future s a -> s -> a
runF = runReader . runDelayed
@@ -1169,7 +1166,7 @@ data ParserState = ParserState
stateInNote :: Bool, -- ^ True if parsing note contents
stateNoteNumber :: Int, -- ^ Last note number for citations
stateMeta :: Meta, -- ^ Document metadata
- stateMeta' :: F Meta, -- ^ Document metadata
+ stateMeta' :: Future ParserState Meta, -- ^ Document metadata
stateCitations :: M.Map Text Text, -- ^ RST-style citations
stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
stateIdentifiers :: Set.Set Text, -- ^ Header identifiers used
@@ -1348,7 +1345,7 @@ data QuoteContext
type NoteTable = [(Text, Text)]
-type NoteTable' = M.Map Text (SourcePos, F Blocks)
+type NoteTable' = M.Map Text (SourcePos, Future ParserState Blocks)
-- used in markdown reader
newtype Key = Key Text deriving (Show, Read, Eq, Ord)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index a86286b3a..7c557b5a7 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -52,6 +52,8 @@ import Text.Pandoc.Readers.Metadata (yamlBsToMeta, yamlBsToRefs)
type MarkdownParser m = ParserT Text ParserState m
+type F = Future ParserState
+
-- | Read markdown from an input string and return a Pandoc document.
readMarkdown :: PandocMonad m
=> ReaderOptions -- ^ Reader options
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index b4eea9d3a..698bfd3d7 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -36,7 +36,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.Parsing hiding (F)
+import Text.Pandoc.Parsing
import Text.Pandoc.Shared (crFilter, trimr, tshow)
-- | Read Muse from an input string and return a Pandoc document.
diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs
index d33920d47..6ed24a602 100644
--- a/src/Text/Pandoc/Readers/Org/Parsing.hs
+++ b/src/Text/Pandoc/Readers/Org/Parsing.hs
@@ -106,8 +106,8 @@ module Text.Pandoc.Readers.Org.Parsing
import Data.Text (Text)
import Text.Pandoc.Readers.Org.ParserState
-import Text.Pandoc.Parsing hiding (F, anyLine, blanklines, newline,
- parseFromString)
+import Text.Pandoc.Parsing hiding (anyLine, blanklines, newline,
+ parseFromString)
import qualified Text.Pandoc.Parsing as P
import Control.Monad (guard)