Parsing: Add extractIdClass, modified type of KeyTable.

(mb21)
This commit is contained in:
John MacFarlane 2015-04-02 21:04:12 -07:00 committed by mb21
parent 878ab00233
commit 76f0708ef5

View file

@ -164,7 +164,8 @@ module Text.Pandoc.Parsing ( anyLine,
setSourceLine,
newPos,
addWarning,
(<+?>)
(<+?>),
extractIdClass
)
where
@ -1067,7 +1068,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
@ -1264,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