2012-05-10 09:13:14 -07:00
|
|
|
|
{-# LANGUAGE OverloadedStrings, CPP #-}
|
2008-08-01 21:00:50 +00:00
|
|
|
|
{-# OPTIONS_GHC -fno-warn-deprecations #-}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
{-
|
2010-03-23 13:31:09 -07:00
|
|
|
|
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
{- |
|
2011-04-16 10:37:47 -07:00
|
|
|
|
Module : Text.Pandoc.Writers.HTML
|
2010-03-23 13:31:09 -07:00
|
|
|
|
Copyright : Copyright (C) 2006-2010 John MacFarlane
|
2011-04-16 10:37:47 -07:00
|
|
|
|
License : GNU GPL, version 2 or above
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
|
Stability : alpha
|
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' documents to HTML.
|
|
|
|
|
-}
|
|
|
|
|
module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where
|
|
|
|
|
import Text.Pandoc.Definition
|
|
|
|
|
import Text.Pandoc.Shared
|
2013-07-01 20:47:26 -07:00
|
|
|
|
import Text.Pandoc.Writers.Shared
|
2012-07-26 22:59:56 -07:00
|
|
|
|
import Text.Pandoc.Options
|
2009-12-31 01:08:46 +00:00
|
|
|
|
import Text.Pandoc.Templates
|
2007-12-02 00:36:32 +00:00
|
|
|
|
import Text.Pandoc.Readers.TeXMath
|
2012-01-24 10:15:41 -08:00
|
|
|
|
import Text.Pandoc.Slides
|
2012-01-25 11:29:42 -08:00
|
|
|
|
import Text.Pandoc.Highlighting ( highlight, styleToCss,
|
2011-12-26 22:49:50 -08:00
|
|
|
|
formatHtmlInline, formatHtmlBlock )
|
2013-09-12 09:24:25 -07:00
|
|
|
|
import Text.Pandoc.XML (fromEntities, escapeStringForXML)
|
2010-07-15 19:01:00 -07:00
|
|
|
|
import Network.HTTP ( urlEncode )
|
2007-11-03 23:27:58 +00:00
|
|
|
|
import Numeric ( showHex )
|
2009-04-25 00:29:58 +00:00
|
|
|
|
import Data.Char ( ord, toLower )
|
2009-12-31 01:15:42 +00:00
|
|
|
|
import Data.List ( isPrefixOf, intersperse )
|
2011-12-15 21:17:32 -08:00
|
|
|
|
import Data.String ( fromString )
|
2009-04-25 00:29:58 +00:00
|
|
|
|
import Data.Maybe ( catMaybes )
|
2007-11-03 23:27:58 +00:00
|
|
|
|
import Control.Monad.State
|
2012-04-23 19:53:04 +10:00
|
|
|
|
import Text.Blaze.Html hiding(contents)
|
|
|
|
|
import Text.Blaze.Internal(preEscapedString)
|
2012-11-02 21:04:32 -07:00
|
|
|
|
#if MIN_VERSION_blaze_html(0,5,1)
|
2012-11-02 20:59:45 -07:00
|
|
|
|
import qualified Text.Blaze.XHtml5 as H5
|
2012-11-02 21:04:32 -07:00
|
|
|
|
#else
|
|
|
|
|
import qualified Text.Blaze.Html5 as H5
|
|
|
|
|
#endif
|
2011-12-20 11:25:26 -08:00
|
|
|
|
import qualified Text.Blaze.XHtml1.Transitional as H
|
|
|
|
|
import qualified Text.Blaze.XHtml1.Transitional.Attributes as A
|
2011-12-15 21:17:32 -08:00
|
|
|
|
import Text.Blaze.Renderer.String (renderHtml)
|
2010-03-18 06:45:56 +00:00
|
|
|
|
import Text.TeXMath
|
|
|
|
|
import Text.XML.Light.Output
|
2011-07-16 10:11:04 -07:00
|
|
|
|
import System.FilePath (takeExtension)
|
2012-09-28 11:11:31 -04:00
|
|
|
|
import Data.Monoid
|
2013-05-10 22:53:35 -07:00
|
|
|
|
import Data.Aeson (Value)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
data WriterState = WriterState
|
2009-12-31 01:13:26 +00:00
|
|
|
|
{ stNotes :: [Html] -- ^ List of notes
|
|
|
|
|
, stMath :: Bool -- ^ Math is used in document
|
2012-03-03 08:27:44 -08:00
|
|
|
|
, stQuotes :: Bool -- ^ <q> tag is used
|
2009-12-31 01:13:26 +00:00
|
|
|
|
, stHighlighting :: Bool -- ^ Syntax highlighting is used
|
|
|
|
|
, stSecNum :: [Int] -- ^ Number of current section
|
2011-12-15 21:17:32 -08:00
|
|
|
|
}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
defaultWriterState :: WriterState
|
2012-03-03 08:27:44 -08:00
|
|
|
|
defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,
|
|
|
|
|
stHighlighting = False, stSecNum = []}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- Helpers to render HTML with the appropriate function.
|
2008-07-13 17:08:55 +00:00
|
|
|
|
|
2011-12-15 21:17:32 -08:00
|
|
|
|
strToHtml :: String -> Html
|
2012-09-28 11:11:31 -04:00
|
|
|
|
strToHtml ('\'':xs) = preEscapedString "\'" `mappend` strToHtml xs
|
|
|
|
|
strToHtml xs@(_:_) = case break (=='\'') xs of
|
|
|
|
|
(_ ,[]) -> toHtml xs
|
|
|
|
|
(ys,zs) -> toHtml ys `mappend` strToHtml zs
|
|
|
|
|
strToHtml [] = ""
|
2008-07-27 03:54:07 +00:00
|
|
|
|
|
2011-02-03 17:30:38 -08:00
|
|
|
|
-- | Hard linebreak.
|
2011-02-04 19:27:53 -08:00
|
|
|
|
nl :: WriterOptions -> Html
|
|
|
|
|
nl opts = if writerWrapText opts
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then preEscapedString "\n"
|
|
|
|
|
else mempty
|
2011-02-03 17:30:38 -08:00
|
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- | Convert Pandoc document to Html string.
|
|
|
|
|
writeHtmlString :: WriterOptions -> Pandoc -> String
|
2009-12-31 01:13:26 +00:00
|
|
|
|
writeHtmlString opts d =
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let (body, context) = evalState (pandocToHtml opts d) defaultWriterState
|
2009-12-31 01:13:26 +00:00
|
|
|
|
in if writerStandalone opts
|
2013-05-10 22:53:35 -07:00
|
|
|
|
then inTemplate opts context body
|
|
|
|
|
else renderHtml body
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert Pandoc document to Html structure.
|
|
|
|
|
writeHtml :: WriterOptions -> Pandoc -> Html
|
2009-12-31 01:13:26 +00:00
|
|
|
|
writeHtml opts d =
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let (body, context) = evalState (pandocToHtml opts d) defaultWriterState
|
2009-12-31 01:13:26 +00:00
|
|
|
|
in if writerStandalone opts
|
2013-05-10 22:53:35 -07:00
|
|
|
|
then inTemplate opts context body
|
|
|
|
|
else body
|
2009-12-31 01:13:26 +00:00
|
|
|
|
|
|
|
|
|
-- result is (title, authors, date, toc, body, new variables)
|
|
|
|
|
pandocToHtml :: WriterOptions
|
|
|
|
|
-> Pandoc
|
2013-05-10 22:53:35 -07:00
|
|
|
|
-> State WriterState (Html, Value)
|
|
|
|
|
pandocToHtml opts (Pandoc meta blocks) = do
|
2013-07-01 20:47:26 -07:00
|
|
|
|
metadata <- metaToJSON opts
|
2013-05-10 22:53:35 -07:00
|
|
|
|
(fmap renderHtml . blockListToHtml opts)
|
|
|
|
|
(fmap renderHtml . inlineListToHtml opts)
|
|
|
|
|
meta
|
2013-09-12 09:24:25 -07:00
|
|
|
|
let stringifyHTML = escapeStringForXML . stringify
|
|
|
|
|
let authsMeta = map stringifyHTML $ docAuthors meta
|
|
|
|
|
let dateMeta = stringifyHTML $ docDate meta
|
2012-01-25 17:50:03 -08:00
|
|
|
|
let slideLevel = maybe (getSlideLevel blocks) id $ writerSlideLevel opts
|
2011-04-16 12:16:24 -07:00
|
|
|
|
let sects = hierarchicalize $
|
|
|
|
|
if writerSlideVariant opts == NoSlides
|
|
|
|
|
then blocks
|
2012-01-24 10:15:41 -08:00
|
|
|
|
else prepSlides slideLevel blocks
|
2011-04-13 18:36:21 -07:00
|
|
|
|
toc <- if writerTableOfContents opts
|
|
|
|
|
then tableOfContents opts sects
|
|
|
|
|
else return Nothing
|
2011-12-15 21:17:32 -08:00
|
|
|
|
blocks' <- liftM (mconcat . intersperse (nl opts)) $
|
2012-01-24 10:15:41 -08:00
|
|
|
|
mapM (elementToHtml slideLevel opts) sects
|
2009-12-31 01:13:26 +00:00
|
|
|
|
st <- get
|
|
|
|
|
let notes = reverse (stNotes st)
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let thebody = blocks' >> footnoteSection opts notes
|
2009-12-31 01:13:26 +00:00
|
|
|
|
let math = if stMath st
|
|
|
|
|
then case writerHTMLMathMethod opts of
|
|
|
|
|
LaTeXMathML (Just url) ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.script ! A.src (toValue url)
|
|
|
|
|
! A.type_ "text/javascript"
|
|
|
|
|
$ mempty
|
2010-03-18 06:45:56 +00:00
|
|
|
|
MathML (Just url) ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.script ! A.src (toValue url)
|
|
|
|
|
! A.type_ "text/javascript"
|
|
|
|
|
$ mempty
|
2010-10-26 21:06:51 -07:00
|
|
|
|
MathJax url ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.script ! A.src (toValue url)
|
|
|
|
|
! A.type_ "text/javascript"
|
2013-10-13 11:31:33 -07:00
|
|
|
|
$ case writerSlideVariant opts of
|
|
|
|
|
SlideousSlides ->
|
|
|
|
|
preEscapedString
|
|
|
|
|
"MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
|
|
|
|
|
_ -> mempty
|
2009-12-31 01:13:26 +00:00
|
|
|
|
JsMath (Just url) ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.script ! A.src (toValue url)
|
|
|
|
|
! A.type_ "text/javascript"
|
|
|
|
|
$ mempty
|
2010-03-18 06:45:56 +00:00
|
|
|
|
_ -> case lookup "mathml-script" (writerVariables opts) of
|
2012-01-31 10:47:48 -08:00
|
|
|
|
Just s | not (writerHtml5 opts) ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.script ! A.type_ "text/javascript"
|
|
|
|
|
$ preEscapedString
|
|
|
|
|
("/*<![CDATA[*/\n" ++ s ++ "/*]]>*/\n")
|
2012-01-31 10:47:48 -08:00
|
|
|
|
| otherwise -> mempty
|
2011-12-15 21:17:32 -08:00
|
|
|
|
Nothing -> mempty
|
|
|
|
|
else mempty
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let context = (if stHighlighting st
|
2013-06-27 22:42:55 -07:00
|
|
|
|
then defField "highlighting-css"
|
2013-05-10 22:53:35 -07:00
|
|
|
|
(styleToCss $ writerHighlightStyle opts)
|
|
|
|
|
else id) $
|
|
|
|
|
(if stMath st
|
2013-06-27 22:42:55 -07:00
|
|
|
|
then defField "math" (renderHtml math)
|
2013-05-10 22:53:35 -07:00
|
|
|
|
else id) $
|
2013-06-27 22:42:55 -07:00
|
|
|
|
defField "quotes" (stQuotes st) $
|
|
|
|
|
maybe id (defField "toc" . renderHtml) toc $
|
|
|
|
|
defField "author-meta" authsMeta $
|
|
|
|
|
maybe id (defField "date-meta") (normalizeDate dateMeta) $
|
2013-09-12 09:24:25 -07:00
|
|
|
|
defField "pagetitle" (stringifyHTML $ docTitle meta) $
|
2013-06-27 22:42:55 -07:00
|
|
|
|
defField "idprefix" (writerIdentifierPrefix opts) $
|
2013-05-10 22:53:35 -07:00
|
|
|
|
-- these should maybe be set in pandoc.hs
|
2013-06-27 22:42:55 -07:00
|
|
|
|
defField "slidy-url"
|
2013-05-10 22:53:35 -07:00
|
|
|
|
("http://www.w3.org/Talks/Tools/Slidy2" :: String) $
|
2013-06-27 22:42:55 -07:00
|
|
|
|
defField "slideous-url" ("slideous" :: String) $
|
|
|
|
|
defField "revealjs-url" ("reveal.js" :: String) $
|
|
|
|
|
defField "s5-url" ("s5/default" :: String) $
|
|
|
|
|
defField "html5" (writerHtml5 opts) $
|
2013-06-29 22:14:01 -07:00
|
|
|
|
metadata
|
2013-05-10 22:53:35 -07:00
|
|
|
|
return (thebody, context)
|
2009-12-31 01:13:26 +00:00
|
|
|
|
|
2009-12-31 01:14:35 +00:00
|
|
|
|
inTemplate :: TemplateTarget a
|
|
|
|
|
=> WriterOptions
|
2013-05-10 22:53:35 -07:00
|
|
|
|
-> Value
|
2009-12-31 01:13:26 +00:00
|
|
|
|
-> Html
|
2009-12-31 01:14:35 +00:00
|
|
|
|
-> a
|
2013-05-10 22:53:35 -07:00
|
|
|
|
inTemplate opts context body = renderTemplate' (writerTemplate opts)
|
2013-06-27 22:42:55 -07:00
|
|
|
|
$ defField "body" (renderHtml body) context
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2009-12-05 17:56:02 +00:00
|
|
|
|
-- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix
|
2011-12-15 21:17:32 -08:00
|
|
|
|
prefixedId :: WriterOptions -> String -> Attribute
|
2012-10-29 22:45:52 -07:00
|
|
|
|
prefixedId opts s =
|
|
|
|
|
case s of
|
|
|
|
|
"" -> mempty
|
|
|
|
|
_ -> A.id $ toValue $ writerIdentifierPrefix opts ++ s
|
2009-12-05 17:56:02 +00:00
|
|
|
|
|
2013-03-20 16:59:47 -04:00
|
|
|
|
toList :: (Html -> Html) -> WriterOptions -> ([Html] -> Html)
|
|
|
|
|
toList listop opts items = do
|
|
|
|
|
if (writerIncremental opts)
|
|
|
|
|
then if (writerSlideVariant opts /= RevealJsSlides)
|
2013-03-21 15:21:53 -07:00
|
|
|
|
then (listop $ mconcat items) ! A.class_ "incremental"
|
|
|
|
|
else listop $ mconcat $ map (! A.class_ "fragment") items
|
|
|
|
|
else listop $ mconcat items
|
2011-02-04 19:27:53 -08:00
|
|
|
|
|
2013-03-20 16:59:47 -04:00
|
|
|
|
unordList :: WriterOptions -> [Html] -> Html
|
2013-03-21 15:21:53 -07:00
|
|
|
|
unordList opts = toList H.ul opts . toListItems opts
|
2013-03-20 16:59:47 -04:00
|
|
|
|
|
|
|
|
|
ordList :: WriterOptions -> [Html] -> Html
|
2013-03-21 15:21:53 -07:00
|
|
|
|
ordList opts = toList H.ol opts . toListItems opts
|
|
|
|
|
|
|
|
|
|
defList :: WriterOptions -> [Html] -> Html
|
|
|
|
|
defList opts items = toList H.dl opts (items ++ [nl opts])
|
2011-02-04 19:27:53 -08:00
|
|
|
|
|
2009-04-25 00:29:58 +00:00
|
|
|
|
-- | Construct table of contents from list of elements.
|
2010-03-20 17:14:18 +00:00
|
|
|
|
tableOfContents :: WriterOptions -> [Element] -> State WriterState (Maybe Html)
|
|
|
|
|
tableOfContents _ [] = return Nothing
|
2009-04-25 00:29:58 +00:00
|
|
|
|
tableOfContents opts sects = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let opts' = opts { writerIgnoreNotes = True }
|
2009-04-25 00:29:58 +00:00
|
|
|
|
contents <- mapM (elementToListItem opts') sects
|
2010-01-09 03:13:08 +00:00
|
|
|
|
let tocList = catMaybes contents
|
2010-03-20 17:14:18 +00:00
|
|
|
|
return $ if null tocList
|
|
|
|
|
then Nothing
|
2011-07-23 12:04:31 -07:00
|
|
|
|
else Just $ unordList opts tocList
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2009-12-09 04:58:29 +00:00
|
|
|
|
-- | Convert section number to string
|
|
|
|
|
showSecNum :: [Int] -> String
|
|
|
|
|
showSecNum = concat . intersperse "." . map show
|
2009-12-08 02:36:16 +00:00
|
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- | Converts an Element to a list item for a table of contents,
|
|
|
|
|
-- retrieving the appropriate identifier from state.
|
2009-04-25 00:29:58 +00:00
|
|
|
|
elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
|
2013-02-14 19:35:58 -08:00
|
|
|
|
elementToListItem opts (Sec lev num (id',classes,_) headerText subsecs)
|
2013-01-05 12:07:09 -08:00
|
|
|
|
| lev <= writerTOCDepth opts = do
|
2013-03-16 14:48:37 -07:00
|
|
|
|
let num' = zipWith (+) num (writerNumberOffset opts ++ repeat 0)
|
2013-02-14 19:35:58 -08:00
|
|
|
|
let sectnum = if writerNumberSections opts && not (null num) &&
|
|
|
|
|
"unnumbered" `notElem` classes
|
2013-02-13 08:49:48 -08:00
|
|
|
|
then (H.span ! A.class_ "toc-section-number"
|
2013-03-16 14:48:37 -07:00
|
|
|
|
$ toHtml $ showSecNum num') >> preEscapedString " "
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else mempty
|
|
|
|
|
txt <- liftM (sectnum >>) $ inlineListToHtml opts headerText
|
2009-04-25 00:29:58 +00:00
|
|
|
|
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let subList = if null subHeads
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then mempty
|
2011-02-04 19:27:53 -08:00
|
|
|
|
else unordList opts subHeads
|
2013-04-20 14:59:39 -07:00
|
|
|
|
-- in reveal.js, we need #/apples, not #apples:
|
|
|
|
|
let revealSlash = ['/' | writerSlideVariant opts == RevealJsSlides]
|
2012-10-29 22:45:52 -07:00
|
|
|
|
return $ Just
|
|
|
|
|
$ if null id'
|
|
|
|
|
then (H.a $ toHtml txt) >> subList
|
2013-04-20 14:59:39 -07:00
|
|
|
|
else (H.a ! A.href (toValue $ "#" ++ revealSlash ++
|
|
|
|
|
writerIdentifierPrefix opts ++ id')
|
2011-12-15 21:17:32 -08:00
|
|
|
|
$ toHtml txt) >> subList
|
2013-01-05 12:07:09 -08:00
|
|
|
|
elementToListItem _ _ = return Nothing
|
2009-04-25 00:29:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert an Element to Html.
|
2012-01-24 10:15:41 -08:00
|
|
|
|
elementToHtml :: Int -> WriterOptions -> Element -> State WriterState Html
|
|
|
|
|
elementToHtml _slideLevel opts (Blk block) = blockToHtml opts block
|
2013-02-12 20:13:23 -08:00
|
|
|
|
elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elements) = do
|
2012-01-24 10:51:15 -08:00
|
|
|
|
let slide = writerSlideVariant opts /= NoSlides && level <= slideLevel
|
2013-02-23 18:51:33 -08:00
|
|
|
|
let num' = zipWith (+) num (writerNumberOffset opts ++ repeat 0)
|
2013-02-22 19:15:38 -08:00
|
|
|
|
modify $ \st -> st{stSecNum = num'} -- update section number
|
2012-01-25 11:30:12 -08:00
|
|
|
|
-- always use level 1 for slide titles
|
|
|
|
|
let level' = if slide then 1 else level
|
2012-01-25 17:50:03 -08:00
|
|
|
|
let titleSlide = slide && level < slideLevel
|
2012-06-25 14:52:09 -07:00
|
|
|
|
header' <- if title' == [Str "\0"] -- marker for hrule
|
|
|
|
|
then return mempty
|
2013-02-12 21:29:17 -08:00
|
|
|
|
else blockToHtml opts (Header level' (id',classes,keyvals) title')
|
2012-01-25 17:50:03 -08:00
|
|
|
|
let isSec (Sec _ _ _ _ _) = True
|
|
|
|
|
isSec (Blk _) = False
|
2013-09-08 15:47:50 -07:00
|
|
|
|
let isPause (Blk x) = x == Para [Str ".",Space,Str ".",Space,Str "."]
|
|
|
|
|
isPause _ = False
|
|
|
|
|
let fragmentClass = case writerSlideVariant opts of
|
|
|
|
|
RevealJsSlides -> "fragment"
|
|
|
|
|
_ -> "incremental"
|
|
|
|
|
let inDiv xs = Blk (RawBlock (Format "html") ("<div class=\""
|
|
|
|
|
++ fragmentClass ++ "\">")) :
|
|
|
|
|
(xs ++ [Blk (RawBlock (Format "html") "</div>")])
|
2012-01-25 17:50:03 -08:00
|
|
|
|
innerContents <- mapM (elementToHtml slideLevel opts)
|
|
|
|
|
$ if titleSlide
|
|
|
|
|
-- title slides have no content of their own
|
|
|
|
|
then filter isSec elements
|
2013-09-08 15:47:50 -07:00
|
|
|
|
else if slide
|
|
|
|
|
then case splitBy isPause elements of
|
|
|
|
|
[] -> []
|
|
|
|
|
[x] -> x
|
|
|
|
|
xs -> concatMap inDiv xs
|
|
|
|
|
else elements
|
2012-01-24 10:15:41 -08:00
|
|
|
|
let inNl x = mconcat $ nl opts : intersperse (nl opts) x ++ [nl opts]
|
2013-02-14 19:35:58 -08:00
|
|
|
|
let classes' = ["titleslide" | titleSlide] ++ ["slide" | slide] ++
|
|
|
|
|
["section" | (slide || writerSectionDivs opts) &&
|
|
|
|
|
not (writerHtml5 opts) ] ++
|
|
|
|
|
["level" ++ show level | slide || writerSectionDivs opts ]
|
|
|
|
|
++ classes
|
2011-12-18 13:09:58 -08:00
|
|
|
|
let secttag = if writerHtml5 opts
|
2013-02-14 19:35:58 -08:00
|
|
|
|
then H5.section
|
|
|
|
|
else H.div
|
|
|
|
|
let attr = (id',classes',keyvals)
|
2012-01-24 10:15:41 -08:00
|
|
|
|
return $ if titleSlide
|
2013-03-21 15:46:47 -07:00
|
|
|
|
then (if writerSlideVariant opts == RevealJsSlides
|
|
|
|
|
then H5.section
|
|
|
|
|
else id) $ mconcat $
|
|
|
|
|
(addAttrs opts attr $ secttag $ header') : innerContents
|
2012-01-24 10:15:41 -08:00
|
|
|
|
else if writerSectionDivs opts || slide
|
2013-02-14 19:35:58 -08:00
|
|
|
|
then addAttrs opts attr
|
|
|
|
|
$ secttag $ inNl $ header' : innerContents
|
|
|
|
|
else mconcat $ intersperse (nl opts)
|
|
|
|
|
$ addAttrs opts attr header' : innerContents
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert list of Note blocks to a footnote <div>.
|
|
|
|
|
-- Assumes notes are sorted.
|
2011-02-04 19:27:53 -08:00
|
|
|
|
footnoteSection :: WriterOptions -> [Html] -> Html
|
|
|
|
|
footnoteSection opts notes =
|
2011-04-16 10:37:47 -07:00
|
|
|
|
if null notes
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then mempty
|
|
|
|
|
else nl opts >> (container
|
2012-01-11 12:22:17 -08:00
|
|
|
|
$ nl opts >> hrtag >> nl opts >>
|
2011-12-20 11:36:51 -08:00
|
|
|
|
H.ol (mconcat notes >> nl opts) >> nl opts)
|
2011-12-15 21:17:32 -08:00
|
|
|
|
where container x = if writerHtml5 opts
|
2011-12-20 11:25:26 -08:00
|
|
|
|
then H5.section ! A.class_ "footnotes" $ x
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else if writerSlideVariant opts /= NoSlides
|
|
|
|
|
then H.div ! A.class_ "footnotes slide" $ x
|
|
|
|
|
else H.div ! A.class_ "footnotes" $ x
|
2012-01-11 12:22:17 -08:00
|
|
|
|
hrtag = if writerHtml5 opts then H5.hr else H.hr
|
2008-02-09 03:21:04 +00:00
|
|
|
|
|
|
|
|
|
-- | Parse a mailto link; return Just (name, domain) or Nothing.
|
|
|
|
|
parseMailto :: String -> Maybe (String, String)
|
2013-04-25 12:28:55 -07:00
|
|
|
|
parseMailto s = do
|
|
|
|
|
case break (==':') s of
|
|
|
|
|
(xs,':':addr) | map toLower xs == "mailto" -> do
|
|
|
|
|
let (name', rest) = span (/='@') addr
|
|
|
|
|
let domain = drop 1 rest
|
|
|
|
|
return (name', domain)
|
|
|
|
|
_ -> fail "not a mailto: URL"
|
2008-02-09 03:21:04 +00:00
|
|
|
|
|
2009-01-24 19:58:48 +00:00
|
|
|
|
-- | Obfuscate a "mailto:" link.
|
2007-11-03 23:27:58 +00:00
|
|
|
|
obfuscateLink :: WriterOptions -> String -> String -> Html
|
2009-01-24 19:58:48 +00:00
|
|
|
|
obfuscateLink opts txt s | writerEmailObfuscation opts == NoObfuscation =
|
2011-12-15 21:17:32 -08:00
|
|
|
|
H.a ! A.href (toValue s) $ toHtml txt
|
2008-07-13 17:08:55 +00:00
|
|
|
|
obfuscateLink opts txt s =
|
2009-01-24 19:58:48 +00:00
|
|
|
|
let meth = writerEmailObfuscation opts
|
2013-04-25 12:28:55 -07:00
|
|
|
|
s' = map toLower (take 7 s) ++ drop 7 s
|
2008-07-13 17:08:55 +00:00
|
|
|
|
in case parseMailto s' of
|
|
|
|
|
(Just (name', domain)) ->
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let domain' = substitute "." " dot " domain
|
|
|
|
|
at' = obfuscateChar '@'
|
2011-04-16 10:37:47 -07:00
|
|
|
|
(linkText, altText) =
|
2008-07-13 17:08:55 +00:00
|
|
|
|
if txt == drop 7 s' -- autolink
|
2013-01-21 11:28:35 -08:00
|
|
|
|
then ("e", name' ++ " at " ++ domain')
|
2011-04-16 10:37:47 -07:00
|
|
|
|
else ("'" ++ txt ++ "'", txt ++ " (" ++ name' ++ " at " ++
|
2007-11-03 23:27:58 +00:00
|
|
|
|
domain' ++ ")")
|
2009-01-24 19:58:48 +00:00
|
|
|
|
in case meth of
|
|
|
|
|
ReferenceObfuscation ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
-- need to use preEscapedString or &'s are escaped to & in URL
|
|
|
|
|
preEscapedString $ "<a href=\"" ++ (obfuscateString s')
|
2008-07-13 17:08:55 +00:00
|
|
|
|
++ "\">" ++ (obfuscateString txt) ++ "</a>"
|
2009-01-24 19:58:48 +00:00
|
|
|
|
JavascriptObfuscation ->
|
2011-12-15 21:17:32 -08:00
|
|
|
|
(H.script ! A.type_ "text/javascript" $
|
|
|
|
|
preEscapedString ("\n<!--\nh='" ++
|
2011-04-16 10:37:47 -07:00
|
|
|
|
obfuscateString domain ++ "';a='" ++ at' ++ "';n='" ++
|
2008-07-13 17:08:55 +00:00
|
|
|
|
obfuscateString name' ++ "';e=n+a+h;\n" ++
|
2011-04-16 10:37:47 -07:00
|
|
|
|
"document.write('<a h'+'ref'+'=\"ma'+'ilto'+':'+e+'\">'+" ++
|
2011-12-15 21:17:32 -08:00
|
|
|
|
linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) >>
|
|
|
|
|
H.noscript (preEscapedString $ obfuscateString altText)
|
2009-01-24 19:58:48 +00:00
|
|
|
|
_ -> error $ "Unknown obfuscation method: " ++ show meth
|
2011-12-15 21:17:32 -08:00
|
|
|
|
_ -> H.a ! A.href (toValue s) $ toHtml txt -- malformed email
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Obfuscate character as entity.
|
|
|
|
|
obfuscateChar :: Char -> String
|
2011-04-16 10:37:47 -07:00
|
|
|
|
obfuscateChar char =
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let num = ord char
|
|
|
|
|
numstr = if even num then show num else "x" ++ showHex num ""
|
|
|
|
|
in "&#" ++ numstr ++ ";"
|
|
|
|
|
|
|
|
|
|
-- | Obfuscate string using entities.
|
|
|
|
|
obfuscateString :: String -> String
|
2012-02-05 22:52:00 -08:00
|
|
|
|
obfuscateString = concatMap obfuscateChar . fromEntities
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2013-02-12 21:29:17 -08:00
|
|
|
|
addAttrs :: WriterOptions -> Attr -> Html -> Html
|
|
|
|
|
addAttrs opts attr h = foldl (!) h (attrsToHtml opts attr)
|
|
|
|
|
|
2011-12-15 21:17:32 -08:00
|
|
|
|
attrsToHtml :: WriterOptions -> Attr -> [Attribute]
|
2011-01-26 20:44:25 -08:00
|
|
|
|
attrsToHtml opts (id',classes',keyvals) =
|
|
|
|
|
[prefixedId opts id' | not (null id')] ++
|
2013-02-14 19:35:58 -08:00
|
|
|
|
[A.class_ (toValue $ unwords classes') | not (null classes')] ++
|
2011-12-15 21:17:32 -08:00
|
|
|
|
map (\(x,y) -> customAttribute (fromString x) (toValue y)) keyvals
|
2011-01-26 20:44:25 -08:00
|
|
|
|
|
2011-07-16 10:11:04 -07:00
|
|
|
|
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 ext = map toLower $ drop 1 $ takeExtension fp
|
|
|
|
|
in null ext || ext `elem` imageExts
|
|
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- | Convert Pandoc block element to HTML.
|
|
|
|
|
blockToHtml :: WriterOptions -> Block -> State WriterState Html
|
2011-12-15 21:17:32 -08:00
|
|
|
|
blockToHtml _ Null = return mempty
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (Plain lst) = inlineListToHtml opts lst
|
2013-01-15 08:45:46 -08:00
|
|
|
|
-- title beginning with fig: indicates that the image is a figure
|
|
|
|
|
blockToHtml opts (Para [Image txt (s,'f':'i':'g':':':tit)]) = do
|
2010-03-16 04:06:25 +00:00
|
|
|
|
img <- inlineToHtml opts (Image txt (s,tit))
|
2012-08-04 11:34:01 -07:00
|
|
|
|
let tocapt = if writerHtml5 opts
|
|
|
|
|
then H5.figcaption
|
|
|
|
|
else H.p ! A.class_ "caption"
|
|
|
|
|
capt <- if null txt
|
|
|
|
|
then return mempty
|
|
|
|
|
else tocapt `fmap` inlineListToHtml opts txt
|
2011-01-11 22:25:57 -08:00
|
|
|
|
return $ if writerHtml5 opts
|
2011-12-20 11:25:26 -08:00
|
|
|
|
then H5.figure $ mconcat
|
2012-08-04 11:34:01 -07:00
|
|
|
|
[nl opts, img, capt, nl opts]
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else H.div ! A.class_ "figure" $ mconcat
|
2012-08-04 11:34:01 -07:00
|
|
|
|
[nl opts, img, capt, nl opts]
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (Para lst) = do
|
2011-02-03 17:30:38 -08:00
|
|
|
|
contents <- inlineListToHtml opts lst
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.p contents
|
2013-10-13 15:36:19 -07:00
|
|
|
|
blockToHtml opts (Div attr@(_,classes,_) bs) = do
|
2013-08-08 23:14:12 -07:00
|
|
|
|
contents <- blockListToHtml opts bs
|
2013-10-13 15:36:19 -07:00
|
|
|
|
let contents' = nl opts >> contents >> nl opts
|
|
|
|
|
return $
|
|
|
|
|
if "notes" `elem` classes
|
|
|
|
|
then case writerSlideVariant opts of
|
|
|
|
|
RevealJsSlides -> addAttrs opts attr $ H5.aside $ contents'
|
|
|
|
|
NoSlides -> addAttrs opts attr $ H.div $ contents'
|
|
|
|
|
_ -> mempty
|
|
|
|
|
else addAttrs opts attr $ H.div $ contents'
|
2013-08-10 17:23:51 -07:00
|
|
|
|
blockToHtml _ (RawBlock f str)
|
|
|
|
|
| f == Format "html" = return $ preEscapedString str
|
|
|
|
|
| otherwise = return mempty
|
2012-01-11 12:22:17 -08:00
|
|
|
|
blockToHtml opts (HorizontalRule) = return $ if writerHtml5 opts then H5.hr else H.hr
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
|
2012-08-08 23:18:19 -07:00
|
|
|
|
let tolhs = isEnabled Ext_literate_haskell opts &&
|
2011-12-26 22:49:50 -08:00
|
|
|
|
any (\c -> map toLower c == "haskell") classes &&
|
|
|
|
|
any (\c -> map toLower c == "literate") classes
|
|
|
|
|
classes' = if tolhs
|
|
|
|
|
then map (\c -> if map toLower c == "haskell"
|
|
|
|
|
then "literatehaskell"
|
|
|
|
|
else c) classes
|
2013-02-14 19:35:58 -08:00
|
|
|
|
else classes
|
2011-12-26 22:49:50 -08:00
|
|
|
|
adjCode = if tolhs
|
|
|
|
|
then unlines . map ("> " ++) . lines $ rawCode
|
|
|
|
|
else rawCode
|
2013-07-13 02:23:27 -04:00
|
|
|
|
hlCode = if writerHighlight opts -- check highlighting options
|
|
|
|
|
then highlight formatHtmlBlock (id',classes',keyvals) adjCode
|
|
|
|
|
else Nothing
|
|
|
|
|
case hlCode of
|
2013-02-12 21:29:17 -08:00
|
|
|
|
Nothing -> return $ addAttrs opts (id',classes,keyvals)
|
|
|
|
|
$ H.pre $ H.code $ toHtml adjCode
|
2011-12-22 00:33:38 -08:00
|
|
|
|
Just h -> modify (\st -> st{ stHighlighting = True }) >>
|
2013-02-12 21:29:17 -08:00
|
|
|
|
return (addAttrs opts (id',[],keyvals) h)
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (BlockQuote blocks) =
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- in S5, treat list in blockquote specially
|
2011-04-16 10:37:47 -07:00
|
|
|
|
-- if default is incremental, make it nonincremental;
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- otherwise incremental
|
2010-07-13 20:44:56 -07:00
|
|
|
|
if writerSlideVariant opts /= NoSlides
|
2007-11-03 23:27:58 +00:00
|
|
|
|
then let inc = not (writerIncremental opts) in
|
2011-04-16 10:37:47 -07:00
|
|
|
|
case blocks of
|
2007-11-03 23:27:58 +00:00
|
|
|
|
[BulletList lst] -> blockToHtml (opts {writerIncremental = inc})
|
|
|
|
|
(BulletList lst)
|
2011-04-16 10:37:47 -07:00
|
|
|
|
[OrderedList attribs lst] ->
|
2007-11-03 23:27:58 +00:00
|
|
|
|
blockToHtml (opts {writerIncremental = inc})
|
|
|
|
|
(OrderedList attribs lst)
|
2013-03-21 15:21:53 -07:00
|
|
|
|
[DefinitionList lst] ->
|
|
|
|
|
blockToHtml (opts {writerIncremental = inc})
|
|
|
|
|
(DefinitionList lst)
|
2011-02-04 23:25:28 -08:00
|
|
|
|
_ -> do contents <- blockListToHtml opts blocks
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.blockquote
|
|
|
|
|
$ nl opts >> contents >> nl opts
|
2011-02-03 17:30:38 -08:00
|
|
|
|
else do
|
|
|
|
|
contents <- blockListToHtml opts blocks
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.blockquote $ nl opts >> contents >> nl opts
|
2012-10-29 22:45:52 -07:00
|
|
|
|
blockToHtml opts (Header level (ident,_,_) lst) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
contents <- inlineListToHtml opts lst
|
2009-12-09 04:58:29 +00:00
|
|
|
|
secnum <- liftM stSecNum get
|
2013-02-13 08:49:48 -08:00
|
|
|
|
let contents' = if writerNumberSections opts && not (null secnum)
|
|
|
|
|
then (H.span ! A.class_ "header-section-number" $ toHtml
|
|
|
|
|
$ showSecNum secnum) >> strToHtml " " >> contents
|
2009-12-09 04:58:29 +00:00
|
|
|
|
else contents
|
2013-04-20 14:59:39 -07:00
|
|
|
|
let revealSlash = ['/' | writerSlideVariant opts == RevealJsSlides]
|
2012-10-29 22:45:52 -07:00
|
|
|
|
let contents'' = if writerTableOfContents opts && not (null ident)
|
|
|
|
|
then H.a ! A.href (toValue $
|
2013-04-20 14:59:39 -07:00
|
|
|
|
'#' : revealSlash ++
|
|
|
|
|
writerIdentifierPrefix opts ++
|
|
|
|
|
ident) $ contents'
|
2009-12-09 04:58:29 +00:00
|
|
|
|
else contents'
|
2013-02-14 19:35:58 -08:00
|
|
|
|
return $ case level of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
1 -> H.h1 contents''
|
|
|
|
|
2 -> H.h2 contents''
|
|
|
|
|
3 -> H.h3 contents''
|
|
|
|
|
4 -> H.h4 contents''
|
|
|
|
|
5 -> H.h5 contents''
|
|
|
|
|
6 -> H.h6 contents''
|
2013-02-14 19:35:58 -08:00
|
|
|
|
_ -> H.p contents''
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (BulletList lst) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
contents <- mapM (blockListToHtml opts) lst
|
2013-03-20 16:59:47 -04:00
|
|
|
|
return $ unordList opts contents
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
contents <- mapM (blockListToHtml opts) lst
|
|
|
|
|
let numstyle' = camelCaseToHyphenated $ show numstyle
|
2013-03-20 16:59:47 -04:00
|
|
|
|
let attribs = (if startnum /= 1
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then [A.start $ toValue startnum]
|
2007-11-03 23:27:58 +00:00
|
|
|
|
else []) ++
|
|
|
|
|
(if numstyle /= DefaultStyle
|
2011-01-11 22:25:57 -08:00
|
|
|
|
then if writerHtml5 opts
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then [A.type_ $
|
2011-01-11 22:25:57 -08:00
|
|
|
|
case numstyle of
|
|
|
|
|
Decimal -> "1"
|
|
|
|
|
LowerAlpha -> "a"
|
|
|
|
|
UpperAlpha -> "A"
|
|
|
|
|
LowerRoman -> "i"
|
|
|
|
|
UpperRoman -> "I"
|
|
|
|
|
_ -> "1"]
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else [A.style $ toValue $ "list-style-type: " ++
|
2011-01-11 22:25:57 -08:00
|
|
|
|
numstyle']
|
2007-11-03 23:27:58 +00:00
|
|
|
|
else [])
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ foldl (!) (ordList opts contents) attribs
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (DefinitionList lst) = do
|
2009-12-07 08:26:53 +00:00
|
|
|
|
contents <- mapM (\(term, defs) ->
|
2012-09-12 17:44:13 -07:00
|
|
|
|
do term' <- if null term
|
|
|
|
|
then return mempty
|
|
|
|
|
else liftM (H.dt) $ inlineListToHtml opts term
|
2011-12-15 21:17:32 -08:00
|
|
|
|
defs' <- mapM ((liftM (\x -> H.dd $ (x >> nl opts))) .
|
2011-02-04 19:27:53 -08:00
|
|
|
|
blockListToHtml opts) defs
|
2012-09-11 08:51:08 -07:00
|
|
|
|
return $ mconcat $ nl opts : term' : nl opts :
|
|
|
|
|
intersperse (nl opts) defs') lst
|
2013-03-21 15:21:53 -07:00
|
|
|
|
return $ defList opts contents
|
2011-02-04 23:03:38 -08:00
|
|
|
|
blockToHtml opts (Table capt aligns widths headers rows') = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
captionDoc <- if null capt
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then return mempty
|
2011-02-04 23:25:28 -08:00
|
|
|
|
else do
|
|
|
|
|
cs <- inlineListToHtml opts capt
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.caption cs >> nl opts
|
2010-03-10 06:19:53 +00:00
|
|
|
|
let percent w = show (truncate (100*w) :: Integer) ++ "%"
|
|
|
|
|
let coltags = if all (== 0.0) widths
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then mempty
|
|
|
|
|
else mconcat $ map (\w ->
|
|
|
|
|
if writerHtml5 opts
|
|
|
|
|
then H.col ! A.style (toValue $ "width: " ++ percent w)
|
|
|
|
|
else H.col ! A.width (toValue $ percent w) >> nl opts)
|
|
|
|
|
widths
|
2010-03-10 06:19:53 +00:00
|
|
|
|
head' <- if all null headers
|
2011-12-15 21:17:32 -08:00
|
|
|
|
then return mempty
|
2011-02-04 23:25:28 -08:00
|
|
|
|
else do
|
|
|
|
|
contents <- tableRowToHtml opts aligns 0 headers
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.thead (nl opts >> contents) >> nl opts
|
|
|
|
|
body' <- liftM (\x -> H.tbody (nl opts >> mconcat x)) $
|
2011-01-11 22:25:57 -08:00
|
|
|
|
zipWithM (tableRowToHtml opts aligns) [1..] rows'
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.table $ nl opts >> captionDoc >> coltags >> head' >>
|
|
|
|
|
body' >> nl opts
|
2008-07-13 17:08:55 +00:00
|
|
|
|
|
2010-03-07 19:35:14 +00:00
|
|
|
|
tableRowToHtml :: WriterOptions
|
2011-01-11 22:25:57 -08:00
|
|
|
|
-> [Alignment]
|
2010-03-10 06:19:53 +00:00
|
|
|
|
-> Int
|
|
|
|
|
-> [[Block]]
|
2008-07-13 17:08:55 +00:00
|
|
|
|
-> State WriterState Html
|
2011-01-11 22:25:57 -08:00
|
|
|
|
tableRowToHtml opts aligns rownum cols' = do
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let mkcell = if rownum == 0 then H.th else H.td
|
2010-03-07 19:35:14 +00:00
|
|
|
|
let rowclass = case rownum of
|
|
|
|
|
0 -> "header"
|
|
|
|
|
x | x `rem` 2 == 1 -> "odd"
|
|
|
|
|
_ -> "even"
|
2011-04-16 10:37:47 -07:00
|
|
|
|
cols'' <- sequence $ zipWith
|
|
|
|
|
(\alignment item -> tableItemToHtml opts mkcell alignment item)
|
2011-01-11 22:25:57 -08:00
|
|
|
|
aligns cols'
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ (H.tr ! A.class_ rowclass $ nl opts >> mconcat cols'')
|
|
|
|
|
>> nl opts
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2008-07-13 17:08:55 +00:00
|
|
|
|
alignmentToString :: Alignment -> [Char]
|
2007-11-03 23:27:58 +00:00
|
|
|
|
alignmentToString alignment = case alignment of
|
|
|
|
|
AlignLeft -> "left"
|
|
|
|
|
AlignRight -> "right"
|
|
|
|
|
AlignCenter -> "center"
|
|
|
|
|
AlignDefault -> "left"
|
|
|
|
|
|
2008-07-13 17:08:55 +00:00
|
|
|
|
tableItemToHtml :: WriterOptions
|
|
|
|
|
-> (Html -> Html)
|
2011-01-11 22:25:57 -08:00
|
|
|
|
-> Alignment
|
2008-07-13 17:08:55 +00:00
|
|
|
|
-> [Block]
|
|
|
|
|
-> State WriterState Html
|
2010-03-10 06:19:53 +00:00
|
|
|
|
tableItemToHtml opts tag' align' item = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
contents <- blockListToHtml opts item
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let alignStr = alignmentToString align'
|
|
|
|
|
let attribs = if writerHtml5 opts
|
|
|
|
|
then A.style (toValue $ "text-align: " ++ alignStr ++ ";")
|
2011-12-20 11:25:26 -08:00
|
|
|
|
else A.align (toValue alignStr)
|
2011-12-17 23:52:59 -08:00
|
|
|
|
return $ (tag' ! attribs $ contents) >> nl opts
|
2011-02-04 19:27:53 -08:00
|
|
|
|
|
|
|
|
|
toListItems :: WriterOptions -> [Html] -> [Html]
|
|
|
|
|
toListItems opts items = map (toListItem opts) items ++ [nl opts]
|
|
|
|
|
|
|
|
|
|
toListItem :: WriterOptions -> Html -> Html
|
2011-12-15 21:17:32 -08:00
|
|
|
|
toListItem opts item = nl opts >> H.li item
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
blockListToHtml :: WriterOptions -> [Block] -> State WriterState Html
|
2011-02-04 19:27:53 -08:00
|
|
|
|
blockListToHtml opts lst =
|
2013-09-08 15:47:50 -07:00
|
|
|
|
fmap (mconcat . intersperse (nl opts)) $ mapM (blockToHtml opts) lst
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert list of Pandoc inline elements to HTML.
|
|
|
|
|
inlineListToHtml :: WriterOptions -> [Inline] -> State WriterState Html
|
2011-04-16 10:37:47 -07:00
|
|
|
|
inlineListToHtml opts lst =
|
2011-12-15 21:17:32 -08:00
|
|
|
|
mapM (inlineToHtml opts) lst >>= return . mconcat
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert Pandoc inline element to HTML.
|
|
|
|
|
inlineToHtml :: WriterOptions -> Inline -> State WriterState Html
|
|
|
|
|
inlineToHtml opts inline =
|
2011-04-16 10:37:47 -07:00
|
|
|
|
case inline of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
(Str str) -> return $ strToHtml str
|
|
|
|
|
(Space) -> return $ strToHtml " "
|
2012-01-11 12:22:17 -08:00
|
|
|
|
(LineBreak) -> return $ if writerHtml5 opts then H5.br else H.br
|
2013-08-08 23:14:12 -07:00
|
|
|
|
(Span attr ils) -> inlineListToHtml opts ils >>=
|
|
|
|
|
return . addAttrs opts attr . H.span
|
2011-12-15 21:17:32 -08:00
|
|
|
|
(Emph lst) -> inlineListToHtml opts lst >>= return . H.em
|
|
|
|
|
(Strong lst) -> inlineListToHtml opts lst >>= return . H.strong
|
2013-07-13 02:23:27 -04:00
|
|
|
|
(Code attr str) -> case hlCode of
|
2011-12-22 00:33:38 -08:00
|
|
|
|
Nothing -> return
|
2013-02-12 21:29:17 -08:00
|
|
|
|
$ addAttrs opts attr
|
|
|
|
|
$ H.code $ strToHtml str
|
2012-11-05 10:45:49 -08:00
|
|
|
|
Just h -> do
|
|
|
|
|
modify $ \st -> st{ stHighlighting = True }
|
2013-02-12 21:29:17 -08:00
|
|
|
|
return $ addAttrs opts (id',[],keyvals) h
|
2013-07-13 02:23:27 -04:00
|
|
|
|
where (id',_,keyvals) = attr
|
|
|
|
|
hlCode = if writerHighlight opts
|
|
|
|
|
then highlight formatHtmlInline attr str
|
|
|
|
|
else Nothing
|
2008-02-24 18:15:36 +00:00
|
|
|
|
(Strikeout lst) -> inlineListToHtml opts lst >>=
|
2011-12-18 11:08:04 -08:00
|
|
|
|
return . H.del
|
2008-07-15 23:25:49 +00:00
|
|
|
|
(SmallCaps lst) -> inlineListToHtml opts lst >>=
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return . (H.span ! A.style "font-variant: small-caps;")
|
|
|
|
|
(Superscript lst) -> inlineListToHtml opts lst >>= return . H.sup
|
|
|
|
|
(Subscript lst) -> inlineListToHtml opts lst >>= return . H.sub
|
2007-11-03 23:27:58 +00:00
|
|
|
|
(Quoted quoteType lst) ->
|
|
|
|
|
let (leftQuote, rightQuote) = case quoteType of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
SingleQuote -> (strToHtml "‘",
|
|
|
|
|
strToHtml "’")
|
|
|
|
|
DoubleQuote -> (strToHtml "“",
|
|
|
|
|
strToHtml "”")
|
2013-01-15 18:50:36 -08:00
|
|
|
|
in if writerHtmlQTags opts
|
2012-03-03 08:27:44 -08:00
|
|
|
|
then do
|
|
|
|
|
modify $ \st -> st{ stQuotes = True }
|
|
|
|
|
H.q `fmap` inlineListToHtml opts lst
|
|
|
|
|
else (\x -> leftQuote >> x >> rightQuote)
|
|
|
|
|
`fmap` inlineListToHtml opts lst
|
2011-04-16 10:37:47 -07:00
|
|
|
|
(Math t str) -> modify (\st -> st {stMath = True}) >>
|
2007-12-02 00:36:32 +00:00
|
|
|
|
(case writerHTMLMathMethod opts of
|
2011-04-16 10:37:47 -07:00
|
|
|
|
LaTeXMathML _ ->
|
2008-09-15 22:43:21 +00:00
|
|
|
|
-- putting LaTeXMathML in container with class "LaTeX" prevents
|
|
|
|
|
-- non-math elements on the page from being treated as math by
|
|
|
|
|
-- the javascript
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ H.span ! A.class_ "LaTeX" $
|
2010-07-15 19:01:00 -07:00
|
|
|
|
case t of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
InlineMath -> toHtml ("$" ++ str ++ "$")
|
|
|
|
|
DisplayMath -> toHtml ("$$" ++ str ++ "$$")
|
2010-07-15 19:01:00 -07:00
|
|
|
|
JsMath _ -> do
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let m = preEscapedString str
|
2010-07-15 19:01:00 -07:00
|
|
|
|
return $ case t of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
InlineMath -> H.span ! A.class_ "math" $ m
|
|
|
|
|
DisplayMath -> H.div ! A.class_ "math" $ m
|
2010-07-15 19:01:00 -07:00
|
|
|
|
WebTeX url -> do
|
2012-01-11 12:22:17 -08:00
|
|
|
|
let imtag = if writerHtml5 opts then H5.img else H.img
|
|
|
|
|
let m = imtag ! A.style "vertical-align:middle"
|
2011-12-15 21:17:32 -08:00
|
|
|
|
! A.src (toValue $ url ++ urlEncode str)
|
|
|
|
|
! A.alt (toValue str)
|
|
|
|
|
! A.title (toValue str)
|
2012-07-26 22:32:53 -07:00
|
|
|
|
let brtag = if writerHtml5 opts then H5.br else H.br
|
2010-07-15 19:01:00 -07:00
|
|
|
|
return $ case t of
|
|
|
|
|
InlineMath -> m
|
2012-01-11 12:22:17 -08:00
|
|
|
|
DisplayMath -> brtag >> m >> brtag
|
2007-12-02 00:36:32 +00:00
|
|
|
|
GladTeX ->
|
2010-08-01 08:30:04 -07:00
|
|
|
|
return $ case t of
|
2012-02-21 09:00:30 -08:00
|
|
|
|
InlineMath -> preEscapedString $ "<EQ ENV=\"math\">" ++ str ++ "</EQ>"
|
|
|
|
|
DisplayMath -> preEscapedString $ "<EQ ENV=\"displaymath\">" ++ str ++ "</EQ>"
|
2010-03-18 06:45:56 +00:00
|
|
|
|
MathML _ -> do
|
|
|
|
|
let dt = if t == InlineMath
|
|
|
|
|
then DisplayInline
|
|
|
|
|
else DisplayBlock
|
|
|
|
|
let conf = useShortEmptyTags (const False)
|
|
|
|
|
defaultConfigPP
|
|
|
|
|
case texMathToMathML dt str of
|
2011-12-15 21:17:32 -08:00
|
|
|
|
Right r -> return $ preEscapedString $
|
2010-03-18 06:45:56 +00:00
|
|
|
|
ppcElement conf r
|
2010-03-21 22:48:47 -07:00
|
|
|
|
Left _ -> inlineListToHtml opts
|
2010-07-15 19:01:00 -07:00
|
|
|
|
(readTeXMath str) >>= return .
|
2011-12-15 21:17:32 -08:00
|
|
|
|
(H.span ! A.class_ "math")
|
2012-07-11 16:54:13 -07:00
|
|
|
|
MathJax _ -> return $ H.span ! A.class_ "math" $ toHtml $
|
2010-10-31 18:55:02 -07:00
|
|
|
|
case t of
|
|
|
|
|
InlineMath -> "\\(" ++ str ++ "\\)"
|
|
|
|
|
DisplayMath -> "\\[" ++ str ++ "\\]"
|
2010-07-15 19:01:00 -07:00
|
|
|
|
PlainMath -> do
|
|
|
|
|
x <- inlineListToHtml opts (readTeXMath str)
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let m = H.span ! A.class_ "math" $ x
|
2012-01-11 12:22:17 -08:00
|
|
|
|
let brtag = if writerHtml5 opts then H5.br else H.br
|
2010-07-15 19:01:00 -07:00
|
|
|
|
return $ case t of
|
|
|
|
|
InlineMath -> m
|
2012-01-11 12:22:17 -08:00
|
|
|
|
DisplayMath -> brtag >> m >> brtag )
|
2013-08-10 17:23:51 -07:00
|
|
|
|
(RawInline f str)
|
|
|
|
|
| f == Format "latex" ->
|
|
|
|
|
case writerHTMLMathMethod opts of
|
2011-01-23 10:55:56 -08:00
|
|
|
|
LaTeXMathML _ -> do modify (\st -> st {stMath = True})
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ toHtml str
|
|
|
|
|
_ -> return mempty
|
2013-08-10 17:23:51 -07:00
|
|
|
|
| f == Format "html" -> return $ preEscapedString str
|
|
|
|
|
| otherwise -> return mempty
|
2013-01-06 20:51:51 -08:00
|
|
|
|
(Link [Str str] (s,_)) | "mailto:" `isPrefixOf` s &&
|
|
|
|
|
s == escapeURI ("mailto" ++ str) ->
|
|
|
|
|
-- autolink
|
2008-07-13 17:08:55 +00:00
|
|
|
|
return $ obfuscateLink opts str s
|
|
|
|
|
(Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do
|
2011-04-16 10:37:47 -07:00
|
|
|
|
linkText <- inlineListToHtml opts txt
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ obfuscateLink opts (renderHtml linkText) s
|
2008-07-13 17:08:55 +00:00
|
|
|
|
(Link txt (s,tit)) -> do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
linkText <- inlineListToHtml opts txt
|
2013-04-20 14:59:39 -07:00
|
|
|
|
let s' = case s of
|
|
|
|
|
'#':xs | writerSlideVariant opts ==
|
|
|
|
|
RevealJsSlides -> '#':'/':xs
|
|
|
|
|
_ -> s
|
|
|
|
|
let link = H.a ! A.href (toValue s') $ linkText
|
2011-12-15 21:17:32 -08:00
|
|
|
|
return $ if null tit
|
|
|
|
|
then link
|
|
|
|
|
else link ! A.title (toValue tit)
|
2011-07-16 10:11:04 -07:00
|
|
|
|
(Image txt (s,tit)) | treatAsImage s -> do
|
2011-02-05 08:16:34 -08:00
|
|
|
|
let alternate' = stringify txt
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let attributes = [A.src $ toValue s] ++
|
2011-04-16 10:37:47 -07:00
|
|
|
|
(if null tit
|
|
|
|
|
then []
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else [A.title $ toValue tit]) ++
|
2011-04-16 10:37:47 -07:00
|
|
|
|
if null txt
|
|
|
|
|
then []
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else [A.alt $ toValue alternate']
|
2012-01-11 12:22:17 -08:00
|
|
|
|
let tag = if writerHtml5 opts then H5.img else H.img
|
|
|
|
|
return $ foldl (!) tag attributes
|
2011-04-16 10:37:47 -07:00
|
|
|
|
-- note: null title included, as in Markdown.pl
|
2011-07-16 10:11:04 -07:00
|
|
|
|
(Image _ (s,tit)) -> do
|
2011-12-15 21:17:32 -08:00
|
|
|
|
let attributes = [A.src $ toValue s] ++
|
2011-07-16 10:11:04 -07:00
|
|
|
|
(if null tit
|
|
|
|
|
then []
|
2011-12-15 21:17:32 -08:00
|
|
|
|
else [A.title $ toValue tit])
|
2011-12-20 11:25:26 -08:00
|
|
|
|
return $ foldl (!) H5.embed attributes
|
2011-07-16 10:11:04 -07:00
|
|
|
|
-- note: null title included, as in Markdown.pl
|
2011-04-16 10:37:47 -07:00
|
|
|
|
(Note contents) -> do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
st <- get
|
|
|
|
|
let notes = stNotes st
|
|
|
|
|
let number = (length notes) + 1
|
|
|
|
|
let ref = show number
|
2011-04-16 10:37:47 -07:00
|
|
|
|
htmlContents <- blockListToNote opts ref contents
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- push contents onto front of notes
|
2011-04-16 10:37:47 -07:00
|
|
|
|
put $ st {stNotes = (htmlContents:notes)}
|
2013-04-20 14:59:39 -07:00
|
|
|
|
let revealSlash = ['/' | writerSlideVariant opts
|
|
|
|
|
== RevealJsSlides]
|
2013-01-05 17:18:43 -08:00
|
|
|
|
let link = H.a ! A.href (toValue $ "#" ++
|
2013-04-20 14:59:39 -07:00
|
|
|
|
revealSlash ++
|
2013-01-05 17:18:43 -08:00
|
|
|
|
writerIdentifierPrefix opts ++ "fn" ++ ref)
|
|
|
|
|
! A.class_ "footnoteRef"
|
|
|
|
|
! prefixedId opts ("fnref" ++ ref)
|
|
|
|
|
$ toHtml ref
|
|
|
|
|
let link' = case writerEpubVersion opts of
|
|
|
|
|
Just EPUB3 -> link ! customAttribute "epub:type" "noteref"
|
|
|
|
|
_ -> link
|
|
|
|
|
return $ H.sup $ link'
|
2013-01-18 12:16:12 -08:00
|
|
|
|
(Cite cits il)-> do contents <- inlineListToHtml opts il
|
|
|
|
|
let citationIds = unwords $ map citationId cits
|
|
|
|
|
let result = H.span ! A.class_ "citation" $ contents
|
|
|
|
|
return $ if writerHtml5 opts
|
|
|
|
|
then result ! customAttribute "data-cites" (toValue citationIds)
|
|
|
|
|
else result
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
blockListToNote :: WriterOptions -> String -> [Block] -> State WriterState Html
|
|
|
|
|
blockListToNote opts ref blocks =
|
|
|
|
|
-- If last block is Para or Plain, include the backlink at the end of
|
|
|
|
|
-- that block. Otherwise, insert a new Plain block with the backlink.
|
2011-12-24 21:49:38 -06:00
|
|
|
|
let backlink = [Link [Str "↩"] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])]
|
2007-11-03 23:27:58 +00:00
|
|
|
|
blocks' = if null blocks
|
|
|
|
|
then []
|
|
|
|
|
else let lastBlock = last blocks
|
|
|
|
|
otherBlocks = init blocks
|
|
|
|
|
in case lastBlock of
|
|
|
|
|
(Para lst) -> otherBlocks ++
|
|
|
|
|
[Para (lst ++ backlink)]
|
|
|
|
|
(Plain lst) -> otherBlocks ++
|
|
|
|
|
[Plain (lst ++ backlink)]
|
|
|
|
|
_ -> otherBlocks ++ [lastBlock,
|
|
|
|
|
Plain backlink]
|
|
|
|
|
in do contents <- blockListToHtml opts blocks'
|
2013-01-05 17:18:43 -08:00
|
|
|
|
let noteItem = H.li ! (prefixedId opts ("fn" ++ ref)) $ contents
|
|
|
|
|
let noteItem' = case writerEpubVersion opts of
|
|
|
|
|
Just EPUB3 -> noteItem ! customAttribute "epub:type" "footnote"
|
|
|
|
|
_ -> noteItem
|
|
|
|
|
return $ nl opts >> noteItem'
|