{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.TestSuiteInterface
  ( TestSuiteInterface (..)
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.ModuleName
import Distribution.Types.TestType
import Distribution.Version

-- | The test suite interfaces that are currently defined.
--
-- More interfaces may be defined in future, either new revisions or totally
-- new interfaces.
data TestSuiteInterface
  = -- | Test interface \"exitcode-stdio-1.0\". The test-suite takes the form
    -- of an executable. It returns a zero exit code for success, non-zero for
    -- failure. The stdout and stderr channels may be logged. Test tooling may
    -- pass command line arguments and/or connect the stdin channel to the test.
    TestSuiteExeV10 Version FilePath
  | -- | Test interface \"detailed-0.9\". The test-suite takes the form of a
    -- library containing a designated module that exports \"tests :: [Test]\".
    TestSuiteLibV09 Version ModuleName
  | -- | A test suite that does not conform to one of the above interfaces for
    -- the given reason (e.g. unknown test type).
    TestSuiteUnsupported TestType
  deriving (TestSuiteInterface -> TestSuiteInterface -> Bool
(TestSuiteInterface -> TestSuiteInterface -> Bool)
-> (TestSuiteInterface -> TestSuiteInterface -> Bool)
-> Eq TestSuiteInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestSuiteInterface -> TestSuiteInterface -> Bool
== :: TestSuiteInterface -> TestSuiteInterface -> Bool
$c/= :: TestSuiteInterface -> TestSuiteInterface -> Bool
/= :: TestSuiteInterface -> TestSuiteInterface -> Bool
Eq, Eq TestSuiteInterface
Eq TestSuiteInterface =>
(TestSuiteInterface -> TestSuiteInterface -> Ordering)
-> (TestSuiteInterface -> TestSuiteInterface -> Bool)
-> (TestSuiteInterface -> TestSuiteInterface -> Bool)
-> (TestSuiteInterface -> TestSuiteInterface -> Bool)
-> (TestSuiteInterface -> TestSuiteInterface -> Bool)
-> (TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface)
-> (TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface)
-> Ord TestSuiteInterface
TestSuiteInterface -> TestSuiteInterface -> Bool
TestSuiteInterface -> TestSuiteInterface -> Ordering
TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
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
$ccompare :: TestSuiteInterface -> TestSuiteInterface -> Ordering
compare :: TestSuiteInterface -> TestSuiteInterface -> Ordering
$c< :: TestSuiteInterface -> TestSuiteInterface -> Bool
< :: TestSuiteInterface -> TestSuiteInterface -> Bool
$c<= :: TestSuiteInterface -> TestSuiteInterface -> Bool
<= :: TestSuiteInterface -> TestSuiteInterface -> Bool
$c> :: TestSuiteInterface -> TestSuiteInterface -> Bool
> :: TestSuiteInterface -> TestSuiteInterface -> Bool
$c>= :: TestSuiteInterface -> TestSuiteInterface -> Bool
>= :: TestSuiteInterface -> TestSuiteInterface -> Bool
$cmax :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
max :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
$cmin :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
min :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
Ord, (forall x. TestSuiteInterface -> Rep TestSuiteInterface x)
-> (forall x. Rep TestSuiteInterface x -> TestSuiteInterface)
-> Generic TestSuiteInterface
forall x. Rep TestSuiteInterface x -> TestSuiteInterface
forall x. TestSuiteInterface -> Rep TestSuiteInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TestSuiteInterface -> Rep TestSuiteInterface x
from :: forall x. TestSuiteInterface -> Rep TestSuiteInterface x
$cto :: forall x. Rep TestSuiteInterface x -> TestSuiteInterface
to :: forall x. Rep TestSuiteInterface x -> TestSuiteInterface
Generic, ReadPrec [TestSuiteInterface]
ReadPrec TestSuiteInterface
Int -> ReadS TestSuiteInterface
ReadS [TestSuiteInterface]
(Int -> ReadS TestSuiteInterface)
-> ReadS [TestSuiteInterface]
-> ReadPrec TestSuiteInterface
-> ReadPrec [TestSuiteInterface]
-> Read TestSuiteInterface
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TestSuiteInterface
readsPrec :: Int -> ReadS TestSuiteInterface
$creadList :: ReadS [TestSuiteInterface]
readList :: ReadS [TestSuiteInterface]
$creadPrec :: ReadPrec TestSuiteInterface
readPrec :: ReadPrec TestSuiteInterface
$creadListPrec :: ReadPrec [TestSuiteInterface]
readListPrec :: ReadPrec [TestSuiteInterface]
Read, Int -> TestSuiteInterface -> ShowS
[TestSuiteInterface] -> ShowS
TestSuiteInterface -> FilePath
(Int -> TestSuiteInterface -> ShowS)
-> (TestSuiteInterface -> FilePath)
-> ([TestSuiteInterface] -> ShowS)
-> Show TestSuiteInterface
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestSuiteInterface -> ShowS
showsPrec :: Int -> TestSuiteInterface -> ShowS
$cshow :: TestSuiteInterface -> FilePath
show :: TestSuiteInterface -> FilePath
$cshowList :: [TestSuiteInterface] -> ShowS
showList :: [TestSuiteInterface] -> ShowS
Show, Typeable, Typeable TestSuiteInterface
Typeable TestSuiteInterface =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> TestSuiteInterface
 -> c TestSuiteInterface)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TestSuiteInterface)
-> (TestSuiteInterface -> Constr)
-> (TestSuiteInterface -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c TestSuiteInterface))
-> ((forall b. Data b => b -> b)
    -> TestSuiteInterface -> TestSuiteInterface)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> TestSuiteInterface -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> TestSuiteInterface -> m TestSuiteInterface)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> TestSuiteInterface -> m TestSuiteInterface)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> TestSuiteInterface -> m TestSuiteInterface)
-> Data TestSuiteInterface
TestSuiteInterface -> Constr
TestSuiteInterface -> DataType
(forall b. Data b => b -> b)
-> TestSuiteInterface -> TestSuiteInterface
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u
forall u. (forall d. Data d => d -> u) -> TestSuiteInterface -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestSuiteInterface
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TestSuiteInterface
-> c TestSuiteInterface
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TestSuiteInterface)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TestSuiteInterface
-> c TestSuiteInterface
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TestSuiteInterface
-> c TestSuiteInterface
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestSuiteInterface
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TestSuiteInterface
$ctoConstr :: TestSuiteInterface -> Constr
toConstr :: TestSuiteInterface -> Constr
$cdataTypeOf :: TestSuiteInterface -> DataType
dataTypeOf :: TestSuiteInterface -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TestSuiteInterface)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TestSuiteInterface)
$cgmapT :: (forall b. Data b => b -> b)
-> TestSuiteInterface -> TestSuiteInterface
gmapT :: (forall b. Data b => b -> b)
-> TestSuiteInterface -> TestSuiteInterface
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TestSuiteInterface -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TestSuiteInterface -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TestSuiteInterface -> m TestSuiteInterface
Data)

instance Binary TestSuiteInterface
instance Structured TestSuiteInterface

instance NFData TestSuiteInterface where rnf :: TestSuiteInterface -> ()
rnf = TestSuiteInterface -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

instance Monoid TestSuiteInterface where
  mempty :: TestSuiteInterface
mempty = TestType -> TestSuiteInterface
TestSuiteUnsupported (FilePath -> Version -> TestType
TestTypeUnknown FilePath
forall a. Monoid a => a
mempty Version
nullVersion)
  mappend :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
mappend = TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup TestSuiteInterface where
  TestSuiteInterface
a <> :: TestSuiteInterface -> TestSuiteInterface -> TestSuiteInterface
<> (TestSuiteUnsupported TestType
_) = TestSuiteInterface
a
  TestSuiteInterface
_ <> TestSuiteInterface
b = TestSuiteInterface
b