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

module Hercules.API.Projects.CreateUserEffectTokenResponse where

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

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