Skip to content
Snippets Groups Projects
Commit a3457055 authored by Mikhail Glushenkov's avatar Mikhail Glushenkov
Browse files

Revert "Added checks to see if files and directories exist"

This reverts commit 1b930232.
parent f9e88b7c
No related branches found
No related tags found
No related merge requests found
...@@ -1383,36 +1383,30 @@ checkPackageContent :: Monad m => CheckPackageContentOps m ...@@ -1383,36 +1383,30 @@ checkPackageContent :: Monad m => CheckPackageContentOps m
-> PackageDescription -> PackageDescription
-> m [PackageCheck] -> m [PackageCheck]
checkPackageContent ops pkg = do checkPackageContent ops pkg = do
licenseErrors <- checkLicensesExist ops pkg
setupError <- checkSetupExists ops pkg setupError <- checkSetupExists ops pkg
configureError <- checkConfigureExists ops pkg configureError <- checkConfigureExists ops pkg
localPathErrors <- checkLocalPathsExist ops pkg localPathErrors <- checkLocalPathsExist ops pkg
vcsLocation <- checkMissingVcsInfo ops pkg vcsLocation <- checkMissingVcsInfo ops pkg
fileExistsError <- checkFilesExist ops pkg
return $ return $ licenseErrors
catMaybes [setupError, configureError] ++ catMaybes [setupError, configureError]
++ localPathErrors ++ localPathErrors
++ vcsLocation ++ vcsLocation
++ fileExistsError
checkLicensesExist :: Monad m => CheckPackageContentOps m
checkFilesExist :: Monad m => CheckPackageContentOps m -> PackageDescription
-> PackageDescription -> m [PackageCheck]
-> m [PackageCheck] checkLicensesExist ops pkg = do
checkFilesExist ops pkg = do exists <- mapM (doesFileExist ops) (licenseFiles pkg)
let filess = [ (files, kind) return
| (files, kind) <- [ PackageBuildWarning $
[ (files, "license-file") | files <- licenseFiles pkg ] "The '" ++ fieldname ++ "' field refers to the file "
++ [ (files, "extra-source-files") | files <- extraSrcFiles pkg ] ++ quote file ++ " which does not exist."
++ [ (files, "data-files") | files <- dataFiles pkg ] | (file, False) <- zip (licenseFiles pkg) exists ]
++ [ (files, "extra-doc-files") | files <- extraDocFiles pkg ] where
] fieldname | length (licenseFiles pkg) == 1 = "license-file"
| otherwise = "license-files"
missing <- filterM (liftM not . doesFileExist ops . fst) filess
return [ PackageBuildWarning {
explanation = quote (kind ++ ": " ++ file)
++ " file does not exist."
}
| (file, kind) <- missing ]
checkSetupExists :: Monad m => CheckPackageContentOps m checkSetupExists :: Monad m => CheckPackageContentOps m
-> PackageDescription -> PackageDescription
...@@ -1442,12 +1436,9 @@ checkLocalPathsExist ops pkg = do ...@@ -1442,12 +1436,9 @@ checkLocalPathsExist ops pkg = do
let dirs = [ (dir, kind) let dirs = [ (dir, kind)
| bi <- allBuildInfo pkg | bi <- allBuildInfo pkg
, (dir, kind) <- , (dir, kind) <-
[ (dir, "extra-lib-dirs") | dir <- extraLibDirs bi ] [ (dir, "extra-lib-dirs") | dir <- extraLibDirs bi ]
++ [ (dir, "include-dirs") | dir <- includeDirs bi ] ++ [ (dir, "include-dirs") | dir <- includeDirs bi ]
++ [ (dir, "hs-source-dirs") | dir <- hsSourceDirs bi ] ++ [ (dir, "hs-source-dirs") | dir <- hsSourceDirs bi ]
++ [ (dir, "c-sources") | dir <- cSources bi ]
++ [ (dir, "js-sources") | dir <- jsSources bi ]
, isRelative dir ] , isRelative dir ]
missing <- filterM (liftM not . doesDirectoryExist ops . fst) dirs missing <- filterM (liftM not . doesDirectoryExist ops . fst) dirs
return [ PackageBuildWarning { return [ PackageBuildWarning {
......
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