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.
This commit is contained in:
Albert Krewinkel 2014-05-14 14:45:37 +02:00
parent a8319d1339
commit 9df589b9c5
3 changed files with 30 additions and 24 deletions

View file

@ -54,7 +54,6 @@ module Text.Pandoc.Parsing ( (>>~),
withRaw,
escaped,
characterReference,
updateLastStrPos,
anyOrderedListMarker,
orderedListMarker,
charRef,
@ -66,11 +65,14 @@ module Text.Pandoc.Parsing ( (>>~),
testStringWith,
guardEnabled,
guardDisabled,
updateLastStrPos,
notAfterString,
ParserState (..),
HasReaderOptions (..),
HasHeaderMap (..),
HasIdentifierList (..),
HasMacros (..),
HasLastStrPosition (..),
defaultParserState,
HeaderType (..),
ParserContext (..),
@ -904,6 +906,14 @@ instance HasMacros ParserState where
extractMacros = stateMacros
updateMacros f st = st{ stateMacros = f $ stateMacros st }
class HasLastStrPosition st where
setLastStrPos :: SourcePos -> st -> st
getLastStrPos :: st -> Maybe SourcePos
instance HasLastStrPosition ParserState where
setLastStrPos pos st = st{ stateLastStrPos = Just pos }
getLastStrPos st = stateLastStrPos st
defaultParserState :: ParserState
defaultParserState =
ParserState { stateOptions = def,
@ -938,6 +948,17 @@ guardEnabled ext = getOption readerExtensions >>= guard . Set.member ext
guardDisabled :: HasReaderOptions st => Extension -> Parser s st ()
guardDisabled ext = getOption readerExtensions >>= guard . not . Set.member ext
-- | Update the position on which the last string ended.
updateLastStrPos :: HasLastStrPosition st => Parser s st ()
updateLastStrPos = getPosition >>= updateState . setLastStrPos
-- | Whether we are right after the end of a string.
notAfterString :: HasLastStrPosition st => Parser s st Bool
notAfterString = do
pos <- getPosition
st <- getState
return $ getLastStrPos st /= Just pos
data HeaderType
= SingleHeader Char -- ^ Single line of characters underneath
| DoubleHeader Char -- ^ Lines of characters above and below
@ -1049,17 +1070,11 @@ charOrRef cs =
guard (c `elem` cs)
return c)
updateLastStrPos :: Parser [Char] ParserState ()
updateLastStrPos = getPosition >>= \p ->
updateState $ \s -> s{ stateLastStrPos = Just p }
singleQuoteStart :: Parser [Char] ParserState ()
singleQuoteStart = do
failIfInQuoteContext InSingleQuote
pos <- getPosition
st <- getState
-- single quote start can't be right after str
guard $ stateLastStrPos st /= Just pos
guard =<< notAfterString
() <$ charOrRef "'\8216\145"
singleQuoteEnd :: Parser [Char] st ()
@ -1156,4 +1171,3 @@ applyMacros' target = do
then do macros <- extractMacros `fmap` getState
return $ applyMacros macros target
else return target

View file

@ -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 '_'

View file

@ -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