aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs2
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs13
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs7
3 files changed, 15 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3b321cc19..bbca7f858 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -297,7 +297,7 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do
<> brackets (text ref)
inlineToConTeXt (Link txt (src, _)) = do
- let isAutolink = txt == [Str src]
+ let isAutolink = txt == [Str (unEscapeString src)]
st <- get
let next = stNextRef st
put $ st {stNextRef = next + 1}
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 36ce2ba21..9ead604d7 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -40,7 +40,7 @@ import Text.Pandoc.Slides
import Text.Pandoc.Highlighting ( highlight, styleToCss,
formatHtmlInline, formatHtmlBlock )
import Text.Pandoc.XML (fromEntities, escapeStringForXML)
-import Network.URI ( parseURIReference, URI(..) )
+import Network.URI ( parseURIReference, URI(..), unEscapeString )
import Network.HTTP ( urlEncode )
import Numeric ( showHex )
import Data.Char ( ord, toLower )
@@ -361,13 +361,13 @@ obfuscateLink opts txt s =
ReferenceObfuscation ->
-- need to use preEscapedString or &'s are escaped to &amp; in URL
preEscapedString $ "<a href=\"" ++ (obfuscateString s')
- ++ "\">" ++ (obfuscateString txt) ++ "</a>"
+ ++ "\" class=\"email\">" ++ (obfuscateString txt) ++ "</a>"
JavascriptObfuscation ->
(H.script ! A.type_ "text/javascript" $
preEscapedString ("\n<!--\nh='" ++
obfuscateString domain ++ "';a='" ++ at' ++ "';n='" ++
obfuscateString name' ++ "';e=n+a+h;\n" ++
- "document.write('<a h'+'ref'+'=\"ma'+'ilto'+':'+e+'\">'+" ++
+ "document.write('<a h'+'ref'+'=\"ma'+'ilto'+':'+e+'\" clas'+'s=\"em' + 'ail\">'+" ++
linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) >>
H.noscript (preEscapedString $ obfuscateString altText)
_ -> error $ "Unknown obfuscation method: " ++ show meth
@@ -739,9 +739,12 @@ inlineToHtml opts inline =
RevealJsSlides -> '#':'/':xs
_ -> s
let link = H.a ! A.href (toValue s') $ linkText
+ let link' = if txt == [Str (unEscapeString s)]
+ then link ! A.class_ "uri"
+ else link
return $ if null tit
- then link
- else link ! A.title (toValue tit)
+ then link'
+ else link' ! A.title (toValue tit)
(Image txt (s,tit)) | treatAsImage s -> do
let alternate' = stringify txt
let attributes = [A.src $ toValue s] ++
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 2fa790e14..d200ecee1 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -793,12 +793,17 @@ inlineToLaTeX (Note contents) = do
(CodeBlock _ _ : _) -> cr
_ -> empty
let noteContents = nest 2 contents' <> optnl
+ opts <- gets stOptions
+ -- in beamer slides, display footnote from current overlay forward
+ let beamerMark = if writerBeamer opts
+ then text "<.->"
+ else empty
modify $ \st -> st{ stNotes = noteContents : stNotes st }
return $
if inMinipage
then "\\footnotemark{}"
-- note: a \n before } needed when note ends with a Verbatim environment
- else "\\footnote" <> braces noteContents
+ else "\\footnote" <> beamerMark <> braces noteContents
protectCode :: [Inline] -> [Inline]
protectCode [] = []