{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE DuplicateRecordFields #-}

module Hercules.API.Build.DerivationEvent where

import Data.Aeson.Types (FromJSON (..), ToJSON (..), genericParseJSON, genericToEncoding, genericToJSON)
import Hercules.API.Build.DerivationEvent.BuiltOutput
import Hercules.API.Prelude
import Hercules.API.Projects.SimpleJob (SimpleJob)

data DerivationEvent
  = Queued DerivationEventQueued
  | DependencyFailed DerivationEventDependencyFailed
  | Started DerivationEventStarted
  | Reset DerivationEventReset
  | Failed DerivationEventFailed
  | Succeeded DerivationEventSucceeded
  | Cancelled DerivationEventCancelled
  | Built DerivationEventBuilt
  | HasCancelled DerivationEventHasCancelled
  | HasCancelledForReset DerivationEventHasCancelledForReset
  deriving ((forall x. DerivationEvent -> Rep DerivationEvent x)
-> (forall x. Rep DerivationEvent x -> DerivationEvent)
-> Generic DerivationEvent
forall x. Rep DerivationEvent x -> DerivationEvent
forall x. DerivationEvent -> Rep DerivationEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEvent x -> DerivationEvent
$cfrom :: forall x. DerivationEvent -> Rep DerivationEvent x
Generic, Int -> DerivationEvent -> ShowS
[DerivationEvent] -> ShowS
DerivationEvent -> String
(Int -> DerivationEvent -> ShowS)
-> (DerivationEvent -> String)
-> ([DerivationEvent] -> ShowS)
-> Show DerivationEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEvent] -> ShowS
$cshowList :: [DerivationEvent] -> ShowS
show :: DerivationEvent -> String
$cshow :: DerivationEvent -> String
showsPrec :: Int -> DerivationEvent -> ShowS
$cshowsPrec :: Int -> DerivationEvent -> ShowS
Show, DerivationEvent -> DerivationEvent -> Bool
(DerivationEvent -> DerivationEvent -> Bool)
-> (DerivationEvent -> DerivationEvent -> Bool)
-> Eq DerivationEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEvent -> DerivationEvent -> Bool
$c/= :: DerivationEvent -> DerivationEvent -> Bool
== :: DerivationEvent -> DerivationEvent -> Bool
$c== :: DerivationEvent -> DerivationEvent -> Bool
Eq, DerivationEvent -> ()
(DerivationEvent -> ()) -> NFData DerivationEvent
forall a. (a -> ()) -> NFData a
rnf :: DerivationEvent -> ()
$crnf :: DerivationEvent -> ()
NFData, Proxy DerivationEvent -> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEvent -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEvent
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEvent -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEvent -> Declare (Definitions Schema) NamedSchema
ToSchema)

instance FromJSON DerivationEvent where
  parseJSON :: Value -> Parser DerivationEvent
parseJSON = Options -> Value -> Parser DerivationEvent
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
schemaCompatibleOptions

instance ToJSON DerivationEvent where
  toJSON :: DerivationEvent -> Value
toJSON = Options -> DerivationEvent -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
schemaCompatibleOptions

  toEncoding :: DerivationEvent -> Encoding
toEncoding = Options -> DerivationEvent -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
schemaCompatibleOptions

eventTime :: DerivationEvent -> UTCTime
eventTime :: DerivationEvent -> UTCTime
eventTime (Queued (DerivationEventQueued {$sel:time:DerivationEventQueued :: DerivationEventQueued -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (DependencyFailed (DerivationEventDependencyFailed {$sel:time:DerivationEventDependencyFailed :: DerivationEventDependencyFailed -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Started (DerivationEventStarted {$sel:time:DerivationEventStarted :: DerivationEventStarted -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Reset (DerivationEventReset {$sel:time:DerivationEventReset :: DerivationEventReset -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Failed (DerivationEventFailed {$sel:time:DerivationEventFailed :: DerivationEventFailed -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Succeeded (DerivationEventSucceeded {$sel:time:DerivationEventSucceeded :: DerivationEventSucceeded -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Cancelled (DerivationEventCancelled {$sel:time:DerivationEventCancelled :: DerivationEventCancelled -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (Built (DerivationEventBuilt {$sel:time:DerivationEventBuilt :: DerivationEventBuilt -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (HasCancelled (DerivationEventHasCancelled {$sel:time:DerivationEventHasCancelled :: DerivationEventHasCancelled -> UTCTime
time = UTCTime
t})) = UTCTime
t
eventTime (HasCancelledForReset (DerivationEventHasCancelledForReset {$sel:time:DerivationEventHasCancelledForReset :: DerivationEventHasCancelledForReset -> UTCTime
time = UTCTime
t})) = UTCTime
t

data DerivationEventQueued = DerivationEventQueued
  { DerivationEventQueued -> UTCTime
time :: UTCTime,
    DerivationEventQueued -> Maybe SimpleJob
requeuedForEvalOfJob :: Maybe SimpleJob,
    DerivationEventQueued -> Maybe Text
requeuedForAgent :: Maybe Text
  }
  deriving ((forall x. DerivationEventQueued -> Rep DerivationEventQueued x)
-> (forall x. Rep DerivationEventQueued x -> DerivationEventQueued)
-> Generic DerivationEventQueued
forall x. Rep DerivationEventQueued x -> DerivationEventQueued
forall x. DerivationEventQueued -> Rep DerivationEventQueued x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEventQueued x -> DerivationEventQueued
$cfrom :: forall x. DerivationEventQueued -> Rep DerivationEventQueued x
Generic, Int -> DerivationEventQueued -> ShowS
[DerivationEventQueued] -> ShowS
DerivationEventQueued -> String
(Int -> DerivationEventQueued -> ShowS)
-> (DerivationEventQueued -> String)
-> ([DerivationEventQueued] -> ShowS)
-> Show DerivationEventQueued
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventQueued] -> ShowS
$cshowList :: [DerivationEventQueued] -> ShowS
show :: DerivationEventQueued -> String
$cshow :: DerivationEventQueued -> String
showsPrec :: Int -> DerivationEventQueued -> ShowS
$cshowsPrec :: Int -> DerivationEventQueued -> ShowS
Show, DerivationEventQueued -> DerivationEventQueued -> Bool
(DerivationEventQueued -> DerivationEventQueued -> Bool)
-> (DerivationEventQueued -> DerivationEventQueued -> Bool)
-> Eq DerivationEventQueued
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventQueued -> DerivationEventQueued -> Bool
$c/= :: DerivationEventQueued -> DerivationEventQueued -> Bool
== :: DerivationEventQueued -> DerivationEventQueued -> Bool
$c== :: DerivationEventQueued -> DerivationEventQueued -> Bool
Eq, DerivationEventQueued -> ()
(DerivationEventQueued -> ()) -> NFData DerivationEventQueued
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventQueued -> ()
$crnf :: DerivationEventQueued -> ()
NFData, [DerivationEventQueued] -> Encoding
[DerivationEventQueued] -> Value
DerivationEventQueued -> Encoding
DerivationEventQueued -> Value
(DerivationEventQueued -> Value)
-> (DerivationEventQueued -> Encoding)
-> ([DerivationEventQueued] -> Value)
-> ([DerivationEventQueued] -> Encoding)
-> ToJSON DerivationEventQueued
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventQueued] -> Encoding
$ctoEncodingList :: [DerivationEventQueued] -> Encoding
toJSONList :: [DerivationEventQueued] -> Value
$ctoJSONList :: [DerivationEventQueued] -> Value
toEncoding :: DerivationEventQueued -> Encoding
$ctoEncoding :: DerivationEventQueued -> Encoding
toJSON :: DerivationEventQueued -> Value
$ctoJSON :: DerivationEventQueued -> Value
ToJSON, Value -> Parser [DerivationEventQueued]
Value -> Parser DerivationEventQueued
(Value -> Parser DerivationEventQueued)
-> (Value -> Parser [DerivationEventQueued])
-> FromJSON DerivationEventQueued
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventQueued]
$cparseJSONList :: Value -> Parser [DerivationEventQueued]
parseJSON :: Value -> Parser DerivationEventQueued
$cparseJSON :: Value -> Parser DerivationEventQueued
FromJSON, Proxy DerivationEventQueued
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventQueued
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventQueued
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventQueued
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventQueued
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventDependencyFailed = DerivationEventDependencyFailed
  { DerivationEventDependencyFailed -> UTCTime
time :: UTCTime
  }
  deriving ((forall x.
 DerivationEventDependencyFailed
 -> Rep DerivationEventDependencyFailed x)
-> (forall x.
    Rep DerivationEventDependencyFailed x
    -> DerivationEventDependencyFailed)
-> Generic DerivationEventDependencyFailed
forall x.
Rep DerivationEventDependencyFailed x
-> DerivationEventDependencyFailed
forall x.
DerivationEventDependencyFailed
-> Rep DerivationEventDependencyFailed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DerivationEventDependencyFailed x
-> DerivationEventDependencyFailed
$cfrom :: forall x.
DerivationEventDependencyFailed
-> Rep DerivationEventDependencyFailed x
Generic, Int -> DerivationEventDependencyFailed -> ShowS
[DerivationEventDependencyFailed] -> ShowS
DerivationEventDependencyFailed -> String
(Int -> DerivationEventDependencyFailed -> ShowS)
-> (DerivationEventDependencyFailed -> String)
-> ([DerivationEventDependencyFailed] -> ShowS)
-> Show DerivationEventDependencyFailed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventDependencyFailed] -> ShowS
$cshowList :: [DerivationEventDependencyFailed] -> ShowS
show :: DerivationEventDependencyFailed -> String
$cshow :: DerivationEventDependencyFailed -> String
showsPrec :: Int -> DerivationEventDependencyFailed -> ShowS
$cshowsPrec :: Int -> DerivationEventDependencyFailed -> ShowS
Show, DerivationEventDependencyFailed
-> DerivationEventDependencyFailed -> Bool
(DerivationEventDependencyFailed
 -> DerivationEventDependencyFailed -> Bool)
-> (DerivationEventDependencyFailed
    -> DerivationEventDependencyFailed -> Bool)
-> Eq DerivationEventDependencyFailed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventDependencyFailed
-> DerivationEventDependencyFailed -> Bool
$c/= :: DerivationEventDependencyFailed
-> DerivationEventDependencyFailed -> Bool
== :: DerivationEventDependencyFailed
-> DerivationEventDependencyFailed -> Bool
$c== :: DerivationEventDependencyFailed
-> DerivationEventDependencyFailed -> Bool
Eq, DerivationEventDependencyFailed -> ()
(DerivationEventDependencyFailed -> ())
-> NFData DerivationEventDependencyFailed
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventDependencyFailed -> ()
$crnf :: DerivationEventDependencyFailed -> ()
NFData, [DerivationEventDependencyFailed] -> Encoding
[DerivationEventDependencyFailed] -> Value
DerivationEventDependencyFailed -> Encoding
DerivationEventDependencyFailed -> Value
(DerivationEventDependencyFailed -> Value)
-> (DerivationEventDependencyFailed -> Encoding)
-> ([DerivationEventDependencyFailed] -> Value)
-> ([DerivationEventDependencyFailed] -> Encoding)
-> ToJSON DerivationEventDependencyFailed
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventDependencyFailed] -> Encoding
$ctoEncodingList :: [DerivationEventDependencyFailed] -> Encoding
toJSONList :: [DerivationEventDependencyFailed] -> Value
$ctoJSONList :: [DerivationEventDependencyFailed] -> Value
toEncoding :: DerivationEventDependencyFailed -> Encoding
$ctoEncoding :: DerivationEventDependencyFailed -> Encoding
toJSON :: DerivationEventDependencyFailed -> Value
$ctoJSON :: DerivationEventDependencyFailed -> Value
ToJSON, Value -> Parser [DerivationEventDependencyFailed]
Value -> Parser DerivationEventDependencyFailed
(Value -> Parser DerivationEventDependencyFailed)
-> (Value -> Parser [DerivationEventDependencyFailed])
-> FromJSON DerivationEventDependencyFailed
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventDependencyFailed]
$cparseJSONList :: Value -> Parser [DerivationEventDependencyFailed]
parseJSON :: Value -> Parser DerivationEventDependencyFailed
$cparseJSON :: Value -> Parser DerivationEventDependencyFailed
FromJSON, Proxy DerivationEventDependencyFailed
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventDependencyFailed
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventDependencyFailed
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventDependencyFailed
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventDependencyFailed
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventStarted = DerivationEventStarted
  { DerivationEventStarted -> UTCTime
time :: UTCTime,
    DerivationEventStarted -> Id "log"
logId :: Id "log",
    DerivationEventStarted -> Maybe Text
agentHostname :: Maybe Text,
    DerivationEventStarted -> Bool
streamable :: Bool
  }
  deriving ((forall x. DerivationEventStarted -> Rep DerivationEventStarted x)
-> (forall x.
    Rep DerivationEventStarted x -> DerivationEventStarted)
-> Generic DerivationEventStarted
forall x. Rep DerivationEventStarted x -> DerivationEventStarted
forall x. DerivationEventStarted -> Rep DerivationEventStarted x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEventStarted x -> DerivationEventStarted
$cfrom :: forall x. DerivationEventStarted -> Rep DerivationEventStarted x
Generic, Int -> DerivationEventStarted -> ShowS
[DerivationEventStarted] -> ShowS
DerivationEventStarted -> String
(Int -> DerivationEventStarted -> ShowS)
-> (DerivationEventStarted -> String)
-> ([DerivationEventStarted] -> ShowS)
-> Show DerivationEventStarted
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventStarted] -> ShowS
$cshowList :: [DerivationEventStarted] -> ShowS
show :: DerivationEventStarted -> String
$cshow :: DerivationEventStarted -> String
showsPrec :: Int -> DerivationEventStarted -> ShowS
$cshowsPrec :: Int -> DerivationEventStarted -> ShowS
Show, DerivationEventStarted -> DerivationEventStarted -> Bool
(DerivationEventStarted -> DerivationEventStarted -> Bool)
-> (DerivationEventStarted -> DerivationEventStarted -> Bool)
-> Eq DerivationEventStarted
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventStarted -> DerivationEventStarted -> Bool
$c/= :: DerivationEventStarted -> DerivationEventStarted -> Bool
== :: DerivationEventStarted -> DerivationEventStarted -> Bool
$c== :: DerivationEventStarted -> DerivationEventStarted -> Bool
Eq, DerivationEventStarted -> ()
(DerivationEventStarted -> ()) -> NFData DerivationEventStarted
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventStarted -> ()
$crnf :: DerivationEventStarted -> ()
NFData, [DerivationEventStarted] -> Encoding
[DerivationEventStarted] -> Value
DerivationEventStarted -> Encoding
DerivationEventStarted -> Value
(DerivationEventStarted -> Value)
-> (DerivationEventStarted -> Encoding)
-> ([DerivationEventStarted] -> Value)
-> ([DerivationEventStarted] -> Encoding)
-> ToJSON DerivationEventStarted
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventStarted] -> Encoding
$ctoEncodingList :: [DerivationEventStarted] -> Encoding
toJSONList :: [DerivationEventStarted] -> Value
$ctoJSONList :: [DerivationEventStarted] -> Value
toEncoding :: DerivationEventStarted -> Encoding
$ctoEncoding :: DerivationEventStarted -> Encoding
toJSON :: DerivationEventStarted -> Value
$ctoJSON :: DerivationEventStarted -> Value
ToJSON, Value -> Parser [DerivationEventStarted]
Value -> Parser DerivationEventStarted
(Value -> Parser DerivationEventStarted)
-> (Value -> Parser [DerivationEventStarted])
-> FromJSON DerivationEventStarted
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventStarted]
$cparseJSONList :: Value -> Parser [DerivationEventStarted]
parseJSON :: Value -> Parser DerivationEventStarted
$cparseJSON :: Value -> Parser DerivationEventStarted
FromJSON, Proxy DerivationEventStarted
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventStarted
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventStarted
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventStarted
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventStarted
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventReset = DerivationEventReset
  { DerivationEventReset -> UTCTime
time :: UTCTime
  }
  deriving ((forall x. DerivationEventReset -> Rep DerivationEventReset x)
-> (forall x. Rep DerivationEventReset x -> DerivationEventReset)
-> Generic DerivationEventReset
forall x. Rep DerivationEventReset x -> DerivationEventReset
forall x. DerivationEventReset -> Rep DerivationEventReset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEventReset x -> DerivationEventReset
$cfrom :: forall x. DerivationEventReset -> Rep DerivationEventReset x
Generic, Int -> DerivationEventReset -> ShowS
[DerivationEventReset] -> ShowS
DerivationEventReset -> String
(Int -> DerivationEventReset -> ShowS)
-> (DerivationEventReset -> String)
-> ([DerivationEventReset] -> ShowS)
-> Show DerivationEventReset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventReset] -> ShowS
$cshowList :: [DerivationEventReset] -> ShowS
show :: DerivationEventReset -> String
$cshow :: DerivationEventReset -> String
showsPrec :: Int -> DerivationEventReset -> ShowS
$cshowsPrec :: Int -> DerivationEventReset -> ShowS
Show, DerivationEventReset -> DerivationEventReset -> Bool
(DerivationEventReset -> DerivationEventReset -> Bool)
-> (DerivationEventReset -> DerivationEventReset -> Bool)
-> Eq DerivationEventReset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventReset -> DerivationEventReset -> Bool
$c/= :: DerivationEventReset -> DerivationEventReset -> Bool
== :: DerivationEventReset -> DerivationEventReset -> Bool
$c== :: DerivationEventReset -> DerivationEventReset -> Bool
Eq, DerivationEventReset -> ()
(DerivationEventReset -> ()) -> NFData DerivationEventReset
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventReset -> ()
$crnf :: DerivationEventReset -> ()
NFData, [DerivationEventReset] -> Encoding
[DerivationEventReset] -> Value
DerivationEventReset -> Encoding
DerivationEventReset -> Value
(DerivationEventReset -> Value)
-> (DerivationEventReset -> Encoding)
-> ([DerivationEventReset] -> Value)
-> ([DerivationEventReset] -> Encoding)
-> ToJSON DerivationEventReset
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventReset] -> Encoding
$ctoEncodingList :: [DerivationEventReset] -> Encoding
toJSONList :: [DerivationEventReset] -> Value
$ctoJSONList :: [DerivationEventReset] -> Value
toEncoding :: DerivationEventReset -> Encoding
$ctoEncoding :: DerivationEventReset -> Encoding
toJSON :: DerivationEventReset -> Value
$ctoJSON :: DerivationEventReset -> Value
ToJSON, Value -> Parser [DerivationEventReset]
Value -> Parser DerivationEventReset
(Value -> Parser DerivationEventReset)
-> (Value -> Parser [DerivationEventReset])
-> FromJSON DerivationEventReset
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventReset]
$cparseJSONList :: Value -> Parser [DerivationEventReset]
parseJSON :: Value -> Parser DerivationEventReset
$cparseJSON :: Value -> Parser DerivationEventReset
FromJSON, Proxy DerivationEventReset
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventReset
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventReset
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventReset
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventReset
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventFailed = DerivationEventFailed
  { DerivationEventFailed -> UTCTime
time :: UTCTime,
    DerivationEventFailed -> Maybe Text
technicalError :: Maybe Text
  }
  deriving ((forall x. DerivationEventFailed -> Rep DerivationEventFailed x)
-> (forall x. Rep DerivationEventFailed x -> DerivationEventFailed)
-> Generic DerivationEventFailed
forall x. Rep DerivationEventFailed x -> DerivationEventFailed
forall x. DerivationEventFailed -> Rep DerivationEventFailed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEventFailed x -> DerivationEventFailed
$cfrom :: forall x. DerivationEventFailed -> Rep DerivationEventFailed x
Generic, Int -> DerivationEventFailed -> ShowS
[DerivationEventFailed] -> ShowS
DerivationEventFailed -> String
(Int -> DerivationEventFailed -> ShowS)
-> (DerivationEventFailed -> String)
-> ([DerivationEventFailed] -> ShowS)
-> Show DerivationEventFailed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventFailed] -> ShowS
$cshowList :: [DerivationEventFailed] -> ShowS
show :: DerivationEventFailed -> String
$cshow :: DerivationEventFailed -> String
showsPrec :: Int -> DerivationEventFailed -> ShowS
$cshowsPrec :: Int -> DerivationEventFailed -> ShowS
Show, DerivationEventFailed -> DerivationEventFailed -> Bool
(DerivationEventFailed -> DerivationEventFailed -> Bool)
-> (DerivationEventFailed -> DerivationEventFailed -> Bool)
-> Eq DerivationEventFailed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventFailed -> DerivationEventFailed -> Bool
$c/= :: DerivationEventFailed -> DerivationEventFailed -> Bool
== :: DerivationEventFailed -> DerivationEventFailed -> Bool
$c== :: DerivationEventFailed -> DerivationEventFailed -> Bool
Eq, DerivationEventFailed -> ()
(DerivationEventFailed -> ()) -> NFData DerivationEventFailed
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventFailed -> ()
$crnf :: DerivationEventFailed -> ()
NFData, [DerivationEventFailed] -> Encoding
[DerivationEventFailed] -> Value
DerivationEventFailed -> Encoding
DerivationEventFailed -> Value
(DerivationEventFailed -> Value)
-> (DerivationEventFailed -> Encoding)
-> ([DerivationEventFailed] -> Value)
-> ([DerivationEventFailed] -> Encoding)
-> ToJSON DerivationEventFailed
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventFailed] -> Encoding
$ctoEncodingList :: [DerivationEventFailed] -> Encoding
toJSONList :: [DerivationEventFailed] -> Value
$ctoJSONList :: [DerivationEventFailed] -> Value
toEncoding :: DerivationEventFailed -> Encoding
$ctoEncoding :: DerivationEventFailed -> Encoding
toJSON :: DerivationEventFailed -> Value
$ctoJSON :: DerivationEventFailed -> Value
ToJSON, Value -> Parser [DerivationEventFailed]
Value -> Parser DerivationEventFailed
(Value -> Parser DerivationEventFailed)
-> (Value -> Parser [DerivationEventFailed])
-> FromJSON DerivationEventFailed
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventFailed]
$cparseJSONList :: Value -> Parser [DerivationEventFailed]
parseJSON :: Value -> Parser DerivationEventFailed
$cparseJSON :: Value -> Parser DerivationEventFailed
FromJSON, Proxy DerivationEventFailed
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventFailed
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventFailed
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventFailed
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventFailed
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventSucceeded = DerivationEventSucceeded
  { DerivationEventSucceeded -> UTCTime
time :: UTCTime
  }
  deriving ((forall x.
 DerivationEventSucceeded -> Rep DerivationEventSucceeded x)
-> (forall x.
    Rep DerivationEventSucceeded x -> DerivationEventSucceeded)
-> Generic DerivationEventSucceeded
forall x.
Rep DerivationEventSucceeded x -> DerivationEventSucceeded
forall x.
DerivationEventSucceeded -> Rep DerivationEventSucceeded x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DerivationEventSucceeded x -> DerivationEventSucceeded
$cfrom :: forall x.
DerivationEventSucceeded -> Rep DerivationEventSucceeded x
Generic, Int -> DerivationEventSucceeded -> ShowS
[DerivationEventSucceeded] -> ShowS
DerivationEventSucceeded -> String
(Int -> DerivationEventSucceeded -> ShowS)
-> (DerivationEventSucceeded -> String)
-> ([DerivationEventSucceeded] -> ShowS)
-> Show DerivationEventSucceeded
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventSucceeded] -> ShowS
$cshowList :: [DerivationEventSucceeded] -> ShowS
show :: DerivationEventSucceeded -> String
$cshow :: DerivationEventSucceeded -> String
showsPrec :: Int -> DerivationEventSucceeded -> ShowS
$cshowsPrec :: Int -> DerivationEventSucceeded -> ShowS
Show, DerivationEventSucceeded -> DerivationEventSucceeded -> Bool
(DerivationEventSucceeded -> DerivationEventSucceeded -> Bool)
-> (DerivationEventSucceeded -> DerivationEventSucceeded -> Bool)
-> Eq DerivationEventSucceeded
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventSucceeded -> DerivationEventSucceeded -> Bool
$c/= :: DerivationEventSucceeded -> DerivationEventSucceeded -> Bool
== :: DerivationEventSucceeded -> DerivationEventSucceeded -> Bool
$c== :: DerivationEventSucceeded -> DerivationEventSucceeded -> Bool
Eq, DerivationEventSucceeded -> ()
(DerivationEventSucceeded -> ()) -> NFData DerivationEventSucceeded
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventSucceeded -> ()
$crnf :: DerivationEventSucceeded -> ()
NFData, [DerivationEventSucceeded] -> Encoding
[DerivationEventSucceeded] -> Value
DerivationEventSucceeded -> Encoding
DerivationEventSucceeded -> Value
(DerivationEventSucceeded -> Value)
-> (DerivationEventSucceeded -> Encoding)
-> ([DerivationEventSucceeded] -> Value)
-> ([DerivationEventSucceeded] -> Encoding)
-> ToJSON DerivationEventSucceeded
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventSucceeded] -> Encoding
$ctoEncodingList :: [DerivationEventSucceeded] -> Encoding
toJSONList :: [DerivationEventSucceeded] -> Value
$ctoJSONList :: [DerivationEventSucceeded] -> Value
toEncoding :: DerivationEventSucceeded -> Encoding
$ctoEncoding :: DerivationEventSucceeded -> Encoding
toJSON :: DerivationEventSucceeded -> Value
$ctoJSON :: DerivationEventSucceeded -> Value
ToJSON, Value -> Parser [DerivationEventSucceeded]
Value -> Parser DerivationEventSucceeded
(Value -> Parser DerivationEventSucceeded)
-> (Value -> Parser [DerivationEventSucceeded])
-> FromJSON DerivationEventSucceeded
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventSucceeded]
$cparseJSONList :: Value -> Parser [DerivationEventSucceeded]
parseJSON :: Value -> Parser DerivationEventSucceeded
$cparseJSON :: Value -> Parser DerivationEventSucceeded
FromJSON, Proxy DerivationEventSucceeded
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventSucceeded
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventSucceeded
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventSucceeded
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventSucceeded
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventCancelled = DerivationEventCancelled
  { DerivationEventCancelled -> UTCTime
time :: UTCTime
  }
  deriving ((forall x.
 DerivationEventCancelled -> Rep DerivationEventCancelled x)
-> (forall x.
    Rep DerivationEventCancelled x -> DerivationEventCancelled)
-> Generic DerivationEventCancelled
forall x.
Rep DerivationEventCancelled x -> DerivationEventCancelled
forall x.
DerivationEventCancelled -> Rep DerivationEventCancelled x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DerivationEventCancelled x -> DerivationEventCancelled
$cfrom :: forall x.
DerivationEventCancelled -> Rep DerivationEventCancelled x
Generic, Int -> DerivationEventCancelled -> ShowS
[DerivationEventCancelled] -> ShowS
DerivationEventCancelled -> String
(Int -> DerivationEventCancelled -> ShowS)
-> (DerivationEventCancelled -> String)
-> ([DerivationEventCancelled] -> ShowS)
-> Show DerivationEventCancelled
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventCancelled] -> ShowS
$cshowList :: [DerivationEventCancelled] -> ShowS
show :: DerivationEventCancelled -> String
$cshow :: DerivationEventCancelled -> String
showsPrec :: Int -> DerivationEventCancelled -> ShowS
$cshowsPrec :: Int -> DerivationEventCancelled -> ShowS
Show, DerivationEventCancelled -> DerivationEventCancelled -> Bool
(DerivationEventCancelled -> DerivationEventCancelled -> Bool)
-> (DerivationEventCancelled -> DerivationEventCancelled -> Bool)
-> Eq DerivationEventCancelled
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventCancelled -> DerivationEventCancelled -> Bool
$c/= :: DerivationEventCancelled -> DerivationEventCancelled -> Bool
== :: DerivationEventCancelled -> DerivationEventCancelled -> Bool
$c== :: DerivationEventCancelled -> DerivationEventCancelled -> Bool
Eq, DerivationEventCancelled -> ()
(DerivationEventCancelled -> ()) -> NFData DerivationEventCancelled
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventCancelled -> ()
$crnf :: DerivationEventCancelled -> ()
NFData, [DerivationEventCancelled] -> Encoding
[DerivationEventCancelled] -> Value
DerivationEventCancelled -> Encoding
DerivationEventCancelled -> Value
(DerivationEventCancelled -> Value)
-> (DerivationEventCancelled -> Encoding)
-> ([DerivationEventCancelled] -> Value)
-> ([DerivationEventCancelled] -> Encoding)
-> ToJSON DerivationEventCancelled
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventCancelled] -> Encoding
$ctoEncodingList :: [DerivationEventCancelled] -> Encoding
toJSONList :: [DerivationEventCancelled] -> Value
$ctoJSONList :: [DerivationEventCancelled] -> Value
toEncoding :: DerivationEventCancelled -> Encoding
$ctoEncoding :: DerivationEventCancelled -> Encoding
toJSON :: DerivationEventCancelled -> Value
$ctoJSON :: DerivationEventCancelled -> Value
ToJSON, Value -> Parser [DerivationEventCancelled]
Value -> Parser DerivationEventCancelled
(Value -> Parser DerivationEventCancelled)
-> (Value -> Parser [DerivationEventCancelled])
-> FromJSON DerivationEventCancelled
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventCancelled]
$cparseJSONList :: Value -> Parser [DerivationEventCancelled]
parseJSON :: Value -> Parser DerivationEventCancelled
$cparseJSON :: Value -> Parser DerivationEventCancelled
FromJSON, Proxy DerivationEventCancelled
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventCancelled
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventCancelled
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventCancelled
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventCancelled
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventBuilt = DerivationEventBuilt
  { DerivationEventBuilt -> UTCTime
time :: UTCTime,
    DerivationEventBuilt -> [BuiltOutput]
outputs :: [BuiltOutput]
  }
  deriving ((forall x. DerivationEventBuilt -> Rep DerivationEventBuilt x)
-> (forall x. Rep DerivationEventBuilt x -> DerivationEventBuilt)
-> Generic DerivationEventBuilt
forall x. Rep DerivationEventBuilt x -> DerivationEventBuilt
forall x. DerivationEventBuilt -> Rep DerivationEventBuilt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationEventBuilt x -> DerivationEventBuilt
$cfrom :: forall x. DerivationEventBuilt -> Rep DerivationEventBuilt x
Generic, Int -> DerivationEventBuilt -> ShowS
[DerivationEventBuilt] -> ShowS
DerivationEventBuilt -> String
(Int -> DerivationEventBuilt -> ShowS)
-> (DerivationEventBuilt -> String)
-> ([DerivationEventBuilt] -> ShowS)
-> Show DerivationEventBuilt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventBuilt] -> ShowS
$cshowList :: [DerivationEventBuilt] -> ShowS
show :: DerivationEventBuilt -> String
$cshow :: DerivationEventBuilt -> String
showsPrec :: Int -> DerivationEventBuilt -> ShowS
$cshowsPrec :: Int -> DerivationEventBuilt -> ShowS
Show, DerivationEventBuilt -> DerivationEventBuilt -> Bool
(DerivationEventBuilt -> DerivationEventBuilt -> Bool)
-> (DerivationEventBuilt -> DerivationEventBuilt -> Bool)
-> Eq DerivationEventBuilt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventBuilt -> DerivationEventBuilt -> Bool
$c/= :: DerivationEventBuilt -> DerivationEventBuilt -> Bool
== :: DerivationEventBuilt -> DerivationEventBuilt -> Bool
$c== :: DerivationEventBuilt -> DerivationEventBuilt -> Bool
Eq, DerivationEventBuilt -> ()
(DerivationEventBuilt -> ()) -> NFData DerivationEventBuilt
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventBuilt -> ()
$crnf :: DerivationEventBuilt -> ()
NFData, [DerivationEventBuilt] -> Encoding
[DerivationEventBuilt] -> Value
DerivationEventBuilt -> Encoding
DerivationEventBuilt -> Value
(DerivationEventBuilt -> Value)
-> (DerivationEventBuilt -> Encoding)
-> ([DerivationEventBuilt] -> Value)
-> ([DerivationEventBuilt] -> Encoding)
-> ToJSON DerivationEventBuilt
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventBuilt] -> Encoding
$ctoEncodingList :: [DerivationEventBuilt] -> Encoding
toJSONList :: [DerivationEventBuilt] -> Value
$ctoJSONList :: [DerivationEventBuilt] -> Value
toEncoding :: DerivationEventBuilt -> Encoding
$ctoEncoding :: DerivationEventBuilt -> Encoding
toJSON :: DerivationEventBuilt -> Value
$ctoJSON :: DerivationEventBuilt -> Value
ToJSON, Value -> Parser [DerivationEventBuilt]
Value -> Parser DerivationEventBuilt
(Value -> Parser DerivationEventBuilt)
-> (Value -> Parser [DerivationEventBuilt])
-> FromJSON DerivationEventBuilt
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventBuilt]
$cparseJSONList :: Value -> Parser [DerivationEventBuilt]
parseJSON :: Value -> Parser DerivationEventBuilt
$cparseJSON :: Value -> Parser DerivationEventBuilt
FromJSON, Proxy DerivationEventBuilt
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventBuilt
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventBuilt
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventBuilt
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventBuilt
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventHasCancelledForReset = DerivationEventHasCancelledForReset
  { DerivationEventHasCancelledForReset -> UTCTime
time :: UTCTime
  }
  deriving ((forall x.
 DerivationEventHasCancelledForReset
 -> Rep DerivationEventHasCancelledForReset x)
-> (forall x.
    Rep DerivationEventHasCancelledForReset x
    -> DerivationEventHasCancelledForReset)
-> Generic DerivationEventHasCancelledForReset
forall x.
Rep DerivationEventHasCancelledForReset x
-> DerivationEventHasCancelledForReset
forall x.
DerivationEventHasCancelledForReset
-> Rep DerivationEventHasCancelledForReset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DerivationEventHasCancelledForReset x
-> DerivationEventHasCancelledForReset
$cfrom :: forall x.
DerivationEventHasCancelledForReset
-> Rep DerivationEventHasCancelledForReset x
Generic, Int -> DerivationEventHasCancelledForReset -> ShowS
[DerivationEventHasCancelledForReset] -> ShowS
DerivationEventHasCancelledForReset -> String
(Int -> DerivationEventHasCancelledForReset -> ShowS)
-> (DerivationEventHasCancelledForReset -> String)
-> ([DerivationEventHasCancelledForReset] -> ShowS)
-> Show DerivationEventHasCancelledForReset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventHasCancelledForReset] -> ShowS
$cshowList :: [DerivationEventHasCancelledForReset] -> ShowS
show :: DerivationEventHasCancelledForReset -> String
$cshow :: DerivationEventHasCancelledForReset -> String
showsPrec :: Int -> DerivationEventHasCancelledForReset -> ShowS
$cshowsPrec :: Int -> DerivationEventHasCancelledForReset -> ShowS
Show, DerivationEventHasCancelledForReset
-> DerivationEventHasCancelledForReset -> Bool
(DerivationEventHasCancelledForReset
 -> DerivationEventHasCancelledForReset -> Bool)
-> (DerivationEventHasCancelledForReset
    -> DerivationEventHasCancelledForReset -> Bool)
-> Eq DerivationEventHasCancelledForReset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventHasCancelledForReset
-> DerivationEventHasCancelledForReset -> Bool
$c/= :: DerivationEventHasCancelledForReset
-> DerivationEventHasCancelledForReset -> Bool
== :: DerivationEventHasCancelledForReset
-> DerivationEventHasCancelledForReset -> Bool
$c== :: DerivationEventHasCancelledForReset
-> DerivationEventHasCancelledForReset -> Bool
Eq, DerivationEventHasCancelledForReset -> ()
(DerivationEventHasCancelledForReset -> ())
-> NFData DerivationEventHasCancelledForReset
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventHasCancelledForReset -> ()
$crnf :: DerivationEventHasCancelledForReset -> ()
NFData, [DerivationEventHasCancelledForReset] -> Encoding
[DerivationEventHasCancelledForReset] -> Value
DerivationEventHasCancelledForReset -> Encoding
DerivationEventHasCancelledForReset -> Value
(DerivationEventHasCancelledForReset -> Value)
-> (DerivationEventHasCancelledForReset -> Encoding)
-> ([DerivationEventHasCancelledForReset] -> Value)
-> ([DerivationEventHasCancelledForReset] -> Encoding)
-> ToJSON DerivationEventHasCancelledForReset
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventHasCancelledForReset] -> Encoding
$ctoEncodingList :: [DerivationEventHasCancelledForReset] -> Encoding
toJSONList :: [DerivationEventHasCancelledForReset] -> Value
$ctoJSONList :: [DerivationEventHasCancelledForReset] -> Value
toEncoding :: DerivationEventHasCancelledForReset -> Encoding
$ctoEncoding :: DerivationEventHasCancelledForReset -> Encoding
toJSON :: DerivationEventHasCancelledForReset -> Value
$ctoJSON :: DerivationEventHasCancelledForReset -> Value
ToJSON, Value -> Parser [DerivationEventHasCancelledForReset]
Value -> Parser DerivationEventHasCancelledForReset
(Value -> Parser DerivationEventHasCancelledForReset)
-> (Value -> Parser [DerivationEventHasCancelledForReset])
-> FromJSON DerivationEventHasCancelledForReset
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventHasCancelledForReset]
$cparseJSONList :: Value -> Parser [DerivationEventHasCancelledForReset]
parseJSON :: Value -> Parser DerivationEventHasCancelledForReset
$cparseJSON :: Value -> Parser DerivationEventHasCancelledForReset
FromJSON, Proxy DerivationEventHasCancelledForReset
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventHasCancelledForReset
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventHasCancelledForReset
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventHasCancelledForReset
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventHasCancelledForReset
-> Declare (Definitions Schema) NamedSchema
ToSchema)

data DerivationEventHasCancelled = DerivationEventHasCancelled
  { DerivationEventHasCancelled -> UTCTime
time :: UTCTime
  }
  deriving ((forall x.
 DerivationEventHasCancelled -> Rep DerivationEventHasCancelled x)
-> (forall x.
    Rep DerivationEventHasCancelled x -> DerivationEventHasCancelled)
-> Generic DerivationEventHasCancelled
forall x.
Rep DerivationEventHasCancelled x -> DerivationEventHasCancelled
forall x.
DerivationEventHasCancelled -> Rep DerivationEventHasCancelled x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DerivationEventHasCancelled x -> DerivationEventHasCancelled
$cfrom :: forall x.
DerivationEventHasCancelled -> Rep DerivationEventHasCancelled x
Generic, Int -> DerivationEventHasCancelled -> ShowS
[DerivationEventHasCancelled] -> ShowS
DerivationEventHasCancelled -> String
(Int -> DerivationEventHasCancelled -> ShowS)
-> (DerivationEventHasCancelled -> String)
-> ([DerivationEventHasCancelled] -> ShowS)
-> Show DerivationEventHasCancelled
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationEventHasCancelled] -> ShowS
$cshowList :: [DerivationEventHasCancelled] -> ShowS
show :: DerivationEventHasCancelled -> String
$cshow :: DerivationEventHasCancelled -> String
showsPrec :: Int -> DerivationEventHasCancelled -> ShowS
$cshowsPrec :: Int -> DerivationEventHasCancelled -> ShowS
Show, DerivationEventHasCancelled -> DerivationEventHasCancelled -> Bool
(DerivationEventHasCancelled
 -> DerivationEventHasCancelled -> Bool)
-> (DerivationEventHasCancelled
    -> DerivationEventHasCancelled -> Bool)
-> Eq DerivationEventHasCancelled
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationEventHasCancelled -> DerivationEventHasCancelled -> Bool
$c/= :: DerivationEventHasCancelled -> DerivationEventHasCancelled -> Bool
== :: DerivationEventHasCancelled -> DerivationEventHasCancelled -> Bool
$c== :: DerivationEventHasCancelled -> DerivationEventHasCancelled -> Bool
Eq, DerivationEventHasCancelled -> ()
(DerivationEventHasCancelled -> ())
-> NFData DerivationEventHasCancelled
forall a. (a -> ()) -> NFData a
rnf :: DerivationEventHasCancelled -> ()
$crnf :: DerivationEventHasCancelled -> ()
NFData, [DerivationEventHasCancelled] -> Encoding
[DerivationEventHasCancelled] -> Value
DerivationEventHasCancelled -> Encoding
DerivationEventHasCancelled -> Value
(DerivationEventHasCancelled -> Value)
-> (DerivationEventHasCancelled -> Encoding)
-> ([DerivationEventHasCancelled] -> Value)
-> ([DerivationEventHasCancelled] -> Encoding)
-> ToJSON DerivationEventHasCancelled
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DerivationEventHasCancelled] -> Encoding
$ctoEncodingList :: [DerivationEventHasCancelled] -> Encoding
toJSONList :: [DerivationEventHasCancelled] -> Value
$ctoJSONList :: [DerivationEventHasCancelled] -> Value
toEncoding :: DerivationEventHasCancelled -> Encoding
$ctoEncoding :: DerivationEventHasCancelled -> Encoding
toJSON :: DerivationEventHasCancelled -> Value
$ctoJSON :: DerivationEventHasCancelled -> Value
ToJSON, Value -> Parser [DerivationEventHasCancelled]
Value -> Parser DerivationEventHasCancelled
(Value -> Parser DerivationEventHasCancelled)
-> (Value -> Parser [DerivationEventHasCancelled])
-> FromJSON DerivationEventHasCancelled
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DerivationEventHasCancelled]
$cparseJSONList :: Value -> Parser [DerivationEventHasCancelled]
parseJSON :: Value -> Parser DerivationEventHasCancelled
$cparseJSON :: Value -> Parser DerivationEventHasCancelled
FromJSON, Proxy DerivationEventHasCancelled
-> Declare (Definitions Schema) NamedSchema
(Proxy DerivationEventHasCancelled
 -> Declare (Definitions Schema) NamedSchema)
-> ToSchema DerivationEventHasCancelled
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy DerivationEventHasCancelled
-> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DerivationEventHasCancelled
-> Declare (Definitions Schema) NamedSchema
ToSchema)