module System.Process.Quick.CallSpec.Type where

import System.Process.Quick.Prelude
import Language.Haskell.TH.Syntax

-- | DC definition order defines validation order
data VerificationMethod
  = TrailingHelpValidate
  | SandboxValidate
  deriving (Int -> VerificationMethod -> ShowS
[VerificationMethod] -> ShowS
VerificationMethod -> String
(Int -> VerificationMethod -> ShowS)
-> (VerificationMethod -> String)
-> ([VerificationMethod] -> ShowS)
-> Show VerificationMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationMethod -> ShowS
showsPrec :: Int -> VerificationMethod -> ShowS
$cshow :: VerificationMethod -> String
show :: VerificationMethod -> String
$cshowList :: [VerificationMethod] -> ShowS
showList :: [VerificationMethod] -> ShowS
Show, Eq VerificationMethod
Eq VerificationMethod =>
(VerificationMethod -> VerificationMethod -> Ordering)
-> (VerificationMethod -> VerificationMethod -> Bool)
-> (VerificationMethod -> VerificationMethod -> Bool)
-> (VerificationMethod -> VerificationMethod -> Bool)
-> (VerificationMethod -> VerificationMethod -> Bool)
-> (VerificationMethod -> VerificationMethod -> VerificationMethod)
-> (VerificationMethod -> VerificationMethod -> VerificationMethod)
-> Ord VerificationMethod
VerificationMethod -> VerificationMethod -> Bool
VerificationMethod -> VerificationMethod -> Ordering
VerificationMethod -> VerificationMethod -> VerificationMethod
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 :: VerificationMethod -> VerificationMethod -> Ordering
compare :: VerificationMethod -> VerificationMethod -> Ordering
$c< :: VerificationMethod -> VerificationMethod -> Bool
< :: VerificationMethod -> VerificationMethod -> Bool
$c<= :: VerificationMethod -> VerificationMethod -> Bool
<= :: VerificationMethod -> VerificationMethod -> Bool
$c> :: VerificationMethod -> VerificationMethod -> Bool
> :: VerificationMethod -> VerificationMethod -> Bool
$c>= :: VerificationMethod -> VerificationMethod -> Bool
>= :: VerificationMethod -> VerificationMethod -> Bool
$cmax :: VerificationMethod -> VerificationMethod -> VerificationMethod
max :: VerificationMethod -> VerificationMethod -> VerificationMethod
$cmin :: VerificationMethod -> VerificationMethod -> VerificationMethod
min :: VerificationMethod -> VerificationMethod -> VerificationMethod
Ord, VerificationMethod -> VerificationMethod -> Bool
(VerificationMethod -> VerificationMethod -> Bool)
-> (VerificationMethod -> VerificationMethod -> Bool)
-> Eq VerificationMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerificationMethod -> VerificationMethod -> Bool
== :: VerificationMethod -> VerificationMethod -> Bool
$c/= :: VerificationMethod -> VerificationMethod -> Bool
/= :: VerificationMethod -> VerificationMethod -> Bool
Eq, Typeable, Typeable VerificationMethod
Typeable VerificationMethod =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> VerificationMethod
 -> c VerificationMethod)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VerificationMethod)
-> (VerificationMethod -> Constr)
-> (VerificationMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c VerificationMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VerificationMethod))
-> ((forall b. Data b => b -> b)
    -> VerificationMethod -> VerificationMethod)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VerificationMethod -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VerificationMethod -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VerificationMethod -> m VerificationMethod)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VerificationMethod -> m VerificationMethod)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VerificationMethod -> m VerificationMethod)
-> Data VerificationMethod
VerificationMethod -> Constr
VerificationMethod -> DataType
(forall b. Data b => b -> b)
-> VerificationMethod -> VerificationMethod
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) -> VerificationMethod -> u
forall u. (forall d. Data d => d -> u) -> VerificationMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VerificationMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VerificationMethod
-> c VerificationMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VerificationMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VerificationMethod)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VerificationMethod
-> c VerificationMethod
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VerificationMethod
-> c VerificationMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VerificationMethod
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VerificationMethod
$ctoConstr :: VerificationMethod -> Constr
toConstr :: VerificationMethod -> Constr
$cdataTypeOf :: VerificationMethod -> DataType
dataTypeOf :: VerificationMethod -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VerificationMethod)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VerificationMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VerificationMethod)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VerificationMethod)
$cgmapT :: (forall b. Data b => b -> b)
-> VerificationMethod -> VerificationMethod
gmapT :: (forall b. Data b => b -> b)
-> VerificationMethod -> VerificationMethod
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VerificationMethod -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VerificationMethod -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> VerificationMethod -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> VerificationMethod -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> VerificationMethod -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VerificationMethod -> m VerificationMethod
Data, (forall x. VerificationMethod -> Rep VerificationMethod x)
-> (forall x. Rep VerificationMethod x -> VerificationMethod)
-> Generic VerificationMethod
forall x. Rep VerificationMethod x -> VerificationMethod
forall x. VerificationMethod -> Rep VerificationMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VerificationMethod -> Rep VerificationMethod x
from :: forall x. VerificationMethod -> Rep VerificationMethod x
$cto :: forall x. Rep VerificationMethod x -> VerificationMethod
to :: forall x. Rep VerificationMethod x -> VerificationMethod
Generic, (forall (m :: * -> *). Quote m => VerificationMethod -> m Exp)
-> (forall (m :: * -> *).
    Quote m =>
    VerificationMethod -> Code m VerificationMethod)
-> Lift VerificationMethod
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => VerificationMethod -> m Exp
forall (m :: * -> *).
Quote m =>
VerificationMethod -> Code m VerificationMethod
$clift :: forall (m :: * -> *). Quote m => VerificationMethod -> m Exp
lift :: forall (m :: * -> *). Quote m => VerificationMethod -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
VerificationMethod -> Code m VerificationMethod
liftTyped :: forall (m :: * -> *).
Quote m =>
VerificationMethod -> Code m VerificationMethod
Lift)

class (Arbitrary cs, Data cs) => CallSpec cs where
  programName :: Proxy cs -> String
  programArgs :: cs -> [String]
  verificationMethods :: Proxy cs -> [VerificationMethod]