{-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE StandaloneDeriving #-} import Control.Applicative import Control.Monad import Data.Maybe import Data.List import Distribution.InstalledPackageInfo import Distribution.Package import Distribution.Simple.Compiler hiding (Flag) import Distribution.Simple.GHC import Distribution.Simple.PackageIndex import Distribution.Simple.Program import Distribution.Simple.Utils import Distribution.Verbosity import System.Console.GetOpt import System.Directory import System.Environment import System.Exit import System.FilePath import System.IO import System.Process import qualified Text.XML.Light as Xml import Test.Haddock.Process import Test.Haddock.Config import Test.Haddock.Xhtml baseDir, rootDir :: FilePath baseDir = takeDirectory __FILE__ rootDir = baseDir ".." srcDir, refDir, outDir :: FilePath srcDir = baseDir "src" refDir = baseDir "ref" outDir = baseDir "out" resDir :: FilePath resDir = rootDir "resources" data CheckResult = Fail | Pass | NoRef main :: IO () main = do cfg <- uncurry loadConfig =<< checkOpt =<< getArgs runHaddock cfg checkFiles cfg checkFiles :: Config -> IO () checkFiles (Config { .. }) = do putStrLn "Testing output files..." failed <- liftM catMaybes . forM cfgFiles $ \file -> do let mdl = takeBaseName file putStr $ "Checking " ++ mdl ++ "... " status <- checkModule mdl case status of Fail -> putStrLn "FAIL" >> (return $ Just mdl) Pass -> putStrLn "PASS" >> (return Nothing) NoRef -> putStrLn "PASS [no .ref]" >> (return Nothing) if null failed then do putStrLn "All tests passed!" exitSuccess else do maybeDiff cfgDiffTool failed exitFailure maybeDiff :: Maybe FilePath -> [String] -> IO () maybeDiff Nothing _ = pure () maybeDiff (Just diff) mdls = do putStrLn "Diffing failed cases..." forM_ mdls $ diffModule diff runHaddock :: Config -> IO () runHaddock (Config { .. }) = do putStrLn "Running Haddock process..." haddockStdOut <- openFile cfgHaddockStdOut WriteMode handle <- runProcess' cfgHaddockPath $ processConfig { pcArgs = cfgHaddockArgs ++ cfgFiles , pcEnv = Just $ cfgEnv , pcStdOut = Just $ haddockStdOut } waitForSuccess "Failed to run Haddock on specified test files" handle checkOpt :: [String] -> IO ([Flag], [String]) checkOpt args = do let (flags, files, errors) = getOpt Permute options args unless (null errors) $ do hPutStr stderr $ concat errors exitFailure when (FlagHelp `elem` flags) $ do hPutStrLn stderr $ usageInfo "" options exitSuccess return (flags, files) loadConfig :: [Flag] -> [String] -> IO Config loadConfig flags files = do cfgEnv <- (:) ("haddock_datadir", resDir) <$> getEnvironment cfgHaddockPath <- pure $ flip fromMaybe (flagsHaddockPath flags) $ rootDir "dist" "build" "haddock" "haddock" printVersions cfgEnv cfgHaddockPath cfgGhcPath <- flip fromMaybe (flagsGhcPath flags) <$> init <$> rawSystemStdout normal cfgHaddockPath ["--print-ghc-path"] cfgFiles <- processFileArgs files cfgHaddockArgs <- liftM concat . sequence $ [ pure ["--no-warnings"] , pure ["--odir=" ++ outDir] , pure ["--pretty-html"] , pure ["--html"] , pure ["--optghc=-w"] , pure $ flagsHaddockOptions flags , baseDependencies cfgGhcPath ] let cfgHaddockStdOut = fromMaybe "/dev/null" (flagsHaddockStdOut flags) cfgDiffTool <- if FlagNoDiff `elem` flags then pure Nothing else (<|>) <$> pure (flagsDiffTool flags) <*> defaultDiffTool return $ Config { .. } checkModule :: String -> IO CheckResult checkModule mdl = do hasRef <- doesFileExist $ refFile mdl if hasRef then do Just outXml <- readXml $ outFile mdl Just refXml <- readXml $ refFile mdl return $ if strip outXml == strip refXml then Pass else Fail else return NoRef diffModule :: FilePath -> String -> IO () diffModule diff mdl = do Just outXml <- readXml $ outFile mdl Just refXml <- readXml $ refFile mdl let outXml' = strip outXml let refXml' = strip refXml writeFile outFile' $ Xml.ppElement outXml' writeFile refFile' $ Xml.ppElement refXml' putStrLn $ "Diff for module " ++ show mdl ++ ":" hFlush stdout handle <- runProcess' diff $ processConfig { pcArgs = [outFile', refFile'] , pcStdOut = Just $ stdout } waitForProcess handle >> return () where outFile' = outFile mdl <.> "nolinks" refFile' = outFile mdl <.> "ref" <.> "nolinks" outFile :: String -> FilePath outFile mdl = outDir mdl <.> "html" refFile :: String -> FilePath refFile mdl = refDir mdl <.> "html" printVersions :: Environment -> FilePath -> IO () printVersions env haddockPath = do handle <- runProcess' haddockPath $ processConfig { pcEnv = Just env , pcArgs = ["--version"] } waitForSuccess "Failed to run `haddock --version`" handle handle <- runProcess' haddockPath $ processConfig { pcEnv = Just env , pcArgs = ["--ghc-version"] } waitForSuccess "Failed to run `haddock --ghc-version`" handle baseDependencies :: FilePath -> IO [String] baseDependencies ghcPath = do (_, _, cfg) <- configure normal (Just ghcPath) Nothing defaultProgramConfiguration pkgIndex <- getInstalledPackages normal [GlobalPackageDB] cfg mapM (getDependency pkgIndex) ["base", "process", "ghc-prim"] where getDependency pkgIndex name = case ifaces pkgIndex name of [] -> do hPutStrLn stderr $ "Couldn't find base test dependency: " ++ name exitFailure (ifArg:_) -> pure ifArg ifaces pkgIndex name = do pkg <- join $ snd <$> lookupPackageName pkgIndex (PackageName name) iface <$> haddockInterfaces pkg <*> haddockHTMLs pkg iface file html = "--read-interface=" ++ html ++ "," ++ file defaultDiffTool :: IO (Maybe FilePath) defaultDiffTool = liftM listToMaybe . filterM isAvailable $ ["colordiff", "diff"] where isAvailable = liftM isJust . findProgramLocation silent processFileArgs :: [String] -> IO [FilePath] processFileArgs [] = map toModulePath . filter isSourceFile <$> getDirectoryContents srcDir where toModulePath = modulePath . takeBaseName processFileArgs args = pure $ map processFileArg args processFileArg :: String -> FilePath processFileArg arg | isSourceFile arg = arg | otherwise = modulePath arg isSourceFile :: FilePath -> Bool isSourceFile path = takeExtension path `elem` [".hs", ".lhs"] modulePath :: String -> FilePath modulePath mdl = srcDir mdl <.> "hs" -- *** OLD TEST RUNNER UTILITY FUNCTIONS *** -- These are considered bad and should be replaced as soon as possible. -- | List of modules in which we don't 'stripLinks' preserveLinksModules :: [String] preserveLinksModules = ["Bug253"]