aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-05-29 12:01:12 -0400
committerGitHub <noreply@github.com>2019-05-29 12:01:12 -0400
commit1de7b20ebbb198362ec0b4717f72d275fb34dd9c (patch)
tree69bd3f6a022e48b8ef459121cfb33b44611a7e44 /src/Text/Pandoc
parent970b820f4762096642ea9fdf2ed8c637998b26f8 (diff)
parenta58304e00edc3c7d78c352c379e843cb908e6887 (diff)
downloadpandoc-1de7b20ebbb198362ec0b4717f72d275fb34dd9c.tar.gz
Merge pull request #5497 from mb21/html-writer-video-audio
Output HTML5 video and audio elements
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/MIME.hs19
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs52
2 files changed, 37 insertions, 34 deletions
diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs
index 19488c9bc..ee0fe3efb 100644
--- a/src/Text/Pandoc/MIME.hs
+++ b/src/Text/Pandoc/MIME.hs
@@ -11,12 +11,13 @@
Mime type lookup for ODT writer.
-}
module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef,
- extensionFromMimeType )where
+ extensionFromMimeType, mediaCategory ) where
import Prelude
import Data.Char (toLower)
import Data.List (isPrefixOf, isSuffixOf)
+import Data.List.Split (splitOn)
import qualified Data.Map as M
-import Data.Maybe (fromMaybe)
+import Data.Maybe (fromMaybe, listToMaybe)
import System.FilePath
type MimeType = String
@@ -42,15 +43,25 @@ extensionFromMimeType mimetype =
M.lookup (takeWhile (/=';') mimetype) reverseMimeTypes
-- note: we just look up the basic mime type, dropping the content-encoding etc.
+-- | Determine general media category for file path, e.g.
+--
+-- prop> mediaCategory "foo.jpg" = Just "image"
+mediaCategory :: FilePath -> Maybe String
+mediaCategory fp = getMimeType fp >>= listToMaybe . splitOn "/"
+
reverseMimeTypes :: M.Map MimeType String
reverseMimeTypes = M.fromList $ map (\(k,v) -> (v,k)) mimeTypesList
mimeTypes :: M.Map String MimeType
mimeTypes = M.fromList mimeTypesList
+-- | Collection of common mime types.
+-- Except for first entry, list borrowed from
+-- <https://github.com/Happstack/happstack-server/blob/master/src/Happstack/Server/FileServe/BuildingBlocks.hs happstack-server>
mimeTypesList :: [(String, MimeType)]
-mimeTypesList = -- List borrowed from happstack-server.
- [("gz","application/x-gzip")
+mimeTypesList =
+ [("cpt","image/x-corelphotopaint")
+ ,("gz","application/x-gzip")
,("cabal","application/x-cabal")
,("%","application/x-trash")
,("323","text/h323")
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 5004f4111..ca44583ab 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -65,18 +65,21 @@ import Text.Blaze.Internal (preEscapedString, preEscapedText)
#endif
#if MIN_VERSION_blaze_html(0,5,1)
import qualified Text.Blaze.XHtml5 as H5
+import qualified Text.Blaze.XHtml5.Attributes as A5
#else
import qualified Text.Blaze.Html5 as H5
+import qualified Text.Blaze.Html5.Attributes as A5
#endif
import Control.Monad.Except (throwError)
import Data.Aeson (Value)
-import System.FilePath (takeBaseName, takeExtension)
+import System.FilePath (takeBaseName)
import Text.Blaze.Html.Renderer.Text (renderHtml)
import qualified Text.Blaze.XHtml1.Transitional as H
import qualified Text.Blaze.XHtml1.Transitional.Attributes as A
import Text.Pandoc.Class (PandocMonad, report, runPure)
import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.Pandoc.MIME (mediaCategory)
import Text.TeXMath
import Text.XML.Light (elChildren, unode, unqual)
import qualified Text.XML.Light as XML
@@ -665,18 +668,6 @@ dimensionsToAttrList attr = consolidateStyles $ go Width ++ go Height
(Just x) -> [("style", show dir ++ ":" ++ show x)]
Nothing -> []
-imageExts :: [String]
-imageExts = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf",
- "gif", "ico", "ief", "jng", "jpg", "jpeg", "nef", "orf", "pat", "pbm",
- "pcx", "pgm", "png", "pnm", "ppm", "psd", "ras", "rgb", "svg", "tiff",
- "wbmp", "xbm", "xpm", "xwd" ]
-
-treatAsImage :: FilePath -> Bool
-treatAsImage fp =
- let path = maybe fp uriPath (parseURIReference fp)
- ext = map toLower $ drop 1 $ takeExtension path
- in null ext || ext `elem` imageExts
-
figure :: PandocMonad m
=> WriterOptions -> Attr -> [Inline] -> (String, String)
-> StateT WriterState m Html
@@ -1135,8 +1126,8 @@ inlineToHtml opts inline = do
return $ if null tit
then link'
else link' ! A.title (toValue tit)
- (Image attr txt (s,tit)) | treatAsImage s -> do
- let alternate' = stringify txt
+ (Image attr txt (s,tit)) -> do
+ let alternate = stringify txt
slideVariant <- gets stSlideVariant
let isReveal = slideVariant == RevealJsSlides
attrs <- imgAttrsToHtml opts attr
@@ -1146,22 +1137,23 @@ inlineToHtml opts inline = do
then customAttribute "data-src" $ toValue s
else A.src $ toValue s) :
[A.title $ toValue tit | not (null tit)] ++
- [A.alt $ toValue alternate' | not (null txt)] ++
- attrs
- let tag = if html5 then H5.img else H.img
- return $ foldl (!) tag attributes
- -- note: null title included, as in Markdown.pl
- (Image attr _ (s,tit)) -> do
- slideVariant <- gets stSlideVariant
- let isReveal = slideVariant == RevealJsSlides
- attrs <- imgAttrsToHtml opts attr
- let attributes =
- (if isReveal
- then customAttribute "data-src" $ toValue s
- else A.src $ toValue s) :
- [A.title $ toValue tit | not (null tit)] ++
attrs
- return $ foldl (!) H5.embed attributes
+ imageTag = (if html5 then H5.img else H.img
+ , [A.alt $ toValue alternate | not (null txt)] )
+ mediaTag tg fallbackTxt =
+ let linkTxt = if null txt
+ then fallbackTxt
+ else alternate
+ in (tg $ H.a ! A.href (toValue s) $ toHtml linkTxt
+ , [A5.controls ""] )
+ normSrc = maybe s uriPath (parseURIReference s)
+ (tag, specAttrs) = case mediaCategory normSrc of
+ Just "image" -> imageTag
+ Just "video" -> mediaTag H5.video "Video"
+ Just "audio" -> mediaTag H5.audio "Audio"
+ Just _ -> (H5.embed, [])
+ _ -> imageTag
+ return $ foldl (!) tag $ attributes ++ specAttrs
-- note: null title included, as in Markdown.pl
(Note contents) -> do
notes <- gets stNotes