[commit: haddock] ghc-head, master, wip/revert-ttg-2017-11-20, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13: Put Quickjump behind --quickjump flag (#697) (0f181c4)

git at git.haskell.org git at git.haskell.org
Mon Nov 20 21:11:42 UTC 2017


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

On branches: ghc-head,master,wip/revert-ttg-2017-11-20,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/0f181c4a70ef5e4753545cd9e0734a015bb815e1

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

commit 0f181c4a70ef5e4753545cd9e0734a015bb815e1
Author: Alexander Biehl <alexbiehl at gmail.com>
Date:   Mon Oct 30 10:15:49 2017 +0100

    Put Quickjump behind --quickjump flag (#697)


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

0f181c4a70ef5e4753545cd9e0734a015bb815e1
 haddock-api/src/Haddock.hs                     | 12 +++++++-----
 haddock-api/src/Haddock/Backends/Xhtml.hs      | 19 +++++++++++--------
 haddock-api/src/Haddock/Backends/Xhtml/Meta.hs | 12 ++++++------
 haddock-api/src/Haddock/Options.hs             |  3 +++
 4 files changed, 27 insertions(+), 19 deletions(-)

diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index a46e58b..7b4b867 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -300,27 +300,29 @@ render dflags flags qual ifaces installedIfaces extSrcMap = do
   prologue <- getPrologue dflags' flags
   themes   <- getThemes libDir flags >>= either bye return
 
+  let withQuickjump = Flag_QuickJumpIndex `elem` flags
+
   when (Flag_GenIndex `elem` flags) $ do
     ppHtmlIndex odir title pkgStr
                 themes opt_mathjax opt_contents_url sourceUrls' opt_wiki_urls
                 allVisibleIfaces pretty
-    copyHtmlBits odir libDir themes
+    copyHtmlBits odir libDir themes withQuickjump
 
   when (Flag_GenContents `elem` flags) $ do
     ppHtmlContents dflags' odir title pkgStr
                    themes opt_mathjax opt_index_url sourceUrls' opt_wiki_urls
                    allVisibleIfaces True prologue pretty
                    (makeContentsQual qual)
-    copyHtmlBits odir libDir themes
+    copyHtmlBits odir libDir themes withQuickjump
 
   when (Flag_Html `elem` flags) $ do
     ppHtml dflags' title pkgStr visibleIfaces odir
                 prologue
                 themes opt_mathjax sourceUrls' opt_wiki_urls
                 opt_contents_url opt_index_url unicode qual
-                pretty
-    copyHtmlBits odir libDir themes
-    writeHaddockMeta odir
+                pretty withQuickjump
+    copyHtmlBits odir libDir themes withQuickjump
+    writeHaddockMeta odir withQuickjump
 
   -- TODO: we throw away Meta for both Hoogle and LaTeX right now,
   -- might want to fix that if/when these two get some work on them
diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs
index c76c0c8..8205f65 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml.hs
@@ -55,7 +55,6 @@ import Module
 -- * Generating HTML documentation
 --------------------------------------------------------------------------------
 
-
 ppHtml :: DynFlags
        -> String                       -- ^ Title
        -> Maybe String                 -- ^ Package
@@ -71,12 +70,13 @@ ppHtml :: DynFlags
        -> Bool                         -- ^ Whether to use unicode in output (--use-unicode)
        -> QualOption                   -- ^ How to qualify names
        -> Bool                         -- ^ Output pretty html (newlines and indenting)
+       -> Bool                         -- ^ Also write Quickjump index
        -> IO ()
 
 ppHtml dflags doctitle maybe_package ifaces odir prologue
         themes maybe_mathjax_url maybe_source_url maybe_wiki_url
         maybe_contents_url maybe_index_url unicode
-        qual debug =  do
+        qual debug withQuickjump =  do
   let
     visible_ifaces = filter visible ifaces
     visible i = OptHide `notElem` ifaceOptions i
@@ -92,24 +92,27 @@ ppHtml dflags doctitle maybe_package ifaces odir prologue
     ppHtmlIndex odir doctitle maybe_package
       themes maybe_mathjax_url maybe_contents_url maybe_source_url maybe_wiki_url
       (map toInstalledIface visible_ifaces) debug
-    ppJsonIndex odir maybe_source_url maybe_wiki_url unicode qual
-      visible_ifaces
+
+    when withQuickjump $
+      ppJsonIndex odir maybe_source_url maybe_wiki_url unicode qual
+        visible_ifaces
 
   mapM_ (ppHtmlModule odir doctitle themes
            maybe_mathjax_url maybe_source_url maybe_wiki_url
            maybe_contents_url maybe_index_url unicode qual debug) visible_ifaces
 
 
-copyHtmlBits :: FilePath -> FilePath -> Themes -> IO ()
-copyHtmlBits odir libdir themes = do
+copyHtmlBits :: FilePath -> FilePath -> Themes -> Bool -> IO ()
+copyHtmlBits odir libdir themes withQuickjump = do
   let
     libhtmldir = joinPath [libdir, "html"]
     copyCssFile f = copyFile f (combine odir (takeFileName f))
     copyLibFile f = copyFile (joinPath [libhtmldir, f]) (joinPath [odir, f])
   mapM_ copyCssFile (cssFiles themes)
-  copyCssFile (joinPath [libhtmldir, quickJumpCssFile])
   copyLibFile haddockJsFile
-  copyLibFile jsQuickJumpFile
+  when withQuickjump $ do
+    copyCssFile (joinPath [libhtmldir, quickJumpCssFile])
+    copyLibFile jsQuickJumpFile
   return ()
 
 
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Meta.hs b/haddock-api/src/Haddock/Backends/Xhtml/Meta.hs
index 5cf03ec..621bdd4 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Meta.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Meta.hs
@@ -15,14 +15,14 @@ quickjumpVersion = 1
 -- | Writes a json encoded file containing additional
 -- information about the generated documentation. This
 -- is useful for external tools (e.g. hackage).
-writeHaddockMeta :: FilePath -> IO ()
-writeHaddockMeta odir = do
+writeHaddockMeta :: FilePath -> Bool -> IO ()
+writeHaddockMeta odir withQuickjump = do
   let
     meta_json :: Value
-    meta_json = object [
-        "haddock_version"   .= String projectVersion
-      , "quickjump_version" .= quickjumpVersion
-      ]
+    meta_json = object (concat [
+        [ "haddock_version"   .= String projectVersion ]
+      , [ "quickjump_version" .= quickjumpVersion | withQuickjump ]
+      ])
 
   withFile (odir </> "meta.json") WriteMode $ \h ->
     hPutBuilder h (encodeToBuilder meta_json)
diff --git a/haddock-api/src/Haddock/Options.hs b/haddock-api/src/Haddock/Options.hs
index d73d1a7..59d2c8a 100644
--- a/haddock-api/src/Haddock/Options.hs
+++ b/haddock-api/src/Haddock/Options.hs
@@ -70,6 +70,7 @@ data Flag
   | Flag_WikiEntityURL String
   | Flag_LaTeX
   | Flag_LaTeXStyle String
+  | Flag_QuickJumpIndex
   | Flag_HyperlinkedSource
   | Flag_SourceCss String
   | Flag_Mathjax String
@@ -126,6 +127,8 @@ options backwardsCompat =
     Option ['U'] ["use-unicode"] (NoArg Flag_UseUnicode) "use Unicode in HTML output",
     Option []  ["hoogle"]     (NoArg Flag_Hoogle)
       "output for Hoogle; you may want --package-name and --package-version too",
+    Option [] ["quickjump"] (NoArg Flag_QuickJumpIndex)
+      "generate an index for interactive documentation navigation",
     Option [] ["hyperlinked-source"] (NoArg Flag_HyperlinkedSource)
       "generate highlighted and hyperlinked source code (for use with --html)",
     Option [] ["source-css"] (ReqArg Flag_SourceCss "FILE")



More information about the ghc-commits mailing list