From a1677b612b85e14dc810b84786d7844a5fc697fa Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Aug 2012 22:40:07 -0700 Subject: Parsing: removed duplication of Key and Key'. Now we just use the former Key' (string contents), renamed Key. lookupKeySrc and fromKey are no longer eport. Key', toKey' and KeyTable' have become Key, toKey, and KeyTable. --- src/Text/Pandoc/Readers/Markdown.hs | 8 ++++---- src/Text/Pandoc/Readers/RST.hs | 33 +++++++++++++++++++-------------- 2 files changed, 23 insertions(+), 18 deletions(-) (limited to 'src/Text/Pandoc/Readers') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 79bd21cab..93edbff30 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -227,8 +227,8 @@ referenceKey = try $ do blanklines let target = (escapeURI $ removeTrailingSpace src, tit) st <- getState - let oldkeys = stateKeys' st - updateState $ \s -> s { stateKeys' = M.insert (toKey' raw) target oldkeys } + let oldkeys = stateKeys st + updateState $ \s -> s { stateKeys = M.insert (toKey raw) target oldkeys } return $ return mempty referenceTitle :: Parser [Char] ParserState String @@ -1405,7 +1405,7 @@ referenceLink constructor (lab, raw) = do raw' <- try (optional (char ' ') >> optional (newline >> skipSpaces) >> (snd <$> reference)) <|> return "" - let key = toKey' $ if raw' == "[]" || raw' == "" then raw else raw' + let key = toKey $ if raw' == "[]" || raw' == "" then raw else raw' let dropRB (']':xs) = xs dropRB xs = xs let dropLB ('[':xs) = xs @@ -1413,7 +1413,7 @@ referenceLink constructor (lab, raw) = do let dropBrackets = reverse . dropRB . reverse . dropLB fallback <- parseFromString (mconcat <$> many inline) $ dropBrackets raw return $ do - keys <- asks stateKeys' + keys <- asks stateKeys case M.lookup key keys of Nothing -> (\x -> B.str "[" <> x <> B.str "]" <> B.str raw') <$> fallback Just (src,tit) -> constructor src tit <$> lab diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 39a04d286..6bbb2fbd2 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -670,26 +670,31 @@ targetURI = do imageKey :: Parser [Char] ParserState (Key, Target) imageKey = try $ do string ".. |" - ref <- manyTill inline (char '|') + (_,ref) <- withRaw (manyTill inline (char '|')) skipSpaces string "image::" src <- targetURI - return (toKey (normalizeSpaces ref), (src, "")) + return (toKey $ init ref, (src, "")) anonymousKey :: Parser [Char] st (Key, Target) anonymousKey = try $ do oneOfStrings [".. __:", "__"] src <- targetURI pos <- getPosition - return (toKey [Str $ "_" ++ printf "%09d" (sourceLine pos)], (src, "")) + return (toKey $ "_" ++ printf "%09d" (sourceLine pos), (src, "")) + +stripTicks :: String -> String +stripTicks = reverse . stripTick . reverse . stripTick + where stripTick ('`':xs) = xs + stripTick xs = xs regularKey :: Parser [Char] ParserState (Key, Target) regularKey = try $ do string ".. _" - ref <- referenceName + (_,ref) <- withRaw referenceName char ':' src <- targetURI - return (toKey (normalizeSpaces ref), (src, "")) + return (toKey $ stripTicks ref, (src, "")) -- -- tables @@ -921,19 +926,19 @@ explicitLink = try $ do referenceLink :: Parser [Char] ParserState Inline referenceLink = try $ do - label' <- (quotedReferenceName <|> simpleReferenceName) >>~ char '_' + (label',ref) <- withRaw (quotedReferenceName <|> simpleReferenceName) >>~ + char '_' state <- getState let keyTable = stateKeys state - let isAnonKey x = case fromKey x of - [Str ('_':_)] -> True - _ -> False - key <- option (toKey label') $ + let isAnonKey (Key ('_':_)) = True + isAnonKey _ = False + key <- option (toKey $ stripTicks ref) $ do char '_' let anonKeys = sort $ filter isAnonKey $ M.keys keyTable if null anonKeys then mzero else return (head anonKeys) - (src,tit) <- case lookupKeySrc keyTable key of + (src,tit) <- case M.lookup key keyTable of Nothing -> fail "no corresponding key" Just target -> return target -- if anonymous link, remove key so it won't be used again @@ -957,13 +962,13 @@ autoLink = autoURI <|> autoEmail image :: Parser [Char] ParserState Inline image = try $ do char '|' - ref <- manyTill inline (char '|') + (alt,ref) <- withRaw (manyTill inline (char '|')) state <- getState let keyTable = stateKeys state - (src,tit) <- case lookupKeySrc keyTable (toKey ref) of + (src,tit) <- case M.lookup (toKey $ init ref) keyTable of Nothing -> fail "no corresponding key" Just target -> return target - return $ Image (normalizeSpaces ref) (src, tit) + return $ Image (normalizeSpaces alt) (src, tit) note :: Parser [Char] ParserState Inline note = try $ do -- cgit v1.2.3