{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}

module Hercules.API.Build.Log where

import Data.OpenApi qualified as O3
import Hercules.API.Build.LogLine
import Hercules.API.Prelude

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