aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Parsing.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Parsing.hs')
-rw-r--r--src/Text/Pandoc/Parsing.hs20
1 files changed, 17 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index d2eaaf0d1..85786eb3e 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -164,7 +164,8 @@ module Text.Pandoc.Parsing ( anyLine,
setSourceLine,
newPos,
addWarning,
- (<+?>)
+ (<+?>),
+ extractIdClass
)
where
@@ -185,6 +186,7 @@ import Text.TeXMath.Readers.TeX.Macros (applyMacros, Macro,
parseMacroDefinitions)
import Text.Pandoc.Compat.TagSoupEntity ( lookupEntity )
import Text.Pandoc.Asciify (toAsciiChar)
+import Text.Pandoc.Compat.Monoid ((<>))
import Data.Default
import qualified Data.Set as Set
import Control.Monad.Reader
@@ -1065,7 +1067,7 @@ toKey = Key . map toLower . unwords . words . unbracket
where unbracket ('[':xs) | "]" `isSuffixOf` xs = take (length xs - 1) xs
unbracket xs = xs
-type KeyTable = M.Map Key Target
+type KeyTable = M.Map Key (Target, Attr)
type SubstTable = M.Map Key Inlines
@@ -1210,7 +1212,8 @@ citeKey = try $ do
firstChar <- alphaNum <|> char '_' <|> char '*' -- @* for wildcard in nocite
let regchar = satisfy (\c -> isAlphaNum c || c == '_')
let internal p = try $ p <* lookAhead regchar
- rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/")
+ rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/") <|>
+ try (oneOf ":/" <* lookAhead (char '/'))
let key = firstChar:rest
return (suppress_author, key)
@@ -1262,3 +1265,14 @@ addWarning mbpos msg =
infixr 5 <+?>
(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)
+
+extractIdClass :: Attr -> Attr
+extractIdClass (ident, cls, kvs) = (ident', cls', kvs')
+ where
+ ident' = case (lookup "id" kvs) of
+ Just v -> v
+ Nothing -> ident
+ cls' = case (lookup "class" kvs) of
+ Just cl -> words cl
+ Nothing -> cls
+ kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs