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