Skip to content
Snippets Groups Projects
Commit 1de86e8a authored by waern's avatar waern
Browse files

Naming wibbles

parent d5ec9853
No related branches found
No related tags found
No related merge requests found
......@@ -20,13 +20,13 @@ module Haddock.Options (
optContentsUrl,
optIndexUrl,
optCssFile,
optSourceUrls,
optWikiUrls,
sourceUrls,
wikiUrls,
optDumpInterfaceFile,
optLaTeXStyle,
verbosity,
ghcFlags,
ifaceTriples
readIfaceArgs
) where
......@@ -196,15 +196,15 @@ optCssFile :: [Flag] -> Maybe FilePath
optCssFile flags = optLast [ str | Flag_CSS str <- flags ]
optSourceUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String)
optSourceUrls flags =
sourceUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String)
sourceUrls flags =
(listToMaybe [str | Flag_SourceBaseURL str <- flags]
,listToMaybe [str | Flag_SourceModuleURL str <- flags]
,listToMaybe [str | Flag_SourceEntityURL str <- flags])
optWikiUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String)
optWikiUrls flags =
wikiUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String)
wikiUrls flags =
(listToMaybe [str | Flag_WikiBaseURL str <- flags]
,listToMaybe [str | Flag_WikiModuleURL str <- flags]
,listToMaybe [str | Flag_WikiEntityURL str <- flags])
......@@ -217,6 +217,7 @@ optDumpInterfaceFile flags = optLast [ str | Flag_DumpInterface str <- flags ]
optLaTeXStyle :: [Flag] -> Maybe String
optLaTeXStyle flags = optLast [ str | Flag_LaTeXStyle str <- flags ]
verbosity :: [Flag] -> Verbosity
verbosity flags =
case [ str | Flag_Verbosity str <- flags ] of
......@@ -230,8 +231,8 @@ ghcFlags :: [Flag] -> [String]
ghcFlags flags = [ option | Flag_OptGhc option <- flags ]
ifaceTriples :: [Flag] -> [(DocPaths, FilePath)]
ifaceTriples flags = [ parseIfaceOption s | Flag_ReadInterface s <- flags ]
readIfaceArgs :: [Flag] -> [(DocPaths, FilePath)]
readIfaceArgs flags = [ parseIfaceOption s | Flag_ReadInterface s <- flags ]
where
parseIfaceOption :: String -> (DocPaths, FilePath)
parseIfaceOption str =
......
......@@ -141,7 +141,7 @@ main = handleTopExceptions $ do
throwE "No input file(s)."
-- Get packages supplied with --read-interface.
packages <- readInterfaceFiles freshNameCache (ifaceTriples flags)
packages <- readInterfaceFiles freshNameCache (readIfaceArgs flags)
-- Render even though there are no input files (usually contents/index).
renderStep flags packages []
......@@ -161,7 +161,7 @@ readPackagesAndProcessModules flags files = do
withGhc libDir (ghcFlags flags) $ \_ -> handleSrcErrors $ do
-- Get packages supplied with --read-interface.
packages <- readInterfaceFiles nameCacheFromGhc (ifaceTriples flags)
packages <- readInterfaceFiles nameCacheFromGhc (readIfaceArgs flags)
-- Create the interfaces -- this is the core part of Haddock.
let ifaceFiles = map snd packages
......@@ -187,7 +187,7 @@ render flags ifaces installedIfaces srcMap = do
let
title = fromMaybe "" (optTitle flags)
unicode = Flag_UseUnicode `elem` flags
opt_wiki_urls = optWikiUrls flags
opt_wiki_urls = wikiUrls flags
opt_contents_url = optContentsUrl flags
opt_index_url = optIndexUrl flags
odir = outputDir flags
......@@ -204,9 +204,9 @@ render flags ifaces installedIfaces srcMap = do
pkgStr = Just (packageIdString pkgId)
(pkgName,pkgVer) = modulePackageInfo pkgMod
(src_base, src_module, src_entity) = optSourceUrls flags
srcMap' = maybe srcMap (\path -> Map.insert pkgId path srcMap) src_entity
sourceUrls = (src_base, src_module, srcMap')
(srcBase, srcModule, srcEntity) = sourceUrls flags
srcMap' = maybe srcMap (\path -> Map.insert pkgId path srcMap) srcEntity
sourceUrls' = (srcBase, srcModule, srcMap')
libDir <- getHaddockLibDir flags
prologue <- getPrologue flags
......@@ -214,20 +214,20 @@ render flags ifaces installedIfaces srcMap = do
when (Flag_GenIndex `elem` flags) $ do
ppHtmlIndex odir title pkgStr
themes opt_contents_url sourceUrls opt_wiki_urls
themes opt_contents_url sourceUrls' opt_wiki_urls
allVisibleIfaces
copyHtmlBits odir libDir themes
when (Flag_GenContents `elem` flags) $ do
ppHtmlContents odir title pkgStr
themes opt_index_url sourceUrls opt_wiki_urls
themes opt_index_url sourceUrls' opt_wiki_urls
allVisibleIfaces True prologue
copyHtmlBits odir libDir themes
when (Flag_Html `elem` flags) $ do
ppHtml title pkgStr visibleIfaces odir
prologue
themes sourceUrls opt_wiki_urls
themes sourceUrls' opt_wiki_urls
opt_contents_url opt_index_url unicode
copyHtmlBits odir libDir themes
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment