{-# LANGUAGE CPP, TypeFamilies, DeriveDataTypeable #-} module PGIP.GraphQL.Result.ReasoningAttempt where import PGIP.GraphQL.Result.Action import PGIP.GraphQL.Result.Reasoner import PGIP.GraphQL.Result.ReasonerConfiguration import PGIP.GraphQL.Result.ReasonerOutput import Data.Data data ReasoningAttempt = ReasoningAttempt { ReasoningAttempt -> Action action :: Action , ReasoningAttempt -> ReasonerConfiguration reasonerConfiguration :: ReasonerConfiguration , ReasoningAttempt -> Maybe ReasonerOutput reasonerOutput :: Maybe ReasonerOutput , ReasoningAttempt -> Maybe Int timeTaken :: Maybe Int , ReasoningAttempt -> Maybe Reasoner usedReasoner :: Maybe Reasoner } deriving (Int -> ReasoningAttempt -> ShowS [ReasoningAttempt] -> ShowS ReasoningAttempt -> String (Int -> ReasoningAttempt -> ShowS) -> (ReasoningAttempt -> String) -> ([ReasoningAttempt] -> ShowS) -> Show ReasoningAttempt forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ReasoningAttempt] -> ShowS $cshowList :: [ReasoningAttempt] -> ShowS show :: ReasoningAttempt -> String $cshow :: ReasoningAttempt -> String showsPrec :: Int -> ReasoningAttempt -> ShowS $cshowsPrec :: Int -> ReasoningAttempt -> ShowS Show, Typeable, Typeable ReasoningAttempt Constr DataType Typeable ReasoningAttempt => (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReasoningAttempt -> c ReasoningAttempt) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReasoningAttempt) -> (ReasoningAttempt -> Constr) -> (ReasoningAttempt -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReasoningAttempt)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReasoningAttempt)) -> ((forall b. Data b => b -> b) -> ReasoningAttempt -> ReasoningAttempt) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r) -> (forall u. (forall d. Data d => d -> u) -> ReasoningAttempt -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> ReasoningAttempt -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt) -> Data ReasoningAttempt ReasoningAttempt -> Constr ReasoningAttempt -> DataType (forall b. Data b => b -> b) -> ReasoningAttempt -> ReasoningAttempt (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReasoningAttempt -> c ReasoningAttempt (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReasoningAttempt 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) -> ReasoningAttempt -> u forall u. (forall d. Data d => d -> u) -> ReasoningAttempt -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReasoningAttempt forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReasoningAttempt -> c ReasoningAttempt forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReasoningAttempt) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReasoningAttempt) $cReasoningAttempt :: Constr $tReasoningAttempt :: DataType gmapMo :: (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt gmapMp :: (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt gmapM :: (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> ReasoningAttempt -> m ReasoningAttempt gmapQi :: Int -> (forall d. Data d => d -> u) -> ReasoningAttempt -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReasoningAttempt -> u gmapQ :: (forall d. Data d => d -> u) -> ReasoningAttempt -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReasoningAttempt -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReasoningAttempt -> r gmapT :: (forall b. Data b => b -> b) -> ReasoningAttempt -> ReasoningAttempt $cgmapT :: (forall b. Data b => b -> b) -> ReasoningAttempt -> ReasoningAttempt dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReasoningAttempt) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReasoningAttempt) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ReasoningAttempt) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReasoningAttempt) dataTypeOf :: ReasoningAttempt -> DataType $cdataTypeOf :: ReasoningAttempt -> DataType toConstr :: ReasoningAttempt -> Constr $ctoConstr :: ReasoningAttempt -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReasoningAttempt $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReasoningAttempt gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReasoningAttempt -> c ReasoningAttempt $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReasoningAttempt -> c ReasoningAttempt $cp1Data :: Typeable ReasoningAttempt Data)