Skip to content

Commit

Permalink
shut up -warning
Browse files Browse the repository at this point in the history
  • Loading branch information
ffaf1 committed Sep 8, 2022
1 parent 69248b9 commit 28948e9
Showing 1 changed file with 19 additions and 26 deletions.
45 changes: 19 additions & 26 deletions Cabal/src/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1008,23 +1008,23 @@ checkP :: Monad m => Bool -> PackageCheck -> CheckM m ()
checkP b ck = do pb <- asksCM (ciPureChecks . ccInterface)
when pb (check b ck)

-- Check with 'CheckPreDistributionOps' operations (operations on work
-- tree files outside of what specified in the .cabal manifest).
checkPre :: forall m. Monad m => (CheckPreDistributionOps m -> m Bool) ->
PackageCheck -> CheckM m ()
checkPre f ck = checkInt ciPreDistOps f ck
-- -- Check with 'CheckPreDistributionOps' operations (operations on work
-- -- tree files outside of what specified in the .cabal manifest).
-- checkPre :: forall m. Monad m => (CheckPreDistributionOps m -> m Bool) ->
-- PackageCheck -> CheckM m ()
-- checkPre f ck = checkInt ciPreDistOps f ck

-- As 'checkPre', but with PackageCheck depending on a monadic computation
-- too.
checkPreDep :: forall m. Monad m =>
(CheckPreDistributionOps m -> m (Maybe PackageCheck)) ->
CheckM m ()
checkPreDep mck = checkIntDep ciPreDistOps mck
-- -- As 'checkPre', but with PackageCheck depending on a monadic computation
-- -- too.
-- checkPreDep :: forall m. Monad m =>
-- (CheckPreDistributionOps m -> m (Maybe PackageCheck)) ->
-- CheckM m ()
-- checkPreDep mck = checkIntDep ciPreDistOps mck


-- Always succeeding 'checkPre'.
tellPre :: Monad m => PackageCheck -> CheckM m ()
tellPre ck = checkPre (const $ return True) ck
-- -- Always succeeding 'checkPre'.
-- tellPre :: Monad m => PackageCheck -> CheckM m ()
-- tellPre ck = checkPre (const $ return True) ck

-- Check with 'CheckPackageContentOps' operations (i.e. package file checks).
checkPkg :: forall m. Monad m => (CheckPackageContentOps m -> m Bool) ->
Expand Down Expand Up @@ -1439,8 +1439,8 @@ checkMissingVcsInfo :: Monad m => [SourceRepo] -> CheckM m ()
checkMissingVcsInfo rs =
let rdirs = concatMap repoTypeDirname knownRepoTypes
in checkPkg
(\ops -> do use <- or <$> traverse (doesDirectoryExist ops) rdirs
return (null rs && use))
(\ops -> do us <- or <$> traverse (doesDirectoryExist ops) rdirs
return (null rs && us))
(PackageDistSuspicious MissingSourceControl)
where
repoTypeDirname :: KnownRepoType -> [FilePath]
Expand Down Expand Up @@ -2202,9 +2202,6 @@ checkCustomField (n, _) =
-- * Package and distribution checks
-- ------------------------------------------------------------

checkFilesGPD :: Monad m => CheckM m ()
checkFilesGPD = undefined --withPackageContentOpsCheck $ \ops b pc ->

-- | Find a package description file in the given directory. Looks for
-- @.cabal@ files. Like 'Distribution.Simple.Utils.findPackageDesc',
-- but generalized over monads.
Expand Down Expand Up @@ -2247,11 +2244,11 @@ checkCabalFile pn = do
checkPkgDep
(\ops -> do ds <- findPackageDesc ops
case ds of
[d] -> let exp = unPackageName pn <.> "cabal" in
if takeFileName d /= exp
[d] -> let expd = unPackageName pn <.> "cabal" in
if takeFileName d /= expd
then return . Just $
PackageDistInexcusable $
(NotPackageName d exp)
(NotPackageName d expd)
else return Nothing
_ -> return Nothing)
-- ppExplanation (NotPackageName pdfile expectedCabalname) =
Expand Down Expand Up @@ -2721,10 +2718,6 @@ pd2gpd pd = gpd
checkConfiguredPackage :: PackageDescription -> [PackageCheck]
checkConfiguredPackage pd = checkPackage (pd2gpd pd)

checkXXXPROVA :: Bool -> PackageCheck -> Maybe PackageCheck
checkXXXPROVA False _ = Nothing
checkXXXPROVA True pc = Just pc

checkPackageFileNamesWithGlobXXX :: p -> [a]
checkPackageFileNamesWithGlobXXX _ = []

Expand Down

0 comments on commit 28948e9

Please sign in to comment.