[commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13: Make sure --mathjax affects all written HTML files (89eac21)

git at git.haskell.org git at git.haskell.org
Mon Nov 20 20:59:45 UTC 2017


Repository : ssh://git@git.haskell.org/haddock

On branches: 2.17.3.1-spanfix,alexbiehl-patch-1,ghc-8.0,ghc-8.0-facebook,ghc-head,ghc-head1,haddock-quick,headdock-library-1.4.5,ie_avails,issue-303,issue-475,master,pr-filter-maps,pr/cabal-desc,travis,v2.17,v2.17.3,v2.18,wip-located-module-as,wip/D2418,wip/T12105,wip/T12105-2,wip/T12942,wip/T13163,wip/T3384,wip/embelleshed-rdr,wip/new-tree-one-param,wip/rae,wip/remove-frames,wip/remove-frames1,wip/revert-ttg-2017-11-20,wip/ttg-2017-10-13,wip/ttg-2017-10-31,wip/ttg-2017-11-06,wip/ttg2-2017-11-10,wip/ttg3-2017-11-12,wip/ttg4-constraints-2017-11-13
Link       : http://git.haskell.org/haddock.git/commitdiff/89eac211dbe062b18e3bc25dd4317d4469078c77

>---------------------------------------------------------------

commit 89eac211dbe062b18e3bc25dd4317d4469078c77
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Jan 19 00:11:38 2016 +0100

    Make sure --mathjax affects all written HTML files
    
    This fixes #475.


>---------------------------------------------------------------

89eac211dbe062b18e3bc25dd4317d4469078c77
 haddock-api/src/Haddock.hs                |  2 +-
 haddock-api/src/Haddock/Backends/Xhtml.hs | 31 ++++++++++++++++---------------
 2 files changed, 17 insertions(+), 16 deletions(-)

diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index 72a6cc9..b119f06 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -292,7 +292,7 @@ render dflags flags qual ifaces installedIfaces extSrcMap = do
 
   when (Flag_GenIndex `elem` flags) $ do
     ppHtmlIndex odir title pkgStr
-                themes opt_contents_url sourceUrls' opt_wiki_urls
+                themes opt_mathjax opt_contents_url sourceUrls' opt_wiki_urls
                 allVisibleIfaces pretty
     copyHtmlBits odir libDir themes
 
diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs
index ebd5337..f728406 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml.hs
@@ -90,11 +90,11 @@ ppHtml dflags doctitle maybe_package ifaces odir prologue
 
   when (isNothing maybe_index_url) $
     ppHtmlIndex odir doctitle maybe_package
-      themes maybe_contents_url maybe_source_url maybe_wiki_url
+      themes maybe_mathjax_url maybe_contents_url maybe_source_url maybe_wiki_url
       (map toInstalledIface visible_ifaces) debug
 
   mapM_ (ppHtmlModule odir doctitle themes
-           maybe_source_url maybe_wiki_url
+           maybe_mathjax_url maybe_source_url maybe_wiki_url
            maybe_contents_url maybe_index_url unicode qual debug) visible_ifaces
 
 
@@ -269,7 +269,7 @@ ppHtmlContents dflags odir doctitle _maybe_package
   writeFile (joinPath [odir, contentsHtmlFile]) (renderToString debug html)
 
   -- XXX: think of a better place for this?
-  ppHtmlContentsFrame odir doctitle themes ifaces debug
+  ppHtmlContentsFrame odir doctitle themes mathjax_url ifaces debug
 
 
 ppPrologue :: Qualification -> String -> Maybe (MDoc GHC.RdrName) -> Html
@@ -342,12 +342,12 @@ flatModuleTree ifaces =
         << toHtml txt
 
 
-ppHtmlContentsFrame :: FilePath -> String -> Themes
+ppHtmlContentsFrame :: FilePath -> String -> Themes -> Maybe String
   -> [InstalledInterface] -> Bool -> IO ()
-ppHtmlContentsFrame odir doctitle themes ifaces debug = do
+ppHtmlContentsFrame odir doctitle themes maybe_mathjax_url ifaces debug = do
   let mods = flatModuleTree ifaces
       html =
-        headHtml doctitle Nothing themes Nothing +++
+        headHtml doctitle Nothing themes maybe_mathjax_url +++
         miniBody << divModuleList <<
           (sectionName << "Modules" +++
            ulist << [ li ! [theclass "module"] << m | m <- mods ])
@@ -365,13 +365,14 @@ ppHtmlIndex :: FilePath
             -> Maybe String
             -> Themes
             -> Maybe String
+            -> Maybe String
             -> SourceURLs
             -> WikiURLs
             -> [InstalledInterface]
             -> Bool
             -> IO ()
 ppHtmlIndex odir doctitle _maybe_package themes
-  maybe_contents_url maybe_source_url maybe_wiki_url ifaces debug = do
+  maybe_mathjax_url maybe_contents_url maybe_source_url maybe_wiki_url ifaces debug = do
   let html = indexPage split_indices Nothing
               (if split_indices then [] else index)
 
@@ -387,7 +388,7 @@ ppHtmlIndex odir doctitle _maybe_package themes
 
   where
     indexPage showLetters ch items =
-      headHtml (doctitle ++ " (" ++ indexName ch ++ ")") Nothing themes Nothing +++
+      headHtml (doctitle ++ " (" ++ indexName ch ++ ")") Nothing themes maybe_mathjax_url +++
       bodyHtml doctitle Nothing
         maybe_source_url maybe_wiki_url
         maybe_contents_url Nothing << [
@@ -487,11 +488,11 @@ ppHtmlIndex odir doctitle _maybe_package themes
 
 ppHtmlModule
         :: FilePath -> String -> Themes
-        -> SourceURLs -> WikiURLs
+        -> Maybe String -> SourceURLs -> WikiURLs
         -> Maybe String -> Maybe String -> Bool -> QualOption
         -> Bool -> Interface -> IO ()
 ppHtmlModule odir doctitle themes
-  maybe_source_url maybe_wiki_url
+  maybe_mathjax_url maybe_source_url maybe_wiki_url
   maybe_contents_url maybe_index_url unicode qual debug iface = do
   let
       mdl = ifaceMod iface
@@ -499,7 +500,7 @@ ppHtmlModule odir doctitle themes
       mdl_str = moduleString mdl
       real_qual = makeModuleQual qual aliases mdl
       html =
-        headHtml mdl_str (Just $ "mini_" ++ moduleHtmlFile mdl) themes Nothing +++
+        headHtml mdl_str (Just $ "mini_" ++ moduleHtmlFile mdl) themes maybe_mathjax_url +++
         bodyHtml doctitle (Just iface)
           maybe_source_url maybe_wiki_url
           maybe_contents_url maybe_index_url << [
@@ -509,14 +510,14 @@ ppHtmlModule odir doctitle themes
 
   createDirectoryIfMissing True odir
   writeFile (joinPath [odir, moduleHtmlFile mdl]) (renderToString debug html)
-  ppHtmlModuleMiniSynopsis odir doctitle themes iface unicode real_qual debug
+  ppHtmlModuleMiniSynopsis odir doctitle themes maybe_mathjax_url iface unicode real_qual debug
 
 ppHtmlModuleMiniSynopsis :: FilePath -> String -> Themes
-  -> Interface -> Bool -> Qualification -> Bool -> IO ()
-ppHtmlModuleMiniSynopsis odir _doctitle themes iface unicode qual debug = do
+  -> Maybe String -> Interface -> Bool -> Qualification -> Bool -> IO ()
+ppHtmlModuleMiniSynopsis odir _doctitle themes maybe_mathjax_url iface unicode qual debug = do
   let mdl = ifaceMod iface
       html =
-        headHtml (moduleString mdl) Nothing themes Nothing +++
+        headHtml (moduleString mdl) Nothing themes maybe_mathjax_url +++
         miniBody <<
           (divModuleHeader << sectionName << moduleString mdl +++
            miniSynopsis mdl iface unicode qual)



More information about the ghc-commits mailing list