-
-
Notifications
You must be signed in to change notification settings - Fork 3.4k
/
HTML.hs
1682 lines (1593 loc) · 72.8 KB
/
HTML.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.HTML
Copyright : Copyright (C) 2006-2022 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <[email protected]>
Stability : alpha
Portability : portable
Conversion of 'Pandoc' documents to HTML.
-}
module Text.Pandoc.Writers.HTML (
writeHtml4,
writeHtml4String,
writeHtml5,
writeHtml5String,
writeHtmlStringForEPUB,
writeS5,
writeSlidy,
writeSlideous,
writeDZSlides,
writeRevealJs,
tagWithAttributes
) where
import Control.Monad.State.Strict
import Data.Char (ord)
import Data.List (intercalate, intersperse, partition, delete, (\\), foldl')
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Maybe (fromMaybe, isJust, isNothing)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Network.URI (URI (..), parseURIReference)
import Numeric (showHex)
import Text.DocLayout (render, literal, Doc)
import Text.Blaze.Internal (MarkupM (Empty), customLeaf, customParent)
import Text.DocTemplates (FromContext (lookupContext), Context (..))
import Text.Blaze.Html hiding (contents)
import Text.Pandoc.Translations (Term(Abstract))
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (formatHtmlBlock, formatHtmlInline, highlight,
styleToCss)
import Text.Pandoc.ImageSize
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Slides
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
import Text.Pandoc.Writers.Shared
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
import Text.Pandoc.Network.HTTP (urlEncode)
import Text.Pandoc.XML (escapeStringForXML, fromEntities, toEntities,
html5Attributes, html4Attributes, rdfaAttributes)
import qualified Text.Blaze.XHtml5 as H5
import qualified Text.Blaze.XHtml5.Attributes as A5
import Control.Monad.Except (throwError)
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 (PandocMonad, report,
translateTerm)
import Text.Pandoc.Class.PandocPure (runPure)
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Text.Pandoc.MIME (mediaCategory)
import Text.Pandoc.Writers.Blaze (layoutMarkup)
import Text.TeXMath
import Text.XML.Light (elChildren, unode, unqual)
import qualified Text.XML.Light as XML
import Text.XML.Light.Output
import Data.String (fromString)
data WriterState = WriterState
{ stNotes :: [Html] -- ^ List of notes
, stEmittedNotes :: Int -- ^ How many notes we've already pushed out to the HTML
, stMath :: Bool -- ^ Math is used in document
, stQuotes :: Bool -- ^ <q> tag is used
, stHighlighting :: Bool -- ^ Syntax highlighting is used
, stHtml5 :: Bool -- ^ Use HTML5
, stEPUBVersion :: Maybe EPUBVersion -- ^ EPUB version if for epub
, stSlideVariant :: HTMLSlideVariant
, stSlideLevel :: Int -- ^ Slide level
, stInSection :: Bool -- ^ Content is in a section (revealjs)
, stCodeBlockNum :: Int -- ^ Number of code block
, stCsl :: Bool -- ^ Has CSL references
, stCslEntrySpacing :: Maybe Int -- ^ CSL entry spacing
, stBlockLevel :: Int -- ^ Current block depth, excluding section divs
}
defaultWriterState :: WriterState
defaultWriterState = WriterState {stNotes= [], stEmittedNotes = 0, stMath = False, stQuotes = False,
stHighlighting = False,
stHtml5 = False,
stEPUBVersion = Nothing,
stSlideVariant = NoSlides,
stSlideLevel = 1,
stInSection = False,
stCodeBlockNum = 0,
stCsl = False,
stCslEntrySpacing = Nothing,
stBlockLevel = 0}
-- Helpers to render HTML with the appropriate function.
strToHtml :: Text -> Html
strToHtml = strToHtml' . T.unpack
where
strToHtml' ('\'':xs) = preEscapedString "\'" `mappend` strToHtml' xs
strToHtml' ('"' :xs) = preEscapedString "\"" `mappend` strToHtml' xs
strToHtml' (x:xs) | needsVariationSelector x
= preEscapedString [x, '\xFE0E'] `mappend`
case xs of
('\xFE0E':ys) -> strToHtml' ys
_ -> strToHtml' xs
strToHtml' xs@(_:_) = case break (\c -> c == '\'' || c == '"' ||
needsVariationSelector c) xs of
(_ ,[]) -> toHtml xs
(ys,zs) -> toHtml ys `mappend` strToHtml' zs
strToHtml' [] = ""
-- See #5469: this prevents iOS from substituting emojis.
needsVariationSelector :: Char -> Bool
needsVariationSelector '↩' = True
needsVariationSelector '↔' = True
needsVariationSelector _ = False
-- | Hard linebreak.
nl :: Html
nl = preEscapedString "\n"
-- | Convert Pandoc document to Html 5 string.
writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeHtml5String = writeHtmlString'
defaultWriterState{ stHtml5 = True }
-- | Convert Pandoc document to Html 5 structure.
writeHtml5 :: PandocMonad m => WriterOptions -> Pandoc -> m Html
writeHtml5 = writeHtml' defaultWriterState{ stHtml5 = True }
-- | Convert Pandoc document to Html 4 string.
writeHtml4String :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeHtml4String = writeHtmlString'
defaultWriterState{ stHtml5 = False }
-- | Convert Pandoc document to Html 4 structure.
writeHtml4 :: PandocMonad m => WriterOptions -> Pandoc -> m Html
writeHtml4 = writeHtml' defaultWriterState{ stHtml5 = False }
-- | Convert Pandoc document to Html appropriate for an epub version.
writeHtmlStringForEPUB :: PandocMonad m
=> EPUBVersion -> WriterOptions -> Pandoc
-> m Text
writeHtmlStringForEPUB version o = writeHtmlString'
defaultWriterState{ stHtml5 = version == EPUB3,
stEPUBVersion = Just version }
o{ writerWrapText = WrapNone }
-- | Convert Pandoc document to Reveal JS HTML slide show.
writeRevealJs :: PandocMonad m
=> WriterOptions -> Pandoc -> m Text
writeRevealJs = writeHtmlSlideShow' RevealJsSlides
-- | Convert Pandoc document to S5 HTML slide show.
writeS5 :: PandocMonad m
=> WriterOptions -> Pandoc -> m Text
writeS5 = writeHtmlSlideShow' S5Slides
-- | Convert Pandoc document to Slidy HTML slide show.
writeSlidy :: PandocMonad m
=> WriterOptions -> Pandoc -> m Text
writeSlidy = writeHtmlSlideShow' SlidySlides
-- | Convert Pandoc document to Slideous HTML slide show.
writeSlideous :: PandocMonad m
=> WriterOptions -> Pandoc -> m Text
writeSlideous = writeHtmlSlideShow' SlideousSlides
-- | Convert Pandoc document to DZSlides HTML slide show.
writeDZSlides :: PandocMonad m
=> WriterOptions -> Pandoc -> m Text
writeDZSlides = writeHtmlSlideShow' DZSlides
writeHtmlSlideShow' :: PandocMonad m
=> HTMLSlideVariant -> WriterOptions -> Pandoc -> m Text
writeHtmlSlideShow' variant = writeHtmlString'
defaultWriterState{ stSlideVariant = variant
, stHtml5 = case variant of
RevealJsSlides -> True
S5Slides -> False
SlidySlides -> False
DZSlides -> True
SlideousSlides -> False
NoSlides -> False
}
renderHtml' :: Html -> Text
renderHtml' = TL.toStrict . renderHtml
writeHtmlString' :: PandocMonad m
=> WriterState -> WriterOptions -> Pandoc -> m Text
writeHtmlString' st opts d = do
(body, context) <- evalStateT (pandocToHtml opts d) st
let colwidth = case writerWrapText opts of
WrapAuto -> Just (writerColumns opts)
_ -> Nothing
(if writerPreferAscii opts
then toEntities
else id) <$>
case writerTemplate opts of
Nothing -> return $
case colwidth of
Nothing -> renderHtml' body -- optimization, skip layout
Just cols -> render (Just cols) $ layoutMarkup body
Just tpl -> do
-- warn if empty lang
when (isNothing (getField "lang" context :: Maybe Text)) $
report NoLangSpecified
-- check for empty pagetitle
(context' :: Context Text) <-
case getField "pagetitle" context of
Just (s :: Text) | not (T.null s) -> return context
_ -> do
let fallback = T.pack $
case lookupContext "sourcefile"
(writerVariables opts) of
Nothing -> "Untitled"
Just [] -> "Untitled"
Just (x:_) -> takeBaseName $ T.unpack x
report $ NoTitleElement fallback
return $ resetField "pagetitle" (literal fallback) context
return $ render colwidth $ renderTemplate tpl
(defField "body" (layoutMarkup body) context')
writeHtml' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Html
writeHtml' st opts d =
case writerTemplate opts of
Just _ -> preEscapedText <$> writeHtmlString' st opts d
Nothing
| writerPreferAscii opts
-> preEscapedText <$> writeHtmlString' st opts d
| otherwise -> do
(body, _) <- evalStateT (pandocToHtml opts d) st
return body
-- result is (title, authors, date, toc, body, new variables)
pandocToHtml :: PandocMonad m
=> WriterOptions
-> Pandoc
-> StateT WriterState m (Html, Context Text)
pandocToHtml opts (Pandoc meta blocks) = do
let slideLevel = fromMaybe (getSlideLevel blocks) $ writerSlideLevel opts
modify $ \st -> st{ stSlideLevel = slideLevel }
metadata <- metaToContext opts
(fmap layoutMarkup . blockListToHtml opts)
(fmap layoutMarkup . inlineListToHtml opts)
meta
let stringifyHTML = escapeStringForXML . stringify
let authsMeta = map (literal . stringifyHTML) $ docAuthors meta
let dateMeta = stringifyHTML $ docDate meta
let descriptionMeta = literal $ escapeStringForXML $
lookupMetaString "description" meta
slideVariant <- gets stSlideVariant
abstractTitle <- translateTerm Abstract
let sects = adjustNumbers opts $
makeSections (writerNumberSections opts) Nothing $
if slideVariant == NoSlides
then blocks
else prepSlides slideLevel blocks
toc <- if writerTableOfContents opts && slideVariant /= S5Slides
then fmap layoutMarkup <$> tableOfContents opts sects
else return Nothing
blocks' <- blockListToHtml opts sects
notes <- do
-- make the st private just to be safe, since we modify it right afterwards
st <- get
if null (stNotes st)
then return mempty
else do
notes <- footnoteSection EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st))
modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') })
return notes
st <- get
let thebody = blocks' >> notes
let math = layoutMarkup $ case writerHTMLMathMethod opts of
MathJax url
| slideVariant /= RevealJsSlides ->
-- mathjax is handled via a special plugin in revealjs
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
$ case slideVariant of
SlideousSlides ->
preEscapedString
"MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
_ -> mempty
KaTeX url -> do
H.script !
A.defer mempty !
A.src (toValue $ url <> "katex.min.js") $ mempty
nl
let katexFlushLeft =
case lookupContext "classoption" metadata of
Just clsops | "fleqn" `elem` (clsops :: [Doc Text]) -> "true"
_ -> "false"
H.script $ text $ T.unlines [
"document.addEventListener(\"DOMContentLoaded\", function () {"
, " var mathElements = document.getElementsByClassName(\"math\");"
, " var macros = [];"
, " for (var i = 0; i < mathElements.length; i++) {"
, " var texText = mathElements[i].firstChild;"
, " if (mathElements[i].tagName == \"SPAN\") {"
, " katex.render(texText.data, mathElements[i], {"
, " displayMode: mathElements[i].classList.contains('display'),"
, " throwOnError: false,"
, " macros: macros,"
, " fleqn: " <> katexFlushLeft
, " });"
, "}}});"
]
nl
H.link ! A.rel "stylesheet" !
A.href (toValue $ url <> "katex.min.css")
_ -> case lookupContext "mathml-script"
(writerVariables opts) of
Just s | not (stHtml5 st) ->
H.script ! A.type_ "text/javascript"
$ preEscapedString
("/*<![CDATA[*/\n" <> T.unpack s <>
"/*]]>*/\n")
| otherwise -> mempty
Nothing -> mempty
let mCss :: Maybe [Text] = lookupContext "css" metadata
let context :: Context Text
context = (if stHighlighting st
then case writerHighlightStyle opts of
Just sty -> defField "highlighting-css"
(literal $ T.pack $ styleToCss sty)
Nothing -> id
else id) .
(if stCsl st
then defField "csl-css" True .
(case stCslEntrySpacing st of
Nothing -> id
Just 0 -> id
Just n ->
defField "csl-entry-spacing"
(literal $ tshow n <> "em"))
else id) .
(if stMath st
then defField "math" math
else id) .
defField "abstract-title" abstractTitle .
(case writerHTMLMathMethod opts of
MathJax u -> defField "mathjax" True .
defField "mathjaxurl"
(literal $ T.takeWhile (/='?') u)
_ -> defField "mathjax" False) .
(case writerHTMLMathMethod opts of
PlainMath -> defField "displaymath-css" True
WebTeX _ -> defField "displaymath-css" True
_ -> id) .
(if slideVariant == RevealJsSlides
then -- set boolean options explicitly, since
-- template can't distinguish False/undefined
defField "controls" True .
defField "controlsTutorial" True .
defField "controlsLayout"
("bottom-right" :: Doc Text) .
defField "controlsBackArrows" ("faded" :: Doc Text) .
defField "progress" True .
defField "slideNumber" False .
defField "showSlideNumber" ("all" :: Doc Text) .
defField "hashOneBasedIndex" False .
defField "hash" True .
defField "respondToHashChanges" True .
defField "history" False .
defField "keyboard" True .
defField "overview" True .
defField "disableLayout" False .
defField "center" True .
defField "touch" True .
defField "loop" False .
defField "rtl" False .
defField "navigationMode" ("default" :: Doc Text) .
defField "shuffle" False .
defField "fragments" True .
defField "fragmentInURL" True .
defField "embedded" False .
defField "help" True .
defField "pause" True .
defField "showNotes" False .
defField "autoPlayMedia" ("null" :: Doc Text) .
defField "preloadIframes" ("null" :: Doc Text) .
defField "autoSlide" ("0" :: Doc Text) .
defField "autoSlideStoppable" True .
defField "autoSlideMethod" ("null" :: Doc Text) .
defField "defaultTiming" ("null" :: Doc Text) .
defField "mouseWheel" False .
defField "display" ("block" :: Doc Text) .
defField "hideInactiveCursor" True .
defField "hideCursorTime" ("5000" :: Doc Text) .
defField "previewLinks" False .
defField "transition" ("slide" :: Doc Text) .
defField "transitionSpeed" ("default" :: Doc Text) .
defField "backgroundTransition" ("fade" :: Doc Text) .
defField "viewDistance" ("3" :: Doc Text) .
defField "mobileViewDistance" ("2" :: Doc Text)
else id) .
defField "document-css" (isNothing mCss && slideVariant == NoSlides) .
defField "quotes" (stQuotes st) .
-- for backwards compatibility we populate toc
-- with the contents of the toc, rather than a
-- boolean:
maybe id (defField "toc") toc .
maybe id (defField "table-of-contents") toc .
defField "author-meta" authsMeta .
maybe id (defField "date-meta" . literal)
(normalizeDate dateMeta) .
defField "description-meta" descriptionMeta .
defField "pagetitle"
(literal . stringifyHTML . docTitle $ meta) .
defField "idprefix" (literal $ writerIdentifierPrefix opts) .
-- these should maybe be set in pandoc.hs
defField "slidy-url"
("https://www.w3.org/Talks/Tools/Slidy2" :: Doc Text) .
defField "slideous-url" ("slideous" :: Doc Text) .
defField "revealjs-url" ("https://unpkg.com/reveal.js@^4/" :: Doc Text) $
defField "s5-url" ("s5/default" :: Doc Text) .
defField "html5" (stHtml5 st) $
metadata
return (thebody, context)
-- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix
prefixedId :: WriterOptions -> Text -> Attribute
prefixedId opts s =
case s of
"" -> mempty
_ -> A.id $ toValue $ writerIdentifierPrefix opts <> s
toList :: PandocMonad m
=> (Html -> Html)
-> WriterOptions
-> [Html]
-> StateT WriterState m Html
toList listop opts items = do
slideVariant <- gets stSlideVariant
return $
if writerIncremental opts
then if slideVariant /= RevealJsSlides
then listop (mconcat items) ! A.class_ "incremental"
else listop $ mconcat $ map (! A.class_ "fragment") items
else listop $ mconcat items
unordList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
unordList opts = toList H.ul opts . toListItems
ordList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
ordList opts = toList H.ol opts . toListItems
defList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
defList opts items = toList H.dl opts (items ++ [nl])
isTaskListItem :: [Block] -> Bool
isTaskListItem (Plain (Str "☐":Space:_):_) = True
isTaskListItem (Plain (Str "☒":Space:_):_) = True
isTaskListItem (Para (Str "☐":Space:_):_) = True
isTaskListItem (Para (Str "☒":Space:_):_) = True
isTaskListItem _ = False
listItemToHtml :: PandocMonad m
=> WriterOptions -> [Block] -> StateT WriterState m Html
listItemToHtml opts bls
| Plain (Str "☐":Space:is) : bs <- bls = taskListItem False id is bs
| Plain (Str "☒":Space:is) : bs <- bls = taskListItem True id is bs
| Para (Str "☐":Space:is) : bs <- bls = taskListItem False H.p is bs
| Para (Str "☒":Space:is) : bs <- bls = taskListItem True H.p is bs
| otherwise = blockListToHtml opts bls
where
taskListItem checked constr is bs = do
let checkbox = if checked
then checkbox' ! A.checked ""
else checkbox'
checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl
isContents <- inlineListToHtml opts is
bsContents <- blockListToHtml opts bs
return $ constr (checkbox >> isContents) >> bsContents
-- | Construct table of contents from list of elements.
tableOfContents :: PandocMonad m => WriterOptions -> [Block]
-> StateT WriterState m (Maybe Html)
tableOfContents _ [] = return Nothing
tableOfContents opts sects = do
-- in reveal.js, we need #/apples, not #apples:
slideVariant <- gets stSlideVariant
let opts' = case slideVariant of
RevealJsSlides ->
opts{ writerIdentifierPrefix =
"/" <> writerIdentifierPrefix opts }
_ -> opts
case toTableOfContents opts sects of
bl@(BulletList (_:_)) -> Just <$> blockToHtml opts' bl
_ -> return Nothing
-- | Convert list of Note blocks to a footnote <div>.
-- Assumes notes are sorted.
footnoteSection ::
PandocMonad m => ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html
footnoteSection refLocation startCounter notes = do
html5 <- gets stHtml5
slideVariant <- gets stSlideVariant
let hrtag = if refLocation /= EndOfBlock
then (if html5 then H5.hr else H.hr) <> nl
else mempty
let additionalClassName = case refLocation of
EndOfBlock -> "footnotes-end-of-block"
EndOfDocument -> "footnotes-end-of-document"
EndOfSection -> "footnotes-end-of-section"
let className = "footnotes " <> additionalClassName
epubVersion <- gets stEPUBVersion
let container x
| html5
, epubVersion == Just EPUB3
= H5.section ! A.class_ className
! customAttribute "epub:type" "footnotes" $ x
| html5 = H5.section ! A.class_ className
! customAttribute "role" "doc-endnotes"
$ x
| slideVariant /= NoSlides = H.div ! A.class_ "footnotes slide" $ x
| otherwise = H.div ! A.class_ className $ x
return $
if null notes
then mempty
else do
nl
container $ do
nl
hrtag
-- Keep the previous output exactly the same if we don't
-- have multiple notes sections
if startCounter == 1
then H.ol $ mconcat notes >> nl
else H.ol ! A.start (fromString (show startCounter)) $
mconcat notes >> nl
nl
-- | Parse a mailto link; return Just (name, domain) or Nothing.
parseMailto :: Text -> Maybe (Text, Text)
parseMailto s =
case T.break (==':') s of
(xs,T.uncons -> Just (':',addr)) | T.toLower xs == "mailto" -> do
let (name', rest) = T.span (/='@') addr
let domain = T.drop 1 rest
return (name', domain)
_ -> Prelude.fail "not a mailto: URL"
-- | Obfuscate a "mailto:" link.
obfuscateLink :: PandocMonad m
=> WriterOptions -> Attr -> Html -> Text
-> StateT WriterState m Html
obfuscateLink opts attr txt s | writerEmailObfuscation opts == NoObfuscation =
addAttrs opts attr $ H.a ! A.href (toValue s) $ txt
obfuscateLink opts attr (TL.toStrict . renderHtml -> txt) s =
let meth = writerEmailObfuscation opts
s' = T.toLower (T.take 7 s) <> T.drop 7 s
in case parseMailto s' of
(Just (name', domain)) ->
let domain' = T.replace "." " dot " domain
at' = obfuscateChar '@'
(linkText, altText) =
if txt == T.drop 7 s' -- autolink
then ("e", name' <> " at " <> domain')
else ("'" <> obfuscateString txt <> "'",
txt <> " (" <> name' <> " at " <> domain' <> ")")
(_, classNames, _) = attr
classNamesStr = T.concat $ map (" "<>) classNames
in case meth of
ReferenceObfuscation ->
-- need to use preEscapedString or &'s are escaped to & in URL
return $
preEscapedText $ "<a href=\"" <> obfuscateString s'
<> "\" class=\"email\">" <> obfuscateString txt <> "</a>"
JavascriptObfuscation ->
return $
(H.script ! A.type_ "text/javascript" $
preEscapedText ("\n<!--\nh='" <>
obfuscateString domain <> "';a='" <> at' <> "';n='" <>
obfuscateString name' <> "';e=n+a+h;\n" <>
"document.write('<a h'+'ref'+'=\"ma'+'ilto'+':'+e+'\" clas'+'s=\"em' + 'ail" <>
classNamesStr <> "\">'+" <>
linkText <> "+'<\\/'+'a'+'>');\n// -->\n")) >>
H.noscript (preEscapedText $ obfuscateString altText)
_ -> throwError $ PandocSomeError $ "Unknown obfuscation method: " <> tshow meth
_ -> addAttrs opts attr $ H.a ! A.href (toValue s) $ toHtml txt -- malformed email
-- | Obfuscate character as entity.
obfuscateChar :: Char -> Text
obfuscateChar char =
let num = ord char
numstr = if even num then show num else "x" <> showHex num ""
in "&#" <> T.pack numstr <> ";"
-- | Obfuscate string using entities.
obfuscateString :: Text -> Text
obfuscateString = T.concatMap obfuscateChar . fromEntities
-- | Create HTML tag with attributes.
tagWithAttributes :: WriterOptions
-> Bool -- ^ True for HTML5
-> Bool -- ^ True if self-closing tag
-> Text -- ^ Tag text
-> Attr -- ^ Pandoc style tag attributes
-> Text
tagWithAttributes opts html5 selfClosing tagname attr =
let mktag = (TL.toStrict . renderHtml <$> evalStateT
(addAttrs opts attr (customLeaf (textTag tagname) selfClosing))
defaultWriterState{ stHtml5 = html5 })
in case runPure mktag of
Left _ -> mempty
Right t -> t
addAttrs :: PandocMonad m
=> WriterOptions -> Attr -> Html -> StateT WriterState m Html
addAttrs opts attr h = foldl' (!) h <$> attrsToHtml opts attr
toAttrs :: PandocMonad m
=> [(Text, Text)] -> StateT WriterState m [Attribute]
toAttrs kvs = do
html5 <- gets stHtml5
mbEpubVersion <- gets stEPUBVersion
reverse . snd <$> foldM (go html5 mbEpubVersion) (Set.empty, []) kvs
where
go html5 mbEpubVersion (keys, attrs) (k,v) = do
if k `Set.member` keys
then do
report $ DuplicateAttribute k v
return (keys, attrs)
else return (Set.insert k keys, addAttr html5 mbEpubVersion k v attrs)
addAttr html5 mbEpubVersion x y
| T.null x = id -- see #7546
| html5
= if x `Set.member` (html5Attributes <> rdfaAttributes)
|| T.any (== ':') x -- e.g. epub: namespace
|| "data-" `T.isPrefixOf` x
|| "aria-" `T.isPrefixOf` x
then (customAttribute (textTag x) (toValue y) :)
else (customAttribute (textTag ("data-" <> x)) (toValue y) :)
| mbEpubVersion == Just EPUB2
, not (x `Set.member` (html4Attributes <> rdfaAttributes) ||
"xml:" `T.isPrefixOf` x)
= id
| otherwise
= (customAttribute (textTag x) (toValue y) :)
attrsToHtml :: PandocMonad m
=> WriterOptions -> Attr -> StateT WriterState m [Attribute]
attrsToHtml opts (id',classes',keyvals) = do
attrs <- toAttrs keyvals
return $
[prefixedId opts id' | not (T.null id')] ++
[A.class_ (toValue $ T.unwords classes') | not (null classes')] ++ attrs
imgAttrsToHtml :: PandocMonad m
=> WriterOptions -> Attr -> StateT WriterState m [Attribute]
imgAttrsToHtml opts attr = do
attrs <- attrsToHtml opts (ident,cls,kvs')
dimattrs <- toAttrs (dimensionsToAttrList attr)
return $ attrs ++ dimattrs
where
(ident,cls,kvs) = attr
kvs' = filter isNotDim kvs
isNotDim ("width", _) = False
isNotDim ("height", _) = False
isNotDim _ = True
dimensionsToAttrList :: Attr -> [(Text, Text)]
dimensionsToAttrList attr = consolidateStyles $ go Width ++ go Height
where
consolidateStyles :: [(Text, Text)] -> [(Text, Text)]
consolidateStyles xs =
case partition isStyle xs of
([], _) -> xs
(ss, rest) -> ("style", T.intercalate ";" $ map snd ss) : rest
isStyle ("style", _) = True
isStyle _ = False
go dir = case dimension dir attr of
(Just (Pixel a)) -> [(tshow dir, tshow a)]
(Just x) -> [("style", tshow dir <> ":" <> tshow x)]
Nothing -> []
figure :: PandocMonad m
=> WriterOptions -> Attr -> [Inline] -> (Text, Text)
-> StateT WriterState m Html
figure opts attr@(_, _, attrList) txt (s,tit) = do
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.
-- When the alt text differs from the caption both should be read.
let alt = if html5 then txt else [Str ""]
let tocapt = if html5
then (H5.figcaption !) $
if isJust (lookup "alt" attrList)
then mempty
else 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 (nl <>) . tocapt <$> inlineListToHtml opts txt
let inner = mconcat [nl, img, capt, nl]
return $ if html5
then H5.figure inner
else H.div ! A.class_ "figure" $ inner
adjustNumbers :: WriterOptions -> [Block] -> [Block]
adjustNumbers opts doc =
if all (==0) (writerNumberOffset opts)
then doc
else walk go doc
where
go (Header level (ident,classes,kvs) lst) =
Header level (ident,classes,map fixnum kvs) lst
go x = x
fixnum ("number",num) = ("number",
showSecNum $ zipWith (+)
(writerNumberOffset opts ++ repeat 0)
(map (fromMaybe 0 . safeRead) $
T.split (=='.') num))
fixnum x = x
showSecNum = T.intercalate "." . map tshow
blockToHtmlInner :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html
blockToHtmlInner _ Null = return mempty
blockToHtmlInner opts (Plain lst) = inlineListToHtml opts lst
blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)])
| "r-stretch" `elem` classes = do
slideVariant <- gets stSlideVariant
case slideVariant of
RevealJsSlides ->
-- a "stretched" image in reveal.js must be a direct child
-- of the slide container
inlineToHtml opts (Image attr txt (src, tit))
_ -> figure opts attr txt (src, tit)
-- title beginning with fig: indicates that the image is a figure
blockToHtmlInner opts (SimpleFigure attr caption (src, title)) =
figure opts attr caption (src, title)
blockToHtmlInner opts (Para lst) = do
contents <- inlineListToHtml opts lst
case contents of
Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty
_ -> return $ H.p contents
blockToHtmlInner opts (LineBlock lns) =
if writerWrapText opts == WrapNone
then blockToHtml opts $ linesToPara lns
else do
htmlLines <- inlineListToHtml opts $ intercalate [LineBreak] lns
return $ H.div ! A.class_ "line-block" $ htmlLines
blockToHtmlInner opts (Div (ident, "section":dclasses, dkvs)
(Header level
hattr@(hident,hclasses,hkvs) ils : xs)) = do
slideVariant <- gets stSlideVariant
slideLevel <- gets stSlideLevel
let slide = slideVariant /= NoSlides &&
level <= slideLevel {- DROPPED old fix for #5168 here -}
html5 <- gets stHtml5
let titleSlide = slide && level < slideLevel
let level' = if level <= slideLevel && slideVariant == SlidySlides
then 1 -- see #3566
else level
header' <- if ils == [Str "\0"] -- marker for hrule
then return mempty
else blockToHtml opts (Header level' hattr ils)
let isSec (Div (_,"section":_,_) _) = True
isSec (Div _ zs) = any isSec zs
isSec _ = False
let isPause (Para [Str ".",Space,Str ".",Space,Str "."]) = True
isPause _ = False
let fragmentClass = case slideVariant of
RevealJsSlides -> "fragment"
_ -> "incremental"
let inDiv' zs = RawBlock (Format "html") ("<div class=\""
<> fragmentClass <> "\">") :
(zs ++ [RawBlock (Format "html") "</div>"])
let breakOnPauses zs = case splitBy isPause zs of
[] -> []
y:ys -> y ++ concatMap inDiv' ys
let (titleBlocks, innerSecs) =
if titleSlide
-- title slides have no content of their own
then let (as, bs) = break isSec xs
in (breakOnPauses as, bs)
else ([], breakOnPauses xs)
let secttag = if html5
then H5.section
else H.div
titleContents <- blockListToHtml opts titleBlocks
inSection <- gets stInSection
innerContents <- do
modify $ \st -> st{ stInSection = True }
res <- blockListToHtml opts innerSecs
modify $ \st -> st{ stInSection = inSection }
return res
let classes' = ordNub $
["title-slide" | titleSlide] ++ ["slide" | slide] ++
["section" | (slide || writerSectionDivs opts) &&
not html5 ] ++
["level" <> tshow level | slide || writerSectionDivs opts ]
<> [d | d <- dclasses,
slideVariant /= RevealJsSlides ||
d /= "r-fit-text"] -- see #5965
let attr = (ident, classes', dkvs)
if titleSlide
then do
t <- addAttrs opts attr $
secttag $ nl <> header' <> nl <> titleContents <> nl
-- ensure 2D nesting for revealjs, but only for one level;
-- revealjs doesn't like more than one level of nesting
return $
if slideVariant == RevealJsSlides && not inSection &&
not (null innerSecs)
then H5.section (nl <> t <> nl <> innerContents)
else t <> nl <> if null innerSecs
then mempty
else innerContents <> nl
else if writerSectionDivs opts || slide ||
(hident /= ident && not (T.null hident || T.null ident)) ||
(hclasses /= dclasses) || (hkvs /= dkvs)
then addAttrs opts attr
$ secttag
$ nl <> header' <> nl <>
if null innerSecs
then mempty
else innerContents <> nl
else do
let attr' = (ident, classes' \\ hclasses, dkvs \\ hkvs)
t <- addAttrs opts attr' header'
return $ t <>
if null innerSecs
then mempty
else nl <> innerContents
blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do
html5 <- gets stHtml5
slideVariant <- gets stSlideVariant
let isCslBibBody = ident == "refs" || "csl-bib-body" `elem` classes
when isCslBibBody $ modify $ \st -> st{ stCsl = True
, stCslEntrySpacing =
lookup "entry-spacing" kvs' >>=
safeRead }
let isCslBibEntry = "csl-entry" `elem` classes
let kvs = [(k,v) | (k,v) <- kvs'
, k /= "width" || "column" `notElem` classes] ++
[("style", "width:" <> w <> ";") | "column" `elem` classes
, ("width", w) <- kvs'] ++
[("role", "doc-bibliography") | isCslBibBody && html5] ++
[("role", "doc-biblioentry") | isCslBibEntry && html5]
let speakerNotes = "notes" `elem` classes
-- we don't want incremental output inside speaker notes, see #1394
let opts' = if | speakerNotes -> opts{ writerIncremental = False }
| "incremental" `elem` classes -> opts{ writerIncremental = True }
| "nonincremental" `elem` classes -> opts{ writerIncremental = False }
| otherwise -> opts
-- we remove "incremental" and "nonincremental" if we're in a
-- slide presentaiton format.
classes' = case slideVariant of
NoSlides -> classes
_ -> filter (\k -> k /= "incremental" && k /= "nonincremental") classes
let paraToPlain (Para ils) = Plain ils
paraToPlain x = x
let bs' = if "csl-entry" `elem` classes'
then walk paraToPlain bs
else bs
contents <- if "columns" `elem` classes'
then -- we don't use blockListToHtml because it inserts
-- a newline between the column divs, which throws
-- off widths! see #4028
mconcat <$> mapM (blockToHtml opts) bs'
else blockListToHtml opts' bs'
let contents' = nl >> contents >> nl
let (divtag, classes'') = if html5 && "section" `elem` classes'
then (H5.section, filter (/= "section") classes')
else (H.div, classes')
if speakerNotes
then case slideVariant of
RevealJsSlides -> addAttrs opts' attr $
H5.aside contents'
DZSlides -> do
t <- addAttrs opts' attr $
H5.div contents'
return $ t ! H5.customAttribute "role" "note"
NoSlides -> addAttrs opts' attr $
H.div contents'
_ -> return mempty
else addAttrs opts (ident, classes'', kvs) $
divtag contents'
blockToHtmlInner opts (RawBlock f str) = do
ishtml <- isRawHtml f
if ishtml
then return $ preEscapedText str
else if (f == Format "latex" || f == Format "tex") &&
allowsMathEnvironments (writerHTMLMathMethod opts) &&
isMathEnvironment str
then blockToHtml opts $ Plain [Math DisplayMath str]
else do
report $ BlockNotRendered (RawBlock f str)
return mempty
blockToHtmlInner _ HorizontalRule = do
html5 <- gets stHtml5
return $ if html5 then H5.hr else H.hr
blockToHtmlInner opts (CodeBlock (id',classes,keyvals) rawCode) = do
id'' <- if T.null id'
then do
modify $ \st -> st{ stCodeBlockNum = stCodeBlockNum st + 1 }
codeblocknum <- gets stCodeBlockNum
return (writerIdentifierPrefix opts <> "cb" <> tshow codeblocknum)
else return (writerIdentifierPrefix opts <> id')
let tolhs = isEnabled Ext_literate_haskell opts &&
any (\c -> T.toLower c == "haskell") classes &&
any (\c -> T.toLower c == "literate") classes
classes' = if tolhs
then map (\c -> if T.toLower c == "haskell"
then "literatehaskell"
else c) classes
else classes
adjCode = if tolhs
then T.unlines . map ("> " <>) . T.lines $ rawCode
else rawCode
hlCode = if isJust (writerHighlightStyle opts)
then highlight (writerSyntaxMap opts) formatHtmlBlock
(id'',classes',keyvals) adjCode
else Left ""
case hlCode of
Left msg -> do
unless (T.null msg) $
report $ CouldNotHighlight msg
addAttrs opts (id',classes,keyvals)
$ H.pre $ H.code $ toHtml adjCode
Right h -> modify (\st -> st{ stHighlighting = True }) >>
-- we set writerIdentifierPrefix to "" since id'' already
-- includes it:
addAttrs opts{writerIdentifierPrefix = ""} (id'',[],keyvals) h
blockToHtmlInner opts (BlockQuote blocks) = do
-- in S5, treat list in blockquote specially
-- if default is incremental, make it nonincremental;
-- otherwise incremental
slideVariant <- gets stSlideVariant
if slideVariant /= NoSlides
then let inc = not (writerIncremental opts) in
case blocks of
[BulletList lst] -> blockToHtml (opts {writerIncremental = inc})
(BulletList lst)
[OrderedList attribs lst] ->
blockToHtml (opts {writerIncremental = inc})
(OrderedList attribs lst)
[DefinitionList lst] ->
blockToHtml (opts {writerIncremental = inc})
(DefinitionList lst)
_ -> do contents <- blockListToHtml opts blocks
return $ H.blockquote
$ nl >> contents >> nl
else do
contents <- blockListToHtml opts blocks
return $ H.blockquote $ nl >> contents >> nl
blockToHtmlInner opts (Header level (ident,classes,kvs) lst) = do
contents <- inlineListToHtml opts lst
let secnum = fromMaybe mempty $ lookup "number" kvs
let contents' = if writerNumberSections opts && not (T.null secnum)
&& "unnumbered" `notElem` classes
then (H.span ! A.class_ "header-section-number"
$ toHtml secnum) >> strToHtml " " >> contents
else contents
html5 <- gets stHtml5
let kvs' = if html5
then kvs
else [ (k, v) | (k, v) <- kvs
, k `elem` (["lang", "dir", "title", "style"
, "align"] ++ intrinsicEventsHTML4)]
addAttrs opts (ident,classes,kvs')
$ case level of
1 -> H.h1 contents'
2 -> H.h2 contents'
3 -> H.h3 contents'
4 -> H.h4 contents'
5 -> H.h5 contents'
6 -> H.h6 contents'
_ -> H.p ! A.class_ "heading" $ contents'