From bd2bd9b19d949f59a64358f756bf8b398a13db0f Mon Sep 17 00:00:00 2001 From: Amogh Rathore Date: Tue, 5 Nov 2019 01:42:30 +0900 Subject: HTML Reader/Writer - Add support for and (#5861) Closes #5799 --- src/Text/Pandoc/Readers/HTML.hs | 12 +++++++----- src/Text/Pandoc/Writers/HTML.hs | 21 +++++++++++++++------ 2 files changed, 22 insertions(+), 11 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 1ed61591b..c5abe0e15 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -652,7 +652,7 @@ inline = choice , pLink , pImage , pCode - , pSamp + , pCodeWithClass [(T.pack "samp","sample"),(T.pack "var","variable")] , pSpan , pMath False , pScriptMath @@ -782,12 +782,14 @@ pImage = do let kvs = concatMap getAtt ["width", "height", "sizes", "srcset"] return $ B.imageWith (uid, cls, kvs) (escapeURI url) title (B.text alt) -pSamp :: PandocMonad m => TagParser m Inlines -pSamp = try $ do - TagOpen open attr' <- pSatisfy $ tagOpen (=="samp") (const True) +pCodeWithClass :: PandocMonad m => [(T.Text,String)] -> TagParser m Inlines +pCodeWithClass elemToClass = try $ do + let tagTest = flip elem . fmap fst $ elemToClass + TagOpen open attr' <- pSatisfy $ tagOpen tagTest (const True) result <- manyTill pAny (pCloses open) let (ids,cs,kvs) = mkAttr . toStringAttr $ attr' - return . B.codeWith (ids,"sample":cs,kvs) . + cs' = maybe cs (:cs) . lookup open $ elemToClass + return . B.codeWith (ids,cs',kvs) . unwords . lines . T.unpack . innerText $ result pCode :: PandocMonad m => TagParser m Inlines diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 86dcb5a43..783aaa8fd 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -31,7 +31,7 @@ module Text.Pandoc.Writers.HTML ( ) where import Control.Monad.State.Strict import Data.Char (ord, toLower) -import Data.List (intercalate, intersperse, isPrefixOf, partition) +import Data.List (intercalate, intersperse, isPrefixOf, partition, delete) import Data.List.Split (splitWhen) import Data.Maybe (fromMaybe, isJust, isNothing, mapMaybe) import qualified Data.Set as Set @@ -1023,20 +1023,29 @@ inlineToHtml opts inline = do (Emph lst) -> inlineListToHtml opts lst >>= return . H.em (Strong lst) -> inlineListToHtml opts lst >>= return . H.strong - (Code attr str) -> case hlCode of + (Code attr@(ids,cs,kvs) str) + -> case hlCode of Left msg -> do unless (null msg) $ report $ CouldNotHighlight msg - addAttrs opts attr $ H.code $ strToHtml str + addAttrs opts (ids,cs',kvs) $ + maybe H.code id sampOrVar $ + strToHtml str Right h -> do modify $ \st -> st{ stHighlighting = True } - addAttrs opts (id',[],keyvals) h - where (id',_,keyvals) = attr - hlCode = if isJust (writerHighlightStyle opts) + addAttrs opts (ids,[],kvs) $ + maybe id id sampOrVar $ h + where hlCode = if isJust (writerHighlightStyle opts) then highlight (writerSyntaxMap opts) formatHtmlInline attr str else Left "" + (sampOrVar,cs') = + if "sample" `elem` cs + then (Just H.samp,"sample" `delete` cs) + else if "variable" `elem` cs + then (Just H.var,"variable" `delete` cs) + else (Nothing,cs) (Strikeout lst) -> inlineListToHtml opts lst >>= return . H.del (SmallCaps lst) -> inlineListToHtml opts lst >>= -- cgit v1.2.3