{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.PackageDescription.Check.Monad
(
CheckM (..)
, execCheckM
, CheckInterface (..)
, CheckPackageContentOps (..)
, CheckPreDistributionOps (..)
, TargetAnnotation (..)
, PackageCheck (..)
, CheckExplanation (..)
, CEType (..)
, WarnLang (..)
, CheckCtx (..)
, pristineCheckCtx
, initCheckCtx
, PNames (..)
, ppPackageCheck
, isHackageDistError
, asksCM
, localCM
, checkP
, checkPkg
, liftInt
, tellP
, checkSpecVer
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion (CabalSpecVersion)
import Distribution.Package (packageName)
import Distribution.PackageDescription.Check.Warning
import Distribution.Simple.BuildToolDepends (desugarBuildToolSimple)
import Distribution.Simple.Glob (Glob, GlobResult)
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.GenericPackageDescription
import Distribution.Types.LegacyExeDependency (LegacyExeDependency)
import Distribution.Types.PackageDescription (package, specVersion)
import Distribution.Types.PackageId (PackageIdentifier)
import Distribution.Types.UnqualComponentName
import qualified Control.Monad.Reader as Reader
import qualified Control.Monad.Trans.Class as Trans
import qualified Control.Monad.Writer as Writer
import qualified Data.ByteString.Lazy as BS
import qualified Data.Set as Set
import Control.Monad
data CheckInterface m = CheckInterface
{ forall (m :: * -> *). CheckInterface m -> Bool
ciPureChecks :: Bool
,
forall (m :: * -> *).
CheckInterface m -> Maybe (CheckPackageContentOps m)
ciPackageOps :: Maybe (CheckPackageContentOps m)
,
forall (m :: * -> *).
CheckInterface m -> Maybe (CheckPreDistributionOps m)
ciPreDistOps :: Maybe (CheckPreDistributionOps m)
}
data CheckPackageContentOps m = CheckPackageContentOps
{ forall (m :: * -> *).
CheckPackageContentOps m -> FilePath -> m Bool
doesFileExist :: FilePath -> m Bool
, forall (m :: * -> *).
CheckPackageContentOps m -> FilePath -> m Bool
doesDirectoryExist :: FilePath -> m Bool
, forall (m :: * -> *).
CheckPackageContentOps m -> FilePath -> m [FilePath]
getDirectoryContents :: FilePath -> m [FilePath]
, forall (m :: * -> *).
CheckPackageContentOps m -> FilePath -> m ByteString
getFileContents :: FilePath -> m BS.ByteString
}
data CheckPreDistributionOps m = CheckPreDistributionOps
{ forall (m :: * -> *).
CheckPreDistributionOps m
-> FilePath -> Glob -> m [GlobResult FilePath]
runDirFileGlobM :: FilePath -> Glob -> m [GlobResult FilePath]
, forall (m :: * -> *).
CheckPreDistributionOps m -> FilePath -> m [FilePath]
getDirectoryContentsM :: FilePath -> m [FilePath]
}
data CheckCtx m = CheckCtx
{ forall (m :: * -> *). CheckCtx m -> CheckInterface m
ccInterface :: CheckInterface m
,
forall (m :: * -> *). CheckCtx m -> Bool
ccFlag :: Bool
,
forall (m :: * -> *). CheckCtx m -> CabalSpecVersion
ccSpecVersion :: CabalSpecVersion
,
forall (m :: * -> *).
CheckCtx m -> LegacyExeDependency -> Maybe ExeDependency
ccDesugar :: LegacyExeDependency -> Maybe ExeDependency
,
forall (m :: * -> *). CheckCtx m -> PNames
ccNames :: PNames
}
pristineCheckCtx
:: Monad m
=> CheckInterface m
-> GenericPackageDescription
-> CheckCtx m
pristineCheckCtx :: forall (m :: * -> *).
Monad m =>
CheckInterface m -> GenericPackageDescription -> CheckCtx m
pristineCheckCtx CheckInterface m
ci GenericPackageDescription
gpd =
let ens :: [UnqualComponentName]
ens = ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> UnqualComponentName)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> UnqualComponentName
forall a b. (a, b) -> a
fst (GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condExecutables GenericPackageDescription
gpd)
in CheckInterface m
-> Bool
-> CabalSpecVersion
-> (LegacyExeDependency -> Maybe ExeDependency)
-> PNames
-> CheckCtx m
forall (m :: * -> *).
CheckInterface m
-> Bool
-> CabalSpecVersion
-> (LegacyExeDependency -> Maybe ExeDependency)
-> PNames
-> CheckCtx m
CheckCtx
CheckInterface m
ci
Bool
False
(PackageDescription -> CabalSpecVersion
specVersion (PackageDescription -> CabalSpecVersion)
-> (GenericPackageDescription -> PackageDescription)
-> GenericPackageDescription
-> CabalSpecVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericPackageDescription -> PackageDescription
packageDescription (GenericPackageDescription -> CabalSpecVersion)
-> GenericPackageDescription -> CabalSpecVersion
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
gpd)
(PackageName
-> [UnqualComponentName]
-> LegacyExeDependency
-> Maybe ExeDependency
desugarBuildToolSimple (GenericPackageDescription -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName GenericPackageDescription
gpd) [UnqualComponentName]
ens)
(GenericPackageDescription -> PNames
initPNames GenericPackageDescription
gpd)
initCheckCtx :: Monad m => TargetAnnotation a -> CheckCtx m -> CheckCtx m
initCheckCtx :: forall (m :: * -> *) a.
Monad m =>
TargetAnnotation a -> CheckCtx m -> CheckCtx m
initCheckCtx TargetAnnotation a
t CheckCtx m
c = CheckCtx m
c{ccFlag = taPackageFlag t}
data TargetAnnotation a = TargetAnnotation
{ forall a. TargetAnnotation a -> a
taTarget :: a
,
forall a. TargetAnnotation a -> Bool
taPackageFlag :: Bool
}
deriving (Int -> TargetAnnotation a -> ShowS
[TargetAnnotation a] -> ShowS
TargetAnnotation a -> FilePath
(Int -> TargetAnnotation a -> ShowS)
-> (TargetAnnotation a -> FilePath)
-> ([TargetAnnotation a] -> ShowS)
-> Show (TargetAnnotation a)
forall a. Show a => Int -> TargetAnnotation a -> ShowS
forall a. Show a => [TargetAnnotation a] -> ShowS
forall a. Show a => TargetAnnotation a -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> TargetAnnotation a -> ShowS
showsPrec :: Int -> TargetAnnotation a -> ShowS
$cshow :: forall a. Show a => TargetAnnotation a -> FilePath
show :: TargetAnnotation a -> FilePath
$cshowList :: forall a. Show a => [TargetAnnotation a] -> ShowS
showList :: [TargetAnnotation a] -> ShowS
Show, TargetAnnotation a -> TargetAnnotation a -> Bool
(TargetAnnotation a -> TargetAnnotation a -> Bool)
-> (TargetAnnotation a -> TargetAnnotation a -> Bool)
-> Eq (TargetAnnotation a)
forall a. Eq a => TargetAnnotation a -> TargetAnnotation a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => TargetAnnotation a -> TargetAnnotation a -> Bool
== :: TargetAnnotation a -> TargetAnnotation a -> Bool
$c/= :: forall a. Eq a => TargetAnnotation a -> TargetAnnotation a -> Bool
/= :: TargetAnnotation a -> TargetAnnotation a -> Bool
Eq, Eq (TargetAnnotation a)
Eq (TargetAnnotation a) =>
(TargetAnnotation a -> TargetAnnotation a -> Ordering)
-> (TargetAnnotation a -> TargetAnnotation a -> Bool)
-> (TargetAnnotation a -> TargetAnnotation a -> Bool)
-> (TargetAnnotation a -> TargetAnnotation a -> Bool)
-> (TargetAnnotation a -> TargetAnnotation a -> Bool)
-> (TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a)
-> (TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a)
-> Ord (TargetAnnotation a)
TargetAnnotation a -> TargetAnnotation a -> Bool
TargetAnnotation a -> TargetAnnotation a -> Ordering
TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (TargetAnnotation a)
forall a. Ord a => TargetAnnotation a -> TargetAnnotation a -> Bool
forall a.
Ord a =>
TargetAnnotation a -> TargetAnnotation a -> Ordering
forall a.
Ord a =>
TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
$ccompare :: forall a.
Ord a =>
TargetAnnotation a -> TargetAnnotation a -> Ordering
compare :: TargetAnnotation a -> TargetAnnotation a -> Ordering
$c< :: forall a. Ord a => TargetAnnotation a -> TargetAnnotation a -> Bool
< :: TargetAnnotation a -> TargetAnnotation a -> Bool
$c<= :: forall a. Ord a => TargetAnnotation a -> TargetAnnotation a -> Bool
<= :: TargetAnnotation a -> TargetAnnotation a -> Bool
$c> :: forall a. Ord a => TargetAnnotation a -> TargetAnnotation a -> Bool
> :: TargetAnnotation a -> TargetAnnotation a -> Bool
$c>= :: forall a. Ord a => TargetAnnotation a -> TargetAnnotation a -> Bool
>= :: TargetAnnotation a -> TargetAnnotation a -> Bool
$cmax :: forall a.
Ord a =>
TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
max :: TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
$cmin :: forall a.
Ord a =>
TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
min :: TargetAnnotation a -> TargetAnnotation a -> TargetAnnotation a
Ord)
data PNames = PNames
{ PNames -> PackageIdentifier
pnPackageId :: PackageIdentifier
, PNames -> [UnqualComponentName]
pnSubLibs :: [UnqualComponentName]
, PNames -> [UnqualComponentName]
pnExecs :: [UnqualComponentName]
, PNames -> [UnqualComponentName]
pnTests :: [UnqualComponentName]
, PNames -> [UnqualComponentName]
pnBenchs :: [UnqualComponentName]
}
initPNames :: GenericPackageDescription -> PNames
initPNames :: GenericPackageDescription -> PNames
initPNames GenericPackageDescription
gpd =
PackageIdentifier
-> [UnqualComponentName]
-> [UnqualComponentName]
-> [UnqualComponentName]
-> [UnqualComponentName]
-> PNames
PNames
(PackageDescription -> PackageIdentifier
package (PackageDescription -> PackageIdentifier)
-> (GenericPackageDescription -> PackageDescription)
-> GenericPackageDescription
-> PackageIdentifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericPackageDescription -> PackageDescription
packageDescription (GenericPackageDescription -> PackageIdentifier)
-> GenericPackageDescription -> PackageIdentifier
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
gpd)
(((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> UnqualComponentName)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> UnqualComponentName
forall a b. (a, b) -> a
fst ([(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [UnqualComponentName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [UnqualComponentName]
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries GenericPackageDescription
gpd)
(((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> UnqualComponentName)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> UnqualComponentName
forall a b. (a, b) -> a
fst ([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> [UnqualComponentName])
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [UnqualComponentName]
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condExecutables GenericPackageDescription
gpd)
(((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> UnqualComponentName)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> UnqualComponentName
forall a b. (a, b) -> a
fst ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [UnqualComponentName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [UnqualComponentName]
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites GenericPackageDescription
gpd)
(((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> UnqualComponentName)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> UnqualComponentName
forall a b. (a, b) -> a
fst ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [UnqualComponentName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [UnqualComponentName]
forall a b. (a -> b) -> a -> b
$ GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks GenericPackageDescription
gpd)
newtype CheckM m a
= CheckM
( Reader.ReaderT
(CheckCtx m)
( Writer.WriterT
(Set.Set PackageCheck)
m
)
a
)
deriving ((forall a b. (a -> b) -> CheckM m a -> CheckM m b)
-> (forall a b. a -> CheckM m b -> CheckM m a)
-> Functor (CheckM m)
forall a b. a -> CheckM m b -> CheckM m a
forall a b. (a -> b) -> CheckM m a -> CheckM m b
forall (m :: * -> *) a b.
Functor m =>
a -> CheckM m b -> CheckM m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> CheckM m a -> CheckM m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> CheckM m a -> CheckM m b
fmap :: forall a b. (a -> b) -> CheckM m a -> CheckM m b
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> CheckM m b -> CheckM m a
<$ :: forall a b. a -> CheckM m b -> CheckM m a
Functor, Functor (CheckM m)
Functor (CheckM m) =>
(forall a. a -> CheckM m a)
-> (forall a b. CheckM m (a -> b) -> CheckM m a -> CheckM m b)
-> (forall a b c.
(a -> b -> c) -> CheckM m a -> CheckM m b -> CheckM m c)
-> (forall a b. CheckM m a -> CheckM m b -> CheckM m b)
-> (forall a b. CheckM m a -> CheckM m b -> CheckM m a)
-> Applicative (CheckM m)
forall a. a -> CheckM m a
forall a b. CheckM m a -> CheckM m b -> CheckM m a
forall a b. CheckM m a -> CheckM m b -> CheckM m b
forall a b. CheckM m (a -> b) -> CheckM m a -> CheckM m b
forall a b c.
(a -> b -> c) -> CheckM m a -> CheckM m b -> CheckM m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *). Applicative m => Functor (CheckM m)
forall (m :: * -> *) a. Applicative m => a -> CheckM m a
forall (m :: * -> *) a b.
Applicative m =>
CheckM m a -> CheckM m b -> CheckM m a
forall (m :: * -> *) a b.
Applicative m =>
CheckM m a -> CheckM m b -> CheckM m b
forall (m :: * -> *) a b.
Applicative m =>
CheckM m (a -> b) -> CheckM m a -> CheckM m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> CheckM m a -> CheckM m b -> CheckM m c
$cpure :: forall (m :: * -> *) a. Applicative m => a -> CheckM m a
pure :: forall a. a -> CheckM m a
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
CheckM m (a -> b) -> CheckM m a -> CheckM m b
<*> :: forall a b. CheckM m (a -> b) -> CheckM m a -> CheckM m b
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> CheckM m a -> CheckM m b -> CheckM m c
liftA2 :: forall a b c.
(a -> b -> c) -> CheckM m a -> CheckM m b -> CheckM m c
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
CheckM m a -> CheckM m b -> CheckM m b
*> :: forall a b. CheckM m a -> CheckM m b -> CheckM m b
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
CheckM m a -> CheckM m b -> CheckM m a
<* :: forall a b. CheckM m a -> CheckM m b -> CheckM m a
Applicative, Applicative (CheckM m)
Applicative (CheckM m) =>
(forall a b. CheckM m a -> (a -> CheckM m b) -> CheckM m b)
-> (forall a b. CheckM m a -> CheckM m b -> CheckM m b)
-> (forall a. a -> CheckM m a)
-> Monad (CheckM m)
forall a. a -> CheckM m a
forall a b. CheckM m a -> CheckM m b -> CheckM m b
forall a b. CheckM m a -> (a -> CheckM m b) -> CheckM m b
forall (m :: * -> *). Monad m => Applicative (CheckM m)
forall (m :: * -> *) a. Monad m => a -> CheckM m a
forall (m :: * -> *) a b.
Monad m =>
CheckM m a -> CheckM m b -> CheckM m b
forall (m :: * -> *) a b.
Monad m =>
CheckM m a -> (a -> CheckM m b) -> CheckM m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
CheckM m a -> (a -> CheckM m b) -> CheckM m b
>>= :: forall a b. CheckM m a -> (a -> CheckM m b) -> CheckM m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
CheckM m a -> CheckM m b -> CheckM m b
>> :: forall a b. CheckM m a -> CheckM m b -> CheckM m b
$creturn :: forall (m :: * -> *) a. Monad m => a -> CheckM m a
return :: forall a. a -> CheckM m a
Monad)
execCheckM :: Monad m => CheckM m () -> CheckCtx m -> m [PackageCheck]
execCheckM :: forall (m :: * -> *).
Monad m =>
CheckM m () -> CheckCtx m -> m [PackageCheck]
execCheckM (CheckM ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
rwm) CheckCtx m
ctx =
let wm :: WriterT (Set PackageCheck) m ()
wm = ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckCtx m -> WriterT (Set PackageCheck) m ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
Reader.runReaderT ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
rwm CheckCtx m
ctx
m :: m (Set PackageCheck)
m = WriterT (Set PackageCheck) m () -> m (Set PackageCheck)
forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
Writer.execWriterT WriterT (Set PackageCheck) m ()
wm
in Set PackageCheck -> [PackageCheck]
forall a. Set a -> [a]
Set.toList (Set PackageCheck -> [PackageCheck])
-> m (Set PackageCheck) -> m [PackageCheck]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Set PackageCheck)
m
tellP :: Monad m => PackageCheck -> CheckM m ()
tellP :: forall (m :: * -> *). Monad m => PackageCheck -> CheckM m ()
tellP = Bool -> PackageCheck -> CheckM m ()
forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
checkP Bool
True
tellCM :: Monad m => PackageCheck -> CheckM m ()
tellCM :: forall (m :: * -> *). Monad m => PackageCheck -> CheckM m ()
tellCM PackageCheck
ck = do
Bool
cf <- (CheckCtx m -> Bool) -> CheckM m Bool
forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM CheckCtx m -> Bool
forall (m :: * -> *). CheckCtx m -> Bool
ccFlag
Bool -> CheckM m () -> CheckM m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless
(Bool
cf Bool -> Bool -> Bool
&& PackageCheck -> Bool
canSkip PackageCheck
ck)
(ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckM m ()
forall (m :: * -> *) a.
ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
CheckM (ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckM m ())
-> (Set PackageCheck
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ())
-> Set PackageCheck
-> CheckM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set PackageCheck
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
Writer.tell (Set PackageCheck -> CheckM m ())
-> Set PackageCheck -> CheckM m ()
forall a b. (a -> b) -> a -> b
$ PackageCheck -> Set PackageCheck
forall a. a -> Set a
Set.singleton PackageCheck
ck)
where
canSkip :: PackageCheck -> Bool
canSkip :: PackageCheck -> Bool
canSkip PackageCheck
wck = Bool -> Bool
not (PackageCheck -> Bool
isSevereLocal PackageCheck
wck) Bool -> Bool -> Bool
|| PackageCheck -> Bool
isErrAllowable PackageCheck
wck
isSevereLocal :: PackageCheck -> Bool
isSevereLocal :: PackageCheck -> Bool
isSevereLocal (PackageBuildImpossible CheckExplanation
_) = Bool
True
isSevereLocal (PackageBuildWarning CheckExplanation
_) = Bool
True
isSevereLocal (PackageDistSuspicious CheckExplanation
_) = Bool
False
isSevereLocal (PackageDistSuspiciousWarn CheckExplanation
_) = Bool
False
isSevereLocal (PackageDistInexcusable CheckExplanation
_) = Bool
True
isErrAllowable :: PackageCheck -> Bool
isErrAllowable :: PackageCheck -> Bool
isErrAllowable PackageCheck
c = case PackageCheck -> CheckExplanation
extractCheckExplantion PackageCheck
c of
(WErrorUnneeded FilePath
_) -> Bool
True
(JUnneeded FilePath
_) -> Bool
True
(FDeferTypeErrorsUnneeded FilePath
_) -> Bool
True
(DynamicUnneeded FilePath
_) -> Bool
True
(ProfilingUnneeded FilePath
_) -> Bool
True
CheckExplanation
_ -> Bool
False
liftCM :: Monad m => m a -> CheckM m a
liftCM :: forall (m :: * -> *) a. Monad m => m a -> CheckM m a
liftCM m a
ma = ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
forall (m :: * -> *) a.
ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
CheckM (ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
-> CheckM m a)
-> (m a -> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a)
-> m a
-> CheckM m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT (Set PackageCheck) m a
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
forall (m :: * -> *) a. Monad m => m a -> ReaderT (CheckCtx m) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (WriterT (Set PackageCheck) m a
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a)
-> (m a -> WriterT (Set PackageCheck) m a)
-> m a
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> WriterT (Set PackageCheck) m a
forall (m :: * -> *) a.
Monad m =>
m a -> WriterT (Set PackageCheck) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (m a -> CheckM m a) -> m a -> CheckM m a
forall a b. (a -> b) -> a -> b
$ m a
ma
liftInt
:: forall m i
. Monad m
=> (CheckInterface m -> Maybe (i m))
-> (i m -> m [PackageCheck])
-> CheckM m ()
liftInt :: forall (m :: * -> *) (i :: (* -> *) -> *).
Monad m =>
(CheckInterface m -> Maybe (i m))
-> (i m -> m [PackageCheck]) -> CheckM m ()
liftInt CheckInterface m -> Maybe (i m)
acc i m -> m [PackageCheck]
f = do
Maybe (i m)
ops <- (CheckCtx m -> Maybe (i m)) -> CheckM m (Maybe (i m))
forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM (CheckInterface m -> Maybe (i m)
acc (CheckInterface m -> Maybe (i m))
-> (CheckCtx m -> CheckInterface m) -> CheckCtx m -> Maybe (i m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckCtx m -> CheckInterface m
forall (m :: * -> *). CheckCtx m -> CheckInterface m
ccInterface)
CheckM m () -> (i m -> CheckM m ()) -> Maybe (i m) -> CheckM m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> CheckM m ()
forall a. a -> CheckM m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) i m -> CheckM m ()
l Maybe (i m)
ops
where
l :: i m -> CheckM m ()
l :: i m -> CheckM m ()
l i m
wi = do
[PackageCheck]
cks <- m [PackageCheck] -> CheckM m [PackageCheck]
forall (m :: * -> *) a. Monad m => m a -> CheckM m a
liftCM (i m -> m [PackageCheck]
f i m
wi)
(PackageCheck -> CheckM m ()) -> [PackageCheck] -> CheckM m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Bool -> PackageCheck -> CheckM m ()
forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
check Bool
True) [PackageCheck]
cks
check
:: Monad m
=> Bool
-> PackageCheck
-> CheckM m ()
check :: forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
check Bool
True PackageCheck
ck = PackageCheck -> CheckM m ()
forall (m :: * -> *). Monad m => PackageCheck -> CheckM m ()
tellCM PackageCheck
ck
check Bool
False PackageCheck
_ = () -> CheckM m ()
forall a. a -> CheckM m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkP
:: Monad m
=> Bool
-> PackageCheck
-> CheckM m ()
checkP :: forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
checkP Bool
b PackageCheck
ck = do
Bool
pb <- (CheckCtx m -> Bool) -> CheckM m Bool
forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM (CheckInterface m -> Bool
forall (m :: * -> *). CheckInterface m -> Bool
ciPureChecks (CheckInterface m -> Bool)
-> (CheckCtx m -> CheckInterface m) -> CheckCtx m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckCtx m -> CheckInterface m
forall (m :: * -> *). CheckCtx m -> CheckInterface m
ccInterface)
Bool -> CheckM m () -> CheckM m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
pb (Bool -> PackageCheck -> CheckM m ()
forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
check Bool
b PackageCheck
ck)
checkPkg
:: forall m
. Monad m
=> (CheckPackageContentOps m -> m Bool)
-> PackageCheck
-> CheckM m ()
checkPkg :: forall (m :: * -> *).
Monad m =>
(CheckPackageContentOps m -> m Bool) -> PackageCheck -> CheckM m ()
checkPkg CheckPackageContentOps m -> m Bool
f PackageCheck
ck = (CheckInterface m -> Maybe (CheckPackageContentOps m))
-> (CheckPackageContentOps m -> m Bool)
-> PackageCheck
-> CheckM m ()
forall (m :: * -> *) (i :: (* -> *) -> *).
Monad m =>
(CheckInterface m -> Maybe (i m))
-> (i m -> m Bool) -> PackageCheck -> CheckM m ()
checkInt CheckInterface m -> Maybe (CheckPackageContentOps m)
forall (m :: * -> *).
CheckInterface m -> Maybe (CheckPackageContentOps m)
ciPackageOps CheckPackageContentOps m -> m Bool
f PackageCheck
ck
checkIntDep
:: forall m i
. Monad m
=> (CheckInterface m -> Maybe (i m))
-> (i m -> m (Maybe PackageCheck))
-> CheckM m ()
checkIntDep :: forall (m :: * -> *) (i :: (* -> *) -> *).
Monad m =>
(CheckInterface m -> Maybe (i m))
-> (i m -> m (Maybe PackageCheck)) -> CheckM m ()
checkIntDep CheckInterface m -> Maybe (i m)
acc i m -> m (Maybe PackageCheck)
mck = do
Maybe (i m)
po <- (CheckCtx m -> Maybe (i m)) -> CheckM m (Maybe (i m))
forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM (CheckInterface m -> Maybe (i m)
acc (CheckInterface m -> Maybe (i m))
-> (CheckCtx m -> CheckInterface m) -> CheckCtx m -> Maybe (i m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckCtx m -> CheckInterface m
forall (m :: * -> *). CheckCtx m -> CheckInterface m
ccInterface)
CheckM m () -> (i m -> CheckM m ()) -> Maybe (i m) -> CheckM m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> CheckM m ()
forall a. a -> CheckM m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (m (Maybe PackageCheck) -> CheckM m ()
Monad m => m (Maybe PackageCheck) -> CheckM m ()
lc (m (Maybe PackageCheck) -> CheckM m ())
-> (i m -> m (Maybe PackageCheck)) -> i m -> CheckM m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i m -> m (Maybe PackageCheck)
mck) Maybe (i m)
po
where
lc :: Monad m => m (Maybe PackageCheck) -> CheckM m ()
lc :: Monad m => m (Maybe PackageCheck) -> CheckM m ()
lc m (Maybe PackageCheck)
wmck = do
Maybe PackageCheck
b <- m (Maybe PackageCheck) -> CheckM m (Maybe PackageCheck)
forall (m :: * -> *) a. Monad m => m a -> CheckM m a
liftCM m (Maybe PackageCheck)
wmck
CheckM m ()
-> (PackageCheck -> CheckM m ())
-> Maybe PackageCheck
-> CheckM m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> CheckM m ()
forall a. a -> CheckM m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (Bool -> PackageCheck -> CheckM m ()
forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
check Bool
True) Maybe PackageCheck
b
checkInt
:: forall m i
. Monad m
=> (CheckInterface m -> Maybe (i m))
-> (i m -> m Bool)
-> PackageCheck
-> CheckM m ()
checkInt :: forall (m :: * -> *) (i :: (* -> *) -> *).
Monad m =>
(CheckInterface m -> Maybe (i m))
-> (i m -> m Bool) -> PackageCheck -> CheckM m ()
checkInt CheckInterface m -> Maybe (i m)
acc i m -> m Bool
f PackageCheck
ck =
(CheckInterface m -> Maybe (i m))
-> (i m -> m (Maybe PackageCheck)) -> CheckM m ()
forall (m :: * -> *) (i :: (* -> *) -> *).
Monad m =>
(CheckInterface m -> Maybe (i m))
-> (i m -> m (Maybe PackageCheck)) -> CheckM m ()
checkIntDep
CheckInterface m -> Maybe (i m)
acc
( \i m
ops -> do
Bool
b <- i m -> m Bool
f i m
ops
if Bool
b
then Maybe PackageCheck -> m (Maybe PackageCheck)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PackageCheck -> m (Maybe PackageCheck))
-> Maybe PackageCheck -> m (Maybe PackageCheck)
forall a b. (a -> b) -> a -> b
$ PackageCheck -> Maybe PackageCheck
forall a. a -> Maybe a
Just PackageCheck
ck
else Maybe PackageCheck -> m (Maybe PackageCheck)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PackageCheck
forall a. Maybe a
Nothing
)
localCM :: Monad m => (CheckCtx m -> CheckCtx m) -> CheckM m () -> CheckM m ()
localCM :: forall (m :: * -> *).
Monad m =>
(CheckCtx m -> CheckCtx m) -> CheckM m () -> CheckM m ()
localCM CheckCtx m -> CheckCtx m
cf (CheckM ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
im) = ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckM m ()
forall (m :: * -> *) a.
ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
CheckM (ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckM m ())
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> CheckM m ()
forall a b. (a -> b) -> a -> b
$ (CheckCtx m -> CheckCtx m)
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
forall a.
(CheckCtx m -> CheckCtx m)
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
Reader.local CheckCtx m -> CheckCtx m
cf ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) ()
im
asksCM :: Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM :: forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM CheckCtx m -> a
f = ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
forall (m :: * -> *) a.
ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a -> CheckM m a
CheckM (ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
-> CheckM m a)
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
-> CheckM m a
forall a b. (a -> b) -> a -> b
$ (CheckCtx m -> a)
-> ReaderT (CheckCtx m) (WriterT (Set PackageCheck) m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
Reader.asks CheckCtx m -> a
f
checkSpecVer
:: Monad m
=> CabalSpecVersion
-> Bool
-> PackageCheck
-> CheckM m ()
checkSpecVer :: forall (m :: * -> *).
Monad m =>
CabalSpecVersion -> Bool -> PackageCheck -> CheckM m ()
checkSpecVer CabalSpecVersion
vc Bool
cond PackageCheck
c = do
CabalSpecVersion
vp <- (CheckCtx m -> CabalSpecVersion) -> CheckM m CabalSpecVersion
forall (m :: * -> *) a. Monad m => (CheckCtx m -> a) -> CheckM m a
asksCM CheckCtx m -> CabalSpecVersion
forall (m :: * -> *). CheckCtx m -> CabalSpecVersion
ccSpecVersion
Bool -> CheckM m () -> CheckM m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CabalSpecVersion
vp CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= CabalSpecVersion
vc) (Bool -> PackageCheck -> CheckM m ()
forall (m :: * -> *).
Monad m =>
Bool -> PackageCheck -> CheckM m ()
checkP Bool
cond PackageCheck
c)