aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorAlbert Krewinkel <tarleb@moltkeplatz.de>2014-05-14 14:45:37 +0200
committerAlbert Krewinkel <tarleb@moltkeplatz.de>2014-05-14 14:57:00 +0200
commit9df589b9c5a4f2dcb19445239dfae41b54625330 (patch)
treeec3a85b63bcb5f434a57bb38b0d8fe0a12719017 /src/Text/Pandoc/Readers
parenta8319d133908f3c39834984e5e11991b166c37b7 (diff)
downloadpandoc-9df589b9c5a4f2dcb19445239dfae41b54625330.tar.gz
Introduce class HasLastStrPosition, generalize functions
Both `ParserState` and `OrgParserState` keep track of the parser position at which the last string ended. This patch introduces a new class `HasLastStrPosition` and makes the above types instances of that class. This enables the generalization of functions updating the state or checking if one is right after a string.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs11
-rw-r--r--src/Text/Pandoc/Readers/Org.hs11
2 files changed, 7 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index d1637b701..1ac98e94c 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1474,9 +1474,7 @@ strongOrEmph = enclosure '*' <|> (checkIntraword >> enclosure '_')
where checkIntraword = do
exts <- getOption readerExtensions
when (Ext_intraword_underscores `Set.member` exts) $ do
- pos <- getPosition
- lastStrPos <- stateLastStrPos <$> getState
- guard $ lastStrPos /= Just pos
+ guard =<< notAfterString
-- | Parses a list of inlines between start and end delimiters.
inlinesBetween :: (Show b)
@@ -1518,8 +1516,7 @@ nonEndline = satisfy (/='\n')
str :: MarkdownParser (F Inlines)
str = do
result <- many1 alphaNum
- pos <- getPosition
- updateState $ \s -> s{ stateLastStrPos = Just pos }
+ updateLastStrPos
let spacesToNbr = map (\c -> if c == ' ' then '\160' else c)
isSmart <- getOption readerSmart
if isSmart
@@ -1821,9 +1818,7 @@ citeKey :: MarkdownParser (Bool, String)
citeKey = try $ do
-- make sure we're not right after an alphanumeric,
-- since foo@bar.baz is probably an email address
- lastStrPos <- stateLastStrPos <$> getState
- pos <- getPosition
- guard $ lastStrPos /= Just pos
+ guard =<< notAfterString
suppress_author <- option False (char '-' >> return True)
char '@'
first <- letter <|> char '_'
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 2e4a29beb..5dbcaee98 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -105,6 +105,10 @@ instance HasMeta OrgParserState where
deleteMeta field st =
st{ orgStateMeta = deleteMeta field $ orgStateMeta st }
+instance HasLastStrPosition OrgParserState where
+ getLastStrPos = orgStateLastStrPos
+ setLastStrPos pos st = st{ orgStateLastStrPos = Just pos }
+
instance Default OrgParserState where
def = defaultOrgParserState
@@ -1274,13 +1278,6 @@ afterEmphasisPreChar = do
lastPrePos <- orgStateLastPreCharPos <$> getState
return . fromMaybe True $ (== pos) <$> lastPrePos
--- | Whether we are right after the end of a string
-notAfterString :: OrgParser Bool
-notAfterString = do
- pos <- getPosition
- lastStrPos <- orgStateLastStrPos <$> getState
- return $ lastStrPos /= Just pos
-
-- | Whether the parser is right after a forbidden border char
notAfterForbiddenBorderChar :: OrgParser Bool
notAfterForbiddenBorderChar = do