aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-07-19 11:24:54 -0700
committerGitHub <noreply@github.com>2020-07-19 11:24:54 -0700
commit8ede05161ffe0e57c330e34965d8d0b8e100d328 (patch)
tree1892bef22bd9ce2352350caa5eaefbe23ef39c41 /src/Text
parent89b8624269e2419d4c9dbd399fce2370054c6921 (diff)
parentb894de64264fe0386b5cb3e1680955a8e879c78e (diff)
downloadpandoc-8ede05161ffe0e57c330e34965d8d0b8e100d328.tar.gz
Merge pull request #6495 from tarleb/html5-figure-accessiblity
HTML writer: improve alt-text/caption handling for HTML5
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs12
1 files changed, 10 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 11daaf06b..4bfd95674 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.HTML
@@ -587,11 +588,18 @@ figure :: PandocMonad m
=> WriterOptions -> Attr -> [Inline] -> (Text, Text)
-> StateT WriterState m Html
figure opts attr txt (s,tit) = do
- img <- inlineToHtml opts (Image attr [Str ""] (s,tit))
html5 <- gets stHtml5
+ -- Screen-readers will normally read the @alt@ text and the figure; we
+ -- want to avoid them reading the same text twice. With HTML5 we can
+ -- use aria-hidden for the caption; with HTML4, we use an empty
+ -- alt-text instead.
+ let alt = if html5 then txt else [Str ""]
let tocapt = if html5
- then H5.figcaption
+ then H5.figcaption !
+ H5.customAttribute (textTag "aria-hidden")
+ (toValue @Text "true")
else H.p ! A.class_ "caption"
+ img <- inlineToHtml opts (Image attr alt (s,tit))
capt <- if null txt
then return mempty
else tocapt `fmap` inlineListToHtml opts txt