{-# LANGUAGE DeriveGeneric #-}
module Distribution.Client.Types.BuildResults (
    BuildOutcome,
    BuildOutcomes,
    BuildFailure (..),
    BuildResult (..),
    TestsResult (..),
    DocsResult (..),
) where

import Distribution.Client.Compat.Prelude
import Prelude ()

import Distribution.Types.InstalledPackageInfo (InstalledPackageInfo)
import Distribution.Types.PackageId            (PackageId)
import Distribution.Types.UnitId               (UnitId)

-- | A summary of the outcome for building a single package.
--
type BuildOutcome = Either BuildFailure BuildResult

-- | A summary of the outcome for building a whole set of packages.
--
type BuildOutcomes = Map UnitId BuildOutcome

data BuildFailure = PlanningFailed
                  | DependentFailed PackageId
                  | DownloadFailed  SomeException
                  | UnpackFailed    SomeException
                  | ConfigureFailed SomeException
                  | BuildFailed     SomeException
                  | TestsFailed     SomeException
                  | InstallFailed   SomeException
  deriving (Int -> BuildFailure -> ShowS
[BuildFailure] -> ShowS
BuildFailure -> String
(Int -> BuildFailure -> ShowS)
-> (BuildFailure -> String)
-> ([BuildFailure] -> ShowS)
-> Show BuildFailure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildFailure] -> ShowS
$cshowList :: [BuildFailure] -> ShowS
show :: BuildFailure -> String
$cshow :: BuildFailure -> String
showsPrec :: Int -> BuildFailure -> ShowS
$cshowsPrec :: Int -> BuildFailure -> ShowS
Show, Typeable, (forall x. BuildFailure -> Rep BuildFailure x)
-> (forall x. Rep BuildFailure x -> BuildFailure)
-> Generic BuildFailure
forall x. Rep BuildFailure x -> BuildFailure
forall x. BuildFailure -> Rep BuildFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildFailure x -> BuildFailure
$cfrom :: forall x. BuildFailure -> Rep BuildFailure x
Generic)

instance Exception BuildFailure

-- Note that the @Maybe InstalledPackageInfo@ is a slight hack: we only
-- the public library's 'InstalledPackageInfo' is stored here, even if
-- there were 'InstalledPackageInfo' from internal libraries.  This
-- 'InstalledPackageInfo' is not used anyway, so it makes no difference.
data BuildResult = BuildResult DocsResult TestsResult
                               (Maybe InstalledPackageInfo)
  deriving (Int -> BuildResult -> ShowS
[BuildResult] -> ShowS
BuildResult -> String
(Int -> BuildResult -> ShowS)
-> (BuildResult -> String)
-> ([BuildResult] -> ShowS)
-> Show BuildResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildResult] -> ShowS
$cshowList :: [BuildResult] -> ShowS
show :: BuildResult -> String
$cshow :: BuildResult -> String
showsPrec :: Int -> BuildResult -> ShowS
$cshowsPrec :: Int -> BuildResult -> ShowS
Show, (forall x. BuildResult -> Rep BuildResult x)
-> (forall x. Rep BuildResult x -> BuildResult)
-> Generic BuildResult
forall x. Rep BuildResult x -> BuildResult
forall x. BuildResult -> Rep BuildResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildResult x -> BuildResult
$cfrom :: forall x. BuildResult -> Rep BuildResult x
Generic)

data DocsResult  = DocsNotTried  | DocsFailed  | DocsOk
  deriving (Int -> DocsResult -> ShowS
[DocsResult] -> ShowS
DocsResult -> String
(Int -> DocsResult -> ShowS)
-> (DocsResult -> String)
-> ([DocsResult] -> ShowS)
-> Show DocsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocsResult] -> ShowS
$cshowList :: [DocsResult] -> ShowS
show :: DocsResult -> String
$cshow :: DocsResult -> String
showsPrec :: Int -> DocsResult -> ShowS
$cshowsPrec :: Int -> DocsResult -> ShowS
Show, (forall x. DocsResult -> Rep DocsResult x)
-> (forall x. Rep DocsResult x -> DocsResult) -> Generic DocsResult
forall x. Rep DocsResult x -> DocsResult
forall x. DocsResult -> Rep DocsResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DocsResult x -> DocsResult
$cfrom :: forall x. DocsResult -> Rep DocsResult x
Generic, Typeable)
data TestsResult = TestsNotTried | TestsOk
  deriving (Int -> TestsResult -> ShowS
[TestsResult] -> ShowS
TestsResult -> String
(Int -> TestsResult -> ShowS)
-> (TestsResult -> String)
-> ([TestsResult] -> ShowS)
-> Show TestsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestsResult] -> ShowS
$cshowList :: [TestsResult] -> ShowS
show :: TestsResult -> String
$cshow :: TestsResult -> String
showsPrec :: Int -> TestsResult -> ShowS
$cshowsPrec :: Int -> TestsResult -> ShowS
Show, (forall x. TestsResult -> Rep TestsResult x)
-> (forall x. Rep TestsResult x -> TestsResult)
-> Generic TestsResult
forall x. Rep TestsResult x -> TestsResult
forall x. TestsResult -> Rep TestsResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestsResult x -> TestsResult
$cfrom :: forall x. TestsResult -> Rep TestsResult x
Generic, Typeable)

instance Binary BuildFailure
instance Binary BuildResult
instance Binary DocsResult
instance Binary TestsResult

instance Structured BuildFailure
instance Structured BuildResult
instance Structured DocsResult
instance Structured TestsResult