{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Hercules.API.Accounts.AccountSettings where
import Data.OpenApi qualified as O3
import Hercules.API.Prelude
data AccountSettings = AccountSettings
{
AccountSettings -> Bool
enableNewRepos :: Bool
}
deriving ((forall x. AccountSettings -> Rep AccountSettings x)
-> (forall x. Rep AccountSettings x -> AccountSettings)
-> Generic AccountSettings
forall x. Rep AccountSettings x -> AccountSettings
forall x. AccountSettings -> Rep AccountSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccountSettings -> Rep AccountSettings x
from :: forall x. AccountSettings -> Rep AccountSettings x
$cto :: forall x. Rep AccountSettings x -> AccountSettings
to :: forall x. Rep AccountSettings x -> AccountSettings
Generic, Int -> AccountSettings -> ShowS
[AccountSettings] -> ShowS
AccountSettings -> String
(Int -> AccountSettings -> ShowS)
-> (AccountSettings -> String)
-> ([AccountSettings] -> ShowS)
-> Show AccountSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccountSettings -> ShowS
showsPrec :: Int -> AccountSettings -> ShowS
$cshow :: AccountSettings -> String
show :: AccountSettings -> String
$cshowList :: [AccountSettings] -> ShowS
showList :: [AccountSettings] -> ShowS
Show, AccountSettings -> AccountSettings -> Bool
(AccountSettings -> AccountSettings -> Bool)
-> (AccountSettings -> AccountSettings -> Bool)
-> Eq AccountSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccountSettings -> AccountSettings -> Bool
== :: AccountSettings -> AccountSettings -> Bool
$c/= :: AccountSettings -> AccountSettings -> Bool
/= :: AccountSettings -> AccountSettings -> Bool
Eq)
deriving anyclass (AccountSettings -> ()
(AccountSettings -> ()) -> NFData AccountSettings
forall a. (a -> ()) -> NFData a
$crnf :: AccountSettings -> ()
rnf :: AccountSettings -> ()
NFData, [AccountSettings] -> Value
[AccountSettings] -> Encoding
AccountSettings -> Value
AccountSettings -> Encoding
(AccountSettings -> Value)
-> (AccountSettings -> Encoding)
-> ([AccountSettings] -> Value)
-> ([AccountSettings] -> Encoding)
-> ToJSON AccountSettings
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: AccountSettings -> Value
toJSON :: AccountSettings -> Value
$ctoEncoding :: AccountSettings -> Encoding
toEncoding :: AccountSettings -> Encoding
$ctoJSONList :: [AccountSettings] -> Value
toJSONList :: [AccountSettings] -> Value
$ctoEncodingList :: [AccountSettings] -> Encoding
toEncodingList :: [AccountSettings] -> Encoding
ToJSON, Value -> Parser [AccountSettings]
Value -> Parser AccountSettings
(Value -> Parser AccountSettings)
-> (Value -> Parser [AccountSettings]) -> FromJSON AccountSettings
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser AccountSettings
parseJSON :: Value -> Parser AccountSettings
$cparseJSONList :: Value -> Parser [AccountSettings]
parseJSONList :: Value -> Parser [AccountSettings]
FromJSON, Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
(Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema)
-> ToSchema AccountSettings
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable AccountSettings
Typeable AccountSettings =>
(Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema)
-> ToSchema AccountSettings
Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy AccountSettings -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)