module Mensam.API.Route.Api.User where
import Mensam.API.Aeson
import Mensam.API.Aeson.StaticText
import Mensam.API.Data.User
import Mensam.API.Data.User.Password
import Mensam.API.Data.User.Username
import Data.Aeson qualified as A
import Data.Kind
import Data.Text qualified as T
import Data.Time qualified as T
import Deriving.Aeson qualified as A
import GHC.Generics
import Servant.API hiding (BasicAuth)
import Servant.API.ImageJpeg
import Servant.Auth
import Servant.Auth.JWT.WithSession
import Text.Email.Parser
type Routes :: Type -> Type
data Routes route = Routes
{ forall route.
Routes route
-> route
:- (Summary "Login"
:> (Description "Login to your user account.\n"
:> ("login"
:> (Auth '[BasicAuth, JWTWithSession] UserAuthenticated
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseLogin, WithStatus 401 ErrorBasicAuth,
WithStatus 500 ()]))))
routeLogin ::
route
:- Summary "Login"
:> Description
"Login to your user account.\n"
:> "login"
:> Auth '[BasicAuth, JWTWithSession] UserAuthenticated
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseLogin
, WithStatus 401 ErrorBasicAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Logout"
:> (Description
"Logout from a user session.\nThe token used with this request will be invalidated.\n"
:> ("logout"
:> (Auth '[JWTWithSession] UserAuthenticated
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseLogout, WithStatus 401 ErrorBearerAuth,
WithStatus 500 ()]))))
routeLogout ::
route
:- Summary "Logout"
:> Description
"Logout from a user session.\n\
\The token used with this request will be invalidated.\n"
:> "logout"
:> Auth '[JWTWithSession] UserAuthenticated
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseLogout
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Register"
:> (Description
"Register a new user account.\nA confirmation email will be sent to the given email address.\n"
:> ("register"
:> (ReqBody' '[Lenient, Required] '[JSON] RequestRegister
:> UVerb
'POST
'[JSON]
'[WithStatus 201 ResponseRegister,
WithStatus 400 ErrorParseBodyJson,
WithStatus 409 (StaticText "Username is taken."),
WithStatus 500 ()]))))
routeRegister ::
route
:- Summary "Register"
:> Description
"Register a new user account.\n\
\A confirmation email will be sent to the given email address.\n"
:> "register"
:> ReqBody' '[Lenient, Required] '[JSON] RequestRegister
:> UVerb
POST
'[JSON]
[ WithStatus 201 ResponseRegister
, WithStatus 400 ErrorParseBodyJson
, WithStatus 409 (StaticText "Username is taken.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Change Password"
:> (Description "Set a new password for your user account.\n"
:> ("password"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestPasswordChange
:> UVerb
'PATCH
'[JSON]
'[WithStatus 200 ResponsePasswordChange,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 500 ()])))))
routePasswordChange ::
route
:- Summary "Change Password"
:> Description
"Set a new password for your user account.\n"
:> "password"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestPasswordChange
:> UVerb
PATCH
'[JSON]
[ WithStatus 200 ResponsePasswordChange
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Change Profile Picture"
:> (Description
"Upload a new profile picture.\nThis overwrites any old profile picture.\n"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[ImageJpeg] ImageJpegBytes
:> UVerb
'PUT
'[JSON]
'[WithStatus 200 (StaticText "Uploaded profile picture."),
WithStatus 400 ErrorParseBodyJpeg, WithStatus 401 ErrorBearerAuth,
WithStatus 500 ()])))))
routePictureUpload ::
route
:- Summary "Change Profile Picture"
:> Description
"Upload a new profile picture.\n\
\This overwrites any old profile picture.\n"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[ImageJpeg] ImageJpegBytes
:> UVerb
PUT
'[JSON]
[ WithStatus 200 (StaticText "Uploaded profile picture.")
, WithStatus 400 ErrorParseBodyJpeg
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Delete Profile Picture"
:> (Description "Delete your current profile picture.\n"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> UVerb
'DELETE
'[JSON]
'[WithStatus 200 (StaticText "Deleted profile picture."),
WithStatus 401 ErrorBearerAuth, WithStatus 500 ()]))))
routePictureDelete ::
route
:- Summary "Delete Profile Picture"
:> Description
"Delete your current profile picture.\n"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> UVerb
DELETE
'[JSON]
[ WithStatus 200 (StaticText "Deleted profile picture.")
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "View Profile Picture"
:> (Description "View a profile picture.\n"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (QueryParam' '[Lenient, Required] "user" IdentifierUser
:> Get '[ImageJpeg] ImageJpegBytes)))))
routePictureDownload ::
route
:- Summary "View Profile Picture"
:> Description
"View a profile picture.\n"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> QueryParam' '[Lenient, Required] "user" IdentifierUser
:> Get '[ImageJpeg] ImageJpegBytes
, forall route.
Routes route
-> route
:- (Summary "Request Email Address Confirmation"
:> (Description
"Send an email to your email address including a link.\nThis email includes a link to verify your email address.\n"
:> ("confirmation"
:> ("request"
:> (Auth '[JWTWithSession] UserAuthenticated
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseConfirmationRequest,
WithStatus 401 ErrorBearerAuth, WithStatus 500 ()])))))
routeConfirmationRequest ::
route
:- Summary "Request Email Address Confirmation"
:> Description
"Send an email to your email address including a link.\n\
\This email includes a link to verify your email address.\n"
:> "confirmation"
:> "request"
:> Auth '[JWTWithSession] UserAuthenticated
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseConfirmationRequest
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Confirm Email Address"
:> (Description "Verify your email address.\n"
:> ("confirm"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestConfirm
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseConfirm,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 410 (), WithStatus 500 ()])))))
routeConfirm ::
route
:- Summary "Confirm Email Address"
:> Description
"Verify your email address.\n"
:> "confirm"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestConfirm
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseConfirm
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 410 ()
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Edit Notification Preferences"
:> (Description
"Edit your notification preferences.\nYou first have to verify your email address to be able edit your notification preferences.\n"
:> ("notificationPreferences"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestNotifications
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseNotifications,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 403 (StaticText "Email address is not verified."),
WithStatus 500 ()])))))
routeNotificationPreferences ::
route
:- Summary "Edit Notification Preferences"
:> Description
"Edit your notification preferences.\n\
\You first have to verify your email address to be able edit your notification preferences.\n"
:> "notificationPreferences"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestNotifications
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseNotifications
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (StaticText "Email address is not verified.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "View User"
:> (Description "Request detailed user information.\n"
:> ("profile"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestProfile
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseProfile,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 404 (), WithStatus 500 ()])))))
routeProfile ::
route
:- Summary "View User"
:> Description
"Request detailed user information.\n"
:> "profile"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestProfile
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseProfile
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 404 ()
, WithStatus 500 ()
]
}
deriving stock ((forall x. Routes route -> Rep (Routes route) x)
-> (forall x. Rep (Routes route) x -> Routes route)
-> Generic (Routes route)
forall x. Rep (Routes route) x -> Routes route
forall x. Routes route -> Rep (Routes route) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall route x. Rep (Routes route) x -> Routes route
forall route x. Routes route -> Rep (Routes route) x
$cfrom :: forall route x. Routes route -> Rep (Routes route) x
from :: forall x. Routes route -> Rep (Routes route) x
$cto :: forall route x. Rep (Routes route) x -> Routes route
to :: forall x. Rep (Routes route) x -> Routes route
Generic)
type ResponseLogin :: Type
data ResponseLogin = MkResponseLogin
{ ResponseLogin -> Jwt
responseLoginJwt :: Jwt
, ResponseLogin -> Maybe UTCTime
responseLoginExpiration :: Maybe T.UTCTime
, ResponseLogin -> IdentifierUser
responseLoginId :: IdentifierUser
}
deriving stock (ResponseLogin -> ResponseLogin -> Bool
(ResponseLogin -> ResponseLogin -> Bool)
-> (ResponseLogin -> ResponseLogin -> Bool) -> Eq ResponseLogin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseLogin -> ResponseLogin -> Bool
== :: ResponseLogin -> ResponseLogin -> Bool
$c/= :: ResponseLogin -> ResponseLogin -> Bool
/= :: ResponseLogin -> ResponseLogin -> Bool
Eq, (forall x. ResponseLogin -> Rep ResponseLogin x)
-> (forall x. Rep ResponseLogin x -> ResponseLogin)
-> Generic ResponseLogin
forall x. Rep ResponseLogin x -> ResponseLogin
forall x. ResponseLogin -> Rep ResponseLogin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseLogin -> Rep ResponseLogin x
from :: forall x. ResponseLogin -> Rep ResponseLogin x
$cto :: forall x. Rep ResponseLogin x -> ResponseLogin
to :: forall x. Rep ResponseLogin x -> ResponseLogin
Generic, Eq ResponseLogin
Eq ResponseLogin =>
(ResponseLogin -> ResponseLogin -> Ordering)
-> (ResponseLogin -> ResponseLogin -> Bool)
-> (ResponseLogin -> ResponseLogin -> Bool)
-> (ResponseLogin -> ResponseLogin -> Bool)
-> (ResponseLogin -> ResponseLogin -> Bool)
-> (ResponseLogin -> ResponseLogin -> ResponseLogin)
-> (ResponseLogin -> ResponseLogin -> ResponseLogin)
-> Ord ResponseLogin
ResponseLogin -> ResponseLogin -> Bool
ResponseLogin -> ResponseLogin -> Ordering
ResponseLogin -> ResponseLogin -> ResponseLogin
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseLogin -> ResponseLogin -> Ordering
compare :: ResponseLogin -> ResponseLogin -> Ordering
$c< :: ResponseLogin -> ResponseLogin -> Bool
< :: ResponseLogin -> ResponseLogin -> Bool
$c<= :: ResponseLogin -> ResponseLogin -> Bool
<= :: ResponseLogin -> ResponseLogin -> Bool
$c> :: ResponseLogin -> ResponseLogin -> Bool
> :: ResponseLogin -> ResponseLogin -> Bool
$c>= :: ResponseLogin -> ResponseLogin -> Bool
>= :: ResponseLogin -> ResponseLogin -> Bool
$cmax :: ResponseLogin -> ResponseLogin -> ResponseLogin
max :: ResponseLogin -> ResponseLogin -> ResponseLogin
$cmin :: ResponseLogin -> ResponseLogin -> ResponseLogin
min :: ResponseLogin -> ResponseLogin -> ResponseLogin
Ord, ReadPrec [ResponseLogin]
ReadPrec ResponseLogin
Int -> ReadS ResponseLogin
ReadS [ResponseLogin]
(Int -> ReadS ResponseLogin)
-> ReadS [ResponseLogin]
-> ReadPrec ResponseLogin
-> ReadPrec [ResponseLogin]
-> Read ResponseLogin
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseLogin
readsPrec :: Int -> ReadS ResponseLogin
$creadList :: ReadS [ResponseLogin]
readList :: ReadS [ResponseLogin]
$creadPrec :: ReadPrec ResponseLogin
readPrec :: ReadPrec ResponseLogin
$creadListPrec :: ReadPrec [ResponseLogin]
readListPrec :: ReadPrec [ResponseLogin]
Read, Int -> ResponseLogin -> ShowS
[ResponseLogin] -> ShowS
ResponseLogin -> String
(Int -> ResponseLogin -> ShowS)
-> (ResponseLogin -> String)
-> ([ResponseLogin] -> ShowS)
-> Show ResponseLogin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseLogin -> ShowS
showsPrec :: Int -> ResponseLogin -> ShowS
$cshow :: ResponseLogin -> String
show :: ResponseLogin -> String
$cshowList :: [ResponseLogin] -> ShowS
showList :: [ResponseLogin] -> ShowS
Show)
deriving
(Value -> Parser [ResponseLogin]
Value -> Parser ResponseLogin
(Value -> Parser ResponseLogin)
-> (Value -> Parser [ResponseLogin]) -> FromJSON ResponseLogin
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseLogin
parseJSON :: Value -> Parser ResponseLogin
$cparseJSONList :: Value -> Parser [ResponseLogin]
parseJSONList :: Value -> Parser [ResponseLogin]
A.FromJSON, [ResponseLogin] -> Value
[ResponseLogin] -> Encoding
ResponseLogin -> Value
ResponseLogin -> Encoding
(ResponseLogin -> Value)
-> (ResponseLogin -> Encoding)
-> ([ResponseLogin] -> Value)
-> ([ResponseLogin] -> Encoding)
-> ToJSON ResponseLogin
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseLogin -> Value
toJSON :: ResponseLogin -> Value
$ctoEncoding :: ResponseLogin -> Encoding
toEncoding :: ResponseLogin -> Encoding
$ctoJSONList :: [ResponseLogin] -> Value
toJSONList :: [ResponseLogin] -> Value
$ctoEncodingList :: [ResponseLogin] -> Encoding
toEncodingList :: [ResponseLogin] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseLogin") ResponseLogin
type Jwt :: Type
newtype Jwt = MkJwt {Jwt -> Text
unJwt :: T.Text}
deriving stock (Jwt -> Jwt -> Bool
(Jwt -> Jwt -> Bool) -> (Jwt -> Jwt -> Bool) -> Eq Jwt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Jwt -> Jwt -> Bool
== :: Jwt -> Jwt -> Bool
$c/= :: Jwt -> Jwt -> Bool
/= :: Jwt -> Jwt -> Bool
Eq, (forall x. Jwt -> Rep Jwt x)
-> (forall x. Rep Jwt x -> Jwt) -> Generic Jwt
forall x. Rep Jwt x -> Jwt
forall x. Jwt -> Rep Jwt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Jwt -> Rep Jwt x
from :: forall x. Jwt -> Rep Jwt x
$cto :: forall x. Rep Jwt x -> Jwt
to :: forall x. Rep Jwt x -> Jwt
Generic, Eq Jwt
Eq Jwt =>
(Jwt -> Jwt -> Ordering)
-> (Jwt -> Jwt -> Bool)
-> (Jwt -> Jwt -> Bool)
-> (Jwt -> Jwt -> Bool)
-> (Jwt -> Jwt -> Bool)
-> (Jwt -> Jwt -> Jwt)
-> (Jwt -> Jwt -> Jwt)
-> Ord Jwt
Jwt -> Jwt -> Bool
Jwt -> Jwt -> Ordering
Jwt -> Jwt -> Jwt
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Jwt -> Jwt -> Ordering
compare :: Jwt -> Jwt -> Ordering
$c< :: Jwt -> Jwt -> Bool
< :: Jwt -> Jwt -> Bool
$c<= :: Jwt -> Jwt -> Bool
<= :: Jwt -> Jwt -> Bool
$c> :: Jwt -> Jwt -> Bool
> :: Jwt -> Jwt -> Bool
$c>= :: Jwt -> Jwt -> Bool
>= :: Jwt -> Jwt -> Bool
$cmax :: Jwt -> Jwt -> Jwt
max :: Jwt -> Jwt -> Jwt
$cmin :: Jwt -> Jwt -> Jwt
min :: Jwt -> Jwt -> Jwt
Ord, ReadPrec [Jwt]
ReadPrec Jwt
Int -> ReadS Jwt
ReadS [Jwt]
(Int -> ReadS Jwt)
-> ReadS [Jwt] -> ReadPrec Jwt -> ReadPrec [Jwt] -> Read Jwt
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Jwt
readsPrec :: Int -> ReadS Jwt
$creadList :: ReadS [Jwt]
readList :: ReadS [Jwt]
$creadPrec :: ReadPrec Jwt
readPrec :: ReadPrec Jwt
$creadListPrec :: ReadPrec [Jwt]
readListPrec :: ReadPrec [Jwt]
Read, Int -> Jwt -> ShowS
[Jwt] -> ShowS
Jwt -> String
(Int -> Jwt -> ShowS)
-> (Jwt -> String) -> ([Jwt] -> ShowS) -> Show Jwt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Jwt -> ShowS
showsPrec :: Int -> Jwt -> ShowS
$cshow :: Jwt -> String
show :: Jwt -> String
$cshowList :: [Jwt] -> ShowS
showList :: [Jwt] -> ShowS
Show)
deriving newtype (Value -> Parser [Jwt]
Value -> Parser Jwt
(Value -> Parser Jwt) -> (Value -> Parser [Jwt]) -> FromJSON Jwt
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Jwt
parseJSON :: Value -> Parser Jwt
$cparseJSONList :: Value -> Parser [Jwt]
parseJSONList :: Value -> Parser [Jwt]
A.FromJSON, [Jwt] -> Value
[Jwt] -> Encoding
Jwt -> Value
Jwt -> Encoding
(Jwt -> Value)
-> (Jwt -> Encoding)
-> ([Jwt] -> Value)
-> ([Jwt] -> Encoding)
-> ToJSON Jwt
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Jwt -> Value
toJSON :: Jwt -> Value
$ctoEncoding :: Jwt -> Encoding
toEncoding :: Jwt -> Encoding
$ctoJSONList :: [Jwt] -> Value
toJSONList :: [Jwt] -> Value
$ctoEncodingList :: [Jwt] -> Encoding
toEncodingList :: [Jwt] -> Encoding
A.ToJSON)
type ResponseLogout :: Type
newtype ResponseLogout = MkResponseLogout
{ ResponseLogout -> ()
responseLogoutUnit :: ()
}
deriving stock (ResponseLogout -> ResponseLogout -> Bool
(ResponseLogout -> ResponseLogout -> Bool)
-> (ResponseLogout -> ResponseLogout -> Bool) -> Eq ResponseLogout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseLogout -> ResponseLogout -> Bool
== :: ResponseLogout -> ResponseLogout -> Bool
$c/= :: ResponseLogout -> ResponseLogout -> Bool
/= :: ResponseLogout -> ResponseLogout -> Bool
Eq, (forall x. ResponseLogout -> Rep ResponseLogout x)
-> (forall x. Rep ResponseLogout x -> ResponseLogout)
-> Generic ResponseLogout
forall x. Rep ResponseLogout x -> ResponseLogout
forall x. ResponseLogout -> Rep ResponseLogout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseLogout -> Rep ResponseLogout x
from :: forall x. ResponseLogout -> Rep ResponseLogout x
$cto :: forall x. Rep ResponseLogout x -> ResponseLogout
to :: forall x. Rep ResponseLogout x -> ResponseLogout
Generic, Eq ResponseLogout
Eq ResponseLogout =>
(ResponseLogout -> ResponseLogout -> Ordering)
-> (ResponseLogout -> ResponseLogout -> Bool)
-> (ResponseLogout -> ResponseLogout -> Bool)
-> (ResponseLogout -> ResponseLogout -> Bool)
-> (ResponseLogout -> ResponseLogout -> Bool)
-> (ResponseLogout -> ResponseLogout -> ResponseLogout)
-> (ResponseLogout -> ResponseLogout -> ResponseLogout)
-> Ord ResponseLogout
ResponseLogout -> ResponseLogout -> Bool
ResponseLogout -> ResponseLogout -> Ordering
ResponseLogout -> ResponseLogout -> ResponseLogout
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseLogout -> ResponseLogout -> Ordering
compare :: ResponseLogout -> ResponseLogout -> Ordering
$c< :: ResponseLogout -> ResponseLogout -> Bool
< :: ResponseLogout -> ResponseLogout -> Bool
$c<= :: ResponseLogout -> ResponseLogout -> Bool
<= :: ResponseLogout -> ResponseLogout -> Bool
$c> :: ResponseLogout -> ResponseLogout -> Bool
> :: ResponseLogout -> ResponseLogout -> Bool
$c>= :: ResponseLogout -> ResponseLogout -> Bool
>= :: ResponseLogout -> ResponseLogout -> Bool
$cmax :: ResponseLogout -> ResponseLogout -> ResponseLogout
max :: ResponseLogout -> ResponseLogout -> ResponseLogout
$cmin :: ResponseLogout -> ResponseLogout -> ResponseLogout
min :: ResponseLogout -> ResponseLogout -> ResponseLogout
Ord, ReadPrec [ResponseLogout]
ReadPrec ResponseLogout
Int -> ReadS ResponseLogout
ReadS [ResponseLogout]
(Int -> ReadS ResponseLogout)
-> ReadS [ResponseLogout]
-> ReadPrec ResponseLogout
-> ReadPrec [ResponseLogout]
-> Read ResponseLogout
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseLogout
readsPrec :: Int -> ReadS ResponseLogout
$creadList :: ReadS [ResponseLogout]
readList :: ReadS [ResponseLogout]
$creadPrec :: ReadPrec ResponseLogout
readPrec :: ReadPrec ResponseLogout
$creadListPrec :: ReadPrec [ResponseLogout]
readListPrec :: ReadPrec [ResponseLogout]
Read, Int -> ResponseLogout -> ShowS
[ResponseLogout] -> ShowS
ResponseLogout -> String
(Int -> ResponseLogout -> ShowS)
-> (ResponseLogout -> String)
-> ([ResponseLogout] -> ShowS)
-> Show ResponseLogout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseLogout -> ShowS
showsPrec :: Int -> ResponseLogout -> ShowS
$cshow :: ResponseLogout -> String
show :: ResponseLogout -> String
$cshowList :: [ResponseLogout] -> ShowS
showList :: [ResponseLogout] -> ShowS
Show)
deriving
(Value -> Parser [ResponseLogout]
Value -> Parser ResponseLogout
(Value -> Parser ResponseLogout)
-> (Value -> Parser [ResponseLogout]) -> FromJSON ResponseLogout
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseLogout
parseJSON :: Value -> Parser ResponseLogout
$cparseJSONList :: Value -> Parser [ResponseLogout]
parseJSONList :: Value -> Parser [ResponseLogout]
A.FromJSON, [ResponseLogout] -> Value
[ResponseLogout] -> Encoding
ResponseLogout -> Value
ResponseLogout -> Encoding
(ResponseLogout -> Value)
-> (ResponseLogout -> Encoding)
-> ([ResponseLogout] -> Value)
-> ([ResponseLogout] -> Encoding)
-> ToJSON ResponseLogout
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseLogout -> Value
toJSON :: ResponseLogout -> Value
$ctoEncoding :: ResponseLogout -> Encoding
toEncoding :: ResponseLogout -> Encoding
$ctoJSONList :: [ResponseLogout] -> Value
toJSONList :: [ResponseLogout] -> Value
$ctoEncodingList :: [ResponseLogout] -> Encoding
toEncodingList :: [ResponseLogout] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseLogout") ResponseLogout
type RequestRegister :: Type
data RequestRegister = MkRequestRegister
{ RequestRegister -> Username
requestRegisterName :: Username
, RequestRegister -> Password
requestRegisterPassword :: Password
, RequestRegister -> EmailAddress
requestRegisterEmail :: EmailAddress
, RequestRegister -> Bool
requestRegisterEmailVisible :: Bool
, RequestRegister -> Bool
requestRegisterEmailNotifications :: Bool
}
deriving stock (RequestRegister -> RequestRegister -> Bool
(RequestRegister -> RequestRegister -> Bool)
-> (RequestRegister -> RequestRegister -> Bool)
-> Eq RequestRegister
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestRegister -> RequestRegister -> Bool
== :: RequestRegister -> RequestRegister -> Bool
$c/= :: RequestRegister -> RequestRegister -> Bool
/= :: RequestRegister -> RequestRegister -> Bool
Eq, (forall x. RequestRegister -> Rep RequestRegister x)
-> (forall x. Rep RequestRegister x -> RequestRegister)
-> Generic RequestRegister
forall x. Rep RequestRegister x -> RequestRegister
forall x. RequestRegister -> Rep RequestRegister x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestRegister -> Rep RequestRegister x
from :: forall x. RequestRegister -> Rep RequestRegister x
$cto :: forall x. Rep RequestRegister x -> RequestRegister
to :: forall x. Rep RequestRegister x -> RequestRegister
Generic, Eq RequestRegister
Eq RequestRegister =>
(RequestRegister -> RequestRegister -> Ordering)
-> (RequestRegister -> RequestRegister -> Bool)
-> (RequestRegister -> RequestRegister -> Bool)
-> (RequestRegister -> RequestRegister -> Bool)
-> (RequestRegister -> RequestRegister -> Bool)
-> (RequestRegister -> RequestRegister -> RequestRegister)
-> (RequestRegister -> RequestRegister -> RequestRegister)
-> Ord RequestRegister
RequestRegister -> RequestRegister -> Bool
RequestRegister -> RequestRegister -> Ordering
RequestRegister -> RequestRegister -> RequestRegister
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RequestRegister -> RequestRegister -> Ordering
compare :: RequestRegister -> RequestRegister -> Ordering
$c< :: RequestRegister -> RequestRegister -> Bool
< :: RequestRegister -> RequestRegister -> Bool
$c<= :: RequestRegister -> RequestRegister -> Bool
<= :: RequestRegister -> RequestRegister -> Bool
$c> :: RequestRegister -> RequestRegister -> Bool
> :: RequestRegister -> RequestRegister -> Bool
$c>= :: RequestRegister -> RequestRegister -> Bool
>= :: RequestRegister -> RequestRegister -> Bool
$cmax :: RequestRegister -> RequestRegister -> RequestRegister
max :: RequestRegister -> RequestRegister -> RequestRegister
$cmin :: RequestRegister -> RequestRegister -> RequestRegister
min :: RequestRegister -> RequestRegister -> RequestRegister
Ord, ReadPrec [RequestRegister]
ReadPrec RequestRegister
Int -> ReadS RequestRegister
ReadS [RequestRegister]
(Int -> ReadS RequestRegister)
-> ReadS [RequestRegister]
-> ReadPrec RequestRegister
-> ReadPrec [RequestRegister]
-> Read RequestRegister
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestRegister
readsPrec :: Int -> ReadS RequestRegister
$creadList :: ReadS [RequestRegister]
readList :: ReadS [RequestRegister]
$creadPrec :: ReadPrec RequestRegister
readPrec :: ReadPrec RequestRegister
$creadListPrec :: ReadPrec [RequestRegister]
readListPrec :: ReadPrec [RequestRegister]
Read, Int -> RequestRegister -> ShowS
[RequestRegister] -> ShowS
RequestRegister -> String
(Int -> RequestRegister -> ShowS)
-> (RequestRegister -> String)
-> ([RequestRegister] -> ShowS)
-> Show RequestRegister
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestRegister -> ShowS
showsPrec :: Int -> RequestRegister -> ShowS
$cshow :: RequestRegister -> String
show :: RequestRegister -> String
$cshowList :: [RequestRegister] -> ShowS
showList :: [RequestRegister] -> ShowS
Show)
deriving
(Value -> Parser [RequestRegister]
Value -> Parser RequestRegister
(Value -> Parser RequestRegister)
-> (Value -> Parser [RequestRegister]) -> FromJSON RequestRegister
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestRegister
parseJSON :: Value -> Parser RequestRegister
$cparseJSONList :: Value -> Parser [RequestRegister]
parseJSONList :: Value -> Parser [RequestRegister]
A.FromJSON, [RequestRegister] -> Value
[RequestRegister] -> Encoding
RequestRegister -> Value
RequestRegister -> Encoding
(RequestRegister -> Value)
-> (RequestRegister -> Encoding)
-> ([RequestRegister] -> Value)
-> ([RequestRegister] -> Encoding)
-> ToJSON RequestRegister
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestRegister -> Value
toJSON :: RequestRegister -> Value
$ctoEncoding :: RequestRegister -> Encoding
toEncoding :: RequestRegister -> Encoding
$ctoJSONList :: [RequestRegister] -> Value
toJSONList :: [RequestRegister] -> Value
$ctoEncodingList :: [RequestRegister] -> Encoding
toEncodingList :: [RequestRegister] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestRegister") RequestRegister
type ResponseRegister :: Type
newtype ResponseRegister = MkResponseRegister
{ ResponseRegister -> Bool
responseRegisterEmailSent :: Bool
}
deriving stock (ResponseRegister -> ResponseRegister -> Bool
(ResponseRegister -> ResponseRegister -> Bool)
-> (ResponseRegister -> ResponseRegister -> Bool)
-> Eq ResponseRegister
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseRegister -> ResponseRegister -> Bool
== :: ResponseRegister -> ResponseRegister -> Bool
$c/= :: ResponseRegister -> ResponseRegister -> Bool
/= :: ResponseRegister -> ResponseRegister -> Bool
Eq, (forall x. ResponseRegister -> Rep ResponseRegister x)
-> (forall x. Rep ResponseRegister x -> ResponseRegister)
-> Generic ResponseRegister
forall x. Rep ResponseRegister x -> ResponseRegister
forall x. ResponseRegister -> Rep ResponseRegister x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseRegister -> Rep ResponseRegister x
from :: forall x. ResponseRegister -> Rep ResponseRegister x
$cto :: forall x. Rep ResponseRegister x -> ResponseRegister
to :: forall x. Rep ResponseRegister x -> ResponseRegister
Generic, Eq ResponseRegister
Eq ResponseRegister =>
(ResponseRegister -> ResponseRegister -> Ordering)
-> (ResponseRegister -> ResponseRegister -> Bool)
-> (ResponseRegister -> ResponseRegister -> Bool)
-> (ResponseRegister -> ResponseRegister -> Bool)
-> (ResponseRegister -> ResponseRegister -> Bool)
-> (ResponseRegister -> ResponseRegister -> ResponseRegister)
-> (ResponseRegister -> ResponseRegister -> ResponseRegister)
-> Ord ResponseRegister
ResponseRegister -> ResponseRegister -> Bool
ResponseRegister -> ResponseRegister -> Ordering
ResponseRegister -> ResponseRegister -> ResponseRegister
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseRegister -> ResponseRegister -> Ordering
compare :: ResponseRegister -> ResponseRegister -> Ordering
$c< :: ResponseRegister -> ResponseRegister -> Bool
< :: ResponseRegister -> ResponseRegister -> Bool
$c<= :: ResponseRegister -> ResponseRegister -> Bool
<= :: ResponseRegister -> ResponseRegister -> Bool
$c> :: ResponseRegister -> ResponseRegister -> Bool
> :: ResponseRegister -> ResponseRegister -> Bool
$c>= :: ResponseRegister -> ResponseRegister -> Bool
>= :: ResponseRegister -> ResponseRegister -> Bool
$cmax :: ResponseRegister -> ResponseRegister -> ResponseRegister
max :: ResponseRegister -> ResponseRegister -> ResponseRegister
$cmin :: ResponseRegister -> ResponseRegister -> ResponseRegister
min :: ResponseRegister -> ResponseRegister -> ResponseRegister
Ord, ReadPrec [ResponseRegister]
ReadPrec ResponseRegister
Int -> ReadS ResponseRegister
ReadS [ResponseRegister]
(Int -> ReadS ResponseRegister)
-> ReadS [ResponseRegister]
-> ReadPrec ResponseRegister
-> ReadPrec [ResponseRegister]
-> Read ResponseRegister
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseRegister
readsPrec :: Int -> ReadS ResponseRegister
$creadList :: ReadS [ResponseRegister]
readList :: ReadS [ResponseRegister]
$creadPrec :: ReadPrec ResponseRegister
readPrec :: ReadPrec ResponseRegister
$creadListPrec :: ReadPrec [ResponseRegister]
readListPrec :: ReadPrec [ResponseRegister]
Read, Int -> ResponseRegister -> ShowS
[ResponseRegister] -> ShowS
ResponseRegister -> String
(Int -> ResponseRegister -> ShowS)
-> (ResponseRegister -> String)
-> ([ResponseRegister] -> ShowS)
-> Show ResponseRegister
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseRegister -> ShowS
showsPrec :: Int -> ResponseRegister -> ShowS
$cshow :: ResponseRegister -> String
show :: ResponseRegister -> String
$cshowList :: [ResponseRegister] -> ShowS
showList :: [ResponseRegister] -> ShowS
Show)
deriving
(Value -> Parser [ResponseRegister]
Value -> Parser ResponseRegister
(Value -> Parser ResponseRegister)
-> (Value -> Parser [ResponseRegister])
-> FromJSON ResponseRegister
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseRegister
parseJSON :: Value -> Parser ResponseRegister
$cparseJSONList :: Value -> Parser [ResponseRegister]
parseJSONList :: Value -> Parser [ResponseRegister]
A.FromJSON, [ResponseRegister] -> Value
[ResponseRegister] -> Encoding
ResponseRegister -> Value
ResponseRegister -> Encoding
(ResponseRegister -> Value)
-> (ResponseRegister -> Encoding)
-> ([ResponseRegister] -> Value)
-> ([ResponseRegister] -> Encoding)
-> ToJSON ResponseRegister
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseRegister -> Value
toJSON :: ResponseRegister -> Value
$ctoEncoding :: ResponseRegister -> Encoding
toEncoding :: ResponseRegister -> Encoding
$ctoJSONList :: [ResponseRegister] -> Value
toJSONList :: [ResponseRegister] -> Value
$ctoEncodingList :: [ResponseRegister] -> Encoding
toEncodingList :: [ResponseRegister] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseRegister") ResponseRegister
type RequestPasswordChange :: Type
newtype RequestPasswordChange = MkRequestPasswordChange
{ RequestPasswordChange -> Password
requestPasswordChangeNewPassword :: Password
}
deriving stock (RequestPasswordChange -> RequestPasswordChange -> Bool
(RequestPasswordChange -> RequestPasswordChange -> Bool)
-> (RequestPasswordChange -> RequestPasswordChange -> Bool)
-> Eq RequestPasswordChange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestPasswordChange -> RequestPasswordChange -> Bool
== :: RequestPasswordChange -> RequestPasswordChange -> Bool
$c/= :: RequestPasswordChange -> RequestPasswordChange -> Bool
/= :: RequestPasswordChange -> RequestPasswordChange -> Bool
Eq, (forall x. RequestPasswordChange -> Rep RequestPasswordChange x)
-> (forall x. Rep RequestPasswordChange x -> RequestPasswordChange)
-> Generic RequestPasswordChange
forall x. Rep RequestPasswordChange x -> RequestPasswordChange
forall x. RequestPasswordChange -> Rep RequestPasswordChange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestPasswordChange -> Rep RequestPasswordChange x
from :: forall x. RequestPasswordChange -> Rep RequestPasswordChange x
$cto :: forall x. Rep RequestPasswordChange x -> RequestPasswordChange
to :: forall x. Rep RequestPasswordChange x -> RequestPasswordChange
Generic, Eq RequestPasswordChange
Eq RequestPasswordChange =>
(RequestPasswordChange -> RequestPasswordChange -> Ordering)
-> (RequestPasswordChange -> RequestPasswordChange -> Bool)
-> (RequestPasswordChange -> RequestPasswordChange -> Bool)
-> (RequestPasswordChange -> RequestPasswordChange -> Bool)
-> (RequestPasswordChange -> RequestPasswordChange -> Bool)
-> (RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange)
-> (RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange)
-> Ord RequestPasswordChange
RequestPasswordChange -> RequestPasswordChange -> Bool
RequestPasswordChange -> RequestPasswordChange -> Ordering
RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RequestPasswordChange -> RequestPasswordChange -> Ordering
compare :: RequestPasswordChange -> RequestPasswordChange -> Ordering
$c< :: RequestPasswordChange -> RequestPasswordChange -> Bool
< :: RequestPasswordChange -> RequestPasswordChange -> Bool
$c<= :: RequestPasswordChange -> RequestPasswordChange -> Bool
<= :: RequestPasswordChange -> RequestPasswordChange -> Bool
$c> :: RequestPasswordChange -> RequestPasswordChange -> Bool
> :: RequestPasswordChange -> RequestPasswordChange -> Bool
$c>= :: RequestPasswordChange -> RequestPasswordChange -> Bool
>= :: RequestPasswordChange -> RequestPasswordChange -> Bool
$cmax :: RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange
max :: RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange
$cmin :: RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange
min :: RequestPasswordChange
-> RequestPasswordChange -> RequestPasswordChange
Ord, ReadPrec [RequestPasswordChange]
ReadPrec RequestPasswordChange
Int -> ReadS RequestPasswordChange
ReadS [RequestPasswordChange]
(Int -> ReadS RequestPasswordChange)
-> ReadS [RequestPasswordChange]
-> ReadPrec RequestPasswordChange
-> ReadPrec [RequestPasswordChange]
-> Read RequestPasswordChange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestPasswordChange
readsPrec :: Int -> ReadS RequestPasswordChange
$creadList :: ReadS [RequestPasswordChange]
readList :: ReadS [RequestPasswordChange]
$creadPrec :: ReadPrec RequestPasswordChange
readPrec :: ReadPrec RequestPasswordChange
$creadListPrec :: ReadPrec [RequestPasswordChange]
readListPrec :: ReadPrec [RequestPasswordChange]
Read, Int -> RequestPasswordChange -> ShowS
[RequestPasswordChange] -> ShowS
RequestPasswordChange -> String
(Int -> RequestPasswordChange -> ShowS)
-> (RequestPasswordChange -> String)
-> ([RequestPasswordChange] -> ShowS)
-> Show RequestPasswordChange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestPasswordChange -> ShowS
showsPrec :: Int -> RequestPasswordChange -> ShowS
$cshow :: RequestPasswordChange -> String
show :: RequestPasswordChange -> String
$cshowList :: [RequestPasswordChange] -> ShowS
showList :: [RequestPasswordChange] -> ShowS
Show)
deriving
(Value -> Parser [RequestPasswordChange]
Value -> Parser RequestPasswordChange
(Value -> Parser RequestPasswordChange)
-> (Value -> Parser [RequestPasswordChange])
-> FromJSON RequestPasswordChange
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestPasswordChange
parseJSON :: Value -> Parser RequestPasswordChange
$cparseJSONList :: Value -> Parser [RequestPasswordChange]
parseJSONList :: Value -> Parser [RequestPasswordChange]
A.FromJSON, [RequestPasswordChange] -> Value
[RequestPasswordChange] -> Encoding
RequestPasswordChange -> Value
RequestPasswordChange -> Encoding
(RequestPasswordChange -> Value)
-> (RequestPasswordChange -> Encoding)
-> ([RequestPasswordChange] -> Value)
-> ([RequestPasswordChange] -> Encoding)
-> ToJSON RequestPasswordChange
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestPasswordChange -> Value
toJSON :: RequestPasswordChange -> Value
$ctoEncoding :: RequestPasswordChange -> Encoding
toEncoding :: RequestPasswordChange -> Encoding
$ctoJSONList :: [RequestPasswordChange] -> Value
toJSONList :: [RequestPasswordChange] -> Value
$ctoEncodingList :: [RequestPasswordChange] -> Encoding
toEncodingList :: [RequestPasswordChange] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestPasswordChange") RequestPasswordChange
type ResponsePasswordChange :: Type
newtype ResponsePasswordChange = MkResponsePasswordChange
{ ResponsePasswordChange -> ()
responsePasswordChangeUnit :: ()
}
deriving stock (ResponsePasswordChange -> ResponsePasswordChange -> Bool
(ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> (ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> Eq ResponsePasswordChange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
== :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
$c/= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
/= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
Eq, (forall x. ResponsePasswordChange -> Rep ResponsePasswordChange x)
-> (forall x.
Rep ResponsePasswordChange x -> ResponsePasswordChange)
-> Generic ResponsePasswordChange
forall x. Rep ResponsePasswordChange x -> ResponsePasswordChange
forall x. ResponsePasswordChange -> Rep ResponsePasswordChange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponsePasswordChange -> Rep ResponsePasswordChange x
from :: forall x. ResponsePasswordChange -> Rep ResponsePasswordChange x
$cto :: forall x. Rep ResponsePasswordChange x -> ResponsePasswordChange
to :: forall x. Rep ResponsePasswordChange x -> ResponsePasswordChange
Generic, Eq ResponsePasswordChange
Eq ResponsePasswordChange =>
(ResponsePasswordChange -> ResponsePasswordChange -> Ordering)
-> (ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> (ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> (ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> (ResponsePasswordChange -> ResponsePasswordChange -> Bool)
-> (ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange)
-> (ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange)
-> Ord ResponsePasswordChange
ResponsePasswordChange -> ResponsePasswordChange -> Bool
ResponsePasswordChange -> ResponsePasswordChange -> Ordering
ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponsePasswordChange -> ResponsePasswordChange -> Ordering
compare :: ResponsePasswordChange -> ResponsePasswordChange -> Ordering
$c< :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
< :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
$c<= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
<= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
$c> :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
> :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
$c>= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
>= :: ResponsePasswordChange -> ResponsePasswordChange -> Bool
$cmax :: ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange
max :: ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange
$cmin :: ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange
min :: ResponsePasswordChange
-> ResponsePasswordChange -> ResponsePasswordChange
Ord, ReadPrec [ResponsePasswordChange]
ReadPrec ResponsePasswordChange
Int -> ReadS ResponsePasswordChange
ReadS [ResponsePasswordChange]
(Int -> ReadS ResponsePasswordChange)
-> ReadS [ResponsePasswordChange]
-> ReadPrec ResponsePasswordChange
-> ReadPrec [ResponsePasswordChange]
-> Read ResponsePasswordChange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponsePasswordChange
readsPrec :: Int -> ReadS ResponsePasswordChange
$creadList :: ReadS [ResponsePasswordChange]
readList :: ReadS [ResponsePasswordChange]
$creadPrec :: ReadPrec ResponsePasswordChange
readPrec :: ReadPrec ResponsePasswordChange
$creadListPrec :: ReadPrec [ResponsePasswordChange]
readListPrec :: ReadPrec [ResponsePasswordChange]
Read, Int -> ResponsePasswordChange -> ShowS
[ResponsePasswordChange] -> ShowS
ResponsePasswordChange -> String
(Int -> ResponsePasswordChange -> ShowS)
-> (ResponsePasswordChange -> String)
-> ([ResponsePasswordChange] -> ShowS)
-> Show ResponsePasswordChange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponsePasswordChange -> ShowS
showsPrec :: Int -> ResponsePasswordChange -> ShowS
$cshow :: ResponsePasswordChange -> String
show :: ResponsePasswordChange -> String
$cshowList :: [ResponsePasswordChange] -> ShowS
showList :: [ResponsePasswordChange] -> ShowS
Show)
deriving
(Value -> Parser [ResponsePasswordChange]
Value -> Parser ResponsePasswordChange
(Value -> Parser ResponsePasswordChange)
-> (Value -> Parser [ResponsePasswordChange])
-> FromJSON ResponsePasswordChange
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponsePasswordChange
parseJSON :: Value -> Parser ResponsePasswordChange
$cparseJSONList :: Value -> Parser [ResponsePasswordChange]
parseJSONList :: Value -> Parser [ResponsePasswordChange]
A.FromJSON, [ResponsePasswordChange] -> Value
[ResponsePasswordChange] -> Encoding
ResponsePasswordChange -> Value
ResponsePasswordChange -> Encoding
(ResponsePasswordChange -> Value)
-> (ResponsePasswordChange -> Encoding)
-> ([ResponsePasswordChange] -> Value)
-> ([ResponsePasswordChange] -> Encoding)
-> ToJSON ResponsePasswordChange
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponsePasswordChange -> Value
toJSON :: ResponsePasswordChange -> Value
$ctoEncoding :: ResponsePasswordChange -> Encoding
toEncoding :: ResponsePasswordChange -> Encoding
$ctoJSONList :: [ResponsePasswordChange] -> Value
toJSONList :: [ResponsePasswordChange] -> Value
$ctoEncodingList :: [ResponsePasswordChange] -> Encoding
toEncodingList :: [ResponsePasswordChange] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responsePasswordChange") ResponsePasswordChange
type ResponseConfirmationRequest :: Type
newtype ResponseConfirmationRequest = MkResponseConfirmationRequest
{ ResponseConfirmationRequest -> ()
responseConfirmationRequestUnit :: ()
}
deriving stock (ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
(ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> Eq ResponseConfirmationRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
== :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
$c/= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
/= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
Eq, (forall x.
ResponseConfirmationRequest -> Rep ResponseConfirmationRequest x)
-> (forall x.
Rep ResponseConfirmationRequest x -> ResponseConfirmationRequest)
-> Generic ResponseConfirmationRequest
forall x.
Rep ResponseConfirmationRequest x -> ResponseConfirmationRequest
forall x.
ResponseConfirmationRequest -> Rep ResponseConfirmationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ResponseConfirmationRequest -> Rep ResponseConfirmationRequest x
from :: forall x.
ResponseConfirmationRequest -> Rep ResponseConfirmationRequest x
$cto :: forall x.
Rep ResponseConfirmationRequest x -> ResponseConfirmationRequest
to :: forall x.
Rep ResponseConfirmationRequest x -> ResponseConfirmationRequest
Generic, Eq ResponseConfirmationRequest
Eq ResponseConfirmationRequest =>
(ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Ordering)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Bool)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest)
-> (ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest)
-> Ord ResponseConfirmationRequest
ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Ordering
ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Ordering
compare :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> Ordering
$c< :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
< :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
$c<= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
<= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
$c> :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
> :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
$c>= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
>= :: ResponseConfirmationRequest -> ResponseConfirmationRequest -> Bool
$cmax :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest
max :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest
$cmin :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest
min :: ResponseConfirmationRequest
-> ResponseConfirmationRequest -> ResponseConfirmationRequest
Ord, ReadPrec [ResponseConfirmationRequest]
ReadPrec ResponseConfirmationRequest
Int -> ReadS ResponseConfirmationRequest
ReadS [ResponseConfirmationRequest]
(Int -> ReadS ResponseConfirmationRequest)
-> ReadS [ResponseConfirmationRequest]
-> ReadPrec ResponseConfirmationRequest
-> ReadPrec [ResponseConfirmationRequest]
-> Read ResponseConfirmationRequest
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseConfirmationRequest
readsPrec :: Int -> ReadS ResponseConfirmationRequest
$creadList :: ReadS [ResponseConfirmationRequest]
readList :: ReadS [ResponseConfirmationRequest]
$creadPrec :: ReadPrec ResponseConfirmationRequest
readPrec :: ReadPrec ResponseConfirmationRequest
$creadListPrec :: ReadPrec [ResponseConfirmationRequest]
readListPrec :: ReadPrec [ResponseConfirmationRequest]
Read, Int -> ResponseConfirmationRequest -> ShowS
[ResponseConfirmationRequest] -> ShowS
ResponseConfirmationRequest -> String
(Int -> ResponseConfirmationRequest -> ShowS)
-> (ResponseConfirmationRequest -> String)
-> ([ResponseConfirmationRequest] -> ShowS)
-> Show ResponseConfirmationRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseConfirmationRequest -> ShowS
showsPrec :: Int -> ResponseConfirmationRequest -> ShowS
$cshow :: ResponseConfirmationRequest -> String
show :: ResponseConfirmationRequest -> String
$cshowList :: [ResponseConfirmationRequest] -> ShowS
showList :: [ResponseConfirmationRequest] -> ShowS
Show)
deriving
(Value -> Parser [ResponseConfirmationRequest]
Value -> Parser ResponseConfirmationRequest
(Value -> Parser ResponseConfirmationRequest)
-> (Value -> Parser [ResponseConfirmationRequest])
-> FromJSON ResponseConfirmationRequest
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseConfirmationRequest
parseJSON :: Value -> Parser ResponseConfirmationRequest
$cparseJSONList :: Value -> Parser [ResponseConfirmationRequest]
parseJSONList :: Value -> Parser [ResponseConfirmationRequest]
A.FromJSON, [ResponseConfirmationRequest] -> Value
[ResponseConfirmationRequest] -> Encoding
ResponseConfirmationRequest -> Value
ResponseConfirmationRequest -> Encoding
(ResponseConfirmationRequest -> Value)
-> (ResponseConfirmationRequest -> Encoding)
-> ([ResponseConfirmationRequest] -> Value)
-> ([ResponseConfirmationRequest] -> Encoding)
-> ToJSON ResponseConfirmationRequest
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseConfirmationRequest -> Value
toJSON :: ResponseConfirmationRequest -> Value
$ctoEncoding :: ResponseConfirmationRequest -> Encoding
toEncoding :: ResponseConfirmationRequest -> Encoding
$ctoJSONList :: [ResponseConfirmationRequest] -> Value
toJSONList :: [ResponseConfirmationRequest] -> Value
$ctoEncodingList :: [ResponseConfirmationRequest] -> Encoding
toEncodingList :: [ResponseConfirmationRequest] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseConfirmationRequest") ResponseConfirmationRequest
type RequestConfirm :: Type
newtype RequestConfirm = MkRequestConfirm
{ RequestConfirm -> ConfirmationSecret
requestConfirmSecret :: ConfirmationSecret
}
deriving stock (RequestConfirm -> RequestConfirm -> Bool
(RequestConfirm -> RequestConfirm -> Bool)
-> (RequestConfirm -> RequestConfirm -> Bool) -> Eq RequestConfirm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestConfirm -> RequestConfirm -> Bool
== :: RequestConfirm -> RequestConfirm -> Bool
$c/= :: RequestConfirm -> RequestConfirm -> Bool
/= :: RequestConfirm -> RequestConfirm -> Bool
Eq, (forall x. RequestConfirm -> Rep RequestConfirm x)
-> (forall x. Rep RequestConfirm x -> RequestConfirm)
-> Generic RequestConfirm
forall x. Rep RequestConfirm x -> RequestConfirm
forall x. RequestConfirm -> Rep RequestConfirm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestConfirm -> Rep RequestConfirm x
from :: forall x. RequestConfirm -> Rep RequestConfirm x
$cto :: forall x. Rep RequestConfirm x -> RequestConfirm
to :: forall x. Rep RequestConfirm x -> RequestConfirm
Generic, Eq RequestConfirm
Eq RequestConfirm =>
(RequestConfirm -> RequestConfirm -> Ordering)
-> (RequestConfirm -> RequestConfirm -> Bool)
-> (RequestConfirm -> RequestConfirm -> Bool)
-> (RequestConfirm -> RequestConfirm -> Bool)
-> (RequestConfirm -> RequestConfirm -> Bool)
-> (RequestConfirm -> RequestConfirm -> RequestConfirm)
-> (RequestConfirm -> RequestConfirm -> RequestConfirm)
-> Ord RequestConfirm
RequestConfirm -> RequestConfirm -> Bool
RequestConfirm -> RequestConfirm -> Ordering
RequestConfirm -> RequestConfirm -> RequestConfirm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RequestConfirm -> RequestConfirm -> Ordering
compare :: RequestConfirm -> RequestConfirm -> Ordering
$c< :: RequestConfirm -> RequestConfirm -> Bool
< :: RequestConfirm -> RequestConfirm -> Bool
$c<= :: RequestConfirm -> RequestConfirm -> Bool
<= :: RequestConfirm -> RequestConfirm -> Bool
$c> :: RequestConfirm -> RequestConfirm -> Bool
> :: RequestConfirm -> RequestConfirm -> Bool
$c>= :: RequestConfirm -> RequestConfirm -> Bool
>= :: RequestConfirm -> RequestConfirm -> Bool
$cmax :: RequestConfirm -> RequestConfirm -> RequestConfirm
max :: RequestConfirm -> RequestConfirm -> RequestConfirm
$cmin :: RequestConfirm -> RequestConfirm -> RequestConfirm
min :: RequestConfirm -> RequestConfirm -> RequestConfirm
Ord, ReadPrec [RequestConfirm]
ReadPrec RequestConfirm
Int -> ReadS RequestConfirm
ReadS [RequestConfirm]
(Int -> ReadS RequestConfirm)
-> ReadS [RequestConfirm]
-> ReadPrec RequestConfirm
-> ReadPrec [RequestConfirm]
-> Read RequestConfirm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestConfirm
readsPrec :: Int -> ReadS RequestConfirm
$creadList :: ReadS [RequestConfirm]
readList :: ReadS [RequestConfirm]
$creadPrec :: ReadPrec RequestConfirm
readPrec :: ReadPrec RequestConfirm
$creadListPrec :: ReadPrec [RequestConfirm]
readListPrec :: ReadPrec [RequestConfirm]
Read, Int -> RequestConfirm -> ShowS
[RequestConfirm] -> ShowS
RequestConfirm -> String
(Int -> RequestConfirm -> ShowS)
-> (RequestConfirm -> String)
-> ([RequestConfirm] -> ShowS)
-> Show RequestConfirm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestConfirm -> ShowS
showsPrec :: Int -> RequestConfirm -> ShowS
$cshow :: RequestConfirm -> String
show :: RequestConfirm -> String
$cshowList :: [RequestConfirm] -> ShowS
showList :: [RequestConfirm] -> ShowS
Show)
deriving
(Value -> Parser [RequestConfirm]
Value -> Parser RequestConfirm
(Value -> Parser RequestConfirm)
-> (Value -> Parser [RequestConfirm]) -> FromJSON RequestConfirm
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestConfirm
parseJSON :: Value -> Parser RequestConfirm
$cparseJSONList :: Value -> Parser [RequestConfirm]
parseJSONList :: Value -> Parser [RequestConfirm]
A.FromJSON, [RequestConfirm] -> Value
[RequestConfirm] -> Encoding
RequestConfirm -> Value
RequestConfirm -> Encoding
(RequestConfirm -> Value)
-> (RequestConfirm -> Encoding)
-> ([RequestConfirm] -> Value)
-> ([RequestConfirm] -> Encoding)
-> ToJSON RequestConfirm
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestConfirm -> Value
toJSON :: RequestConfirm -> Value
$ctoEncoding :: RequestConfirm -> Encoding
toEncoding :: RequestConfirm -> Encoding
$ctoJSONList :: [RequestConfirm] -> Value
toJSONList :: [RequestConfirm] -> Value
$ctoEncodingList :: [RequestConfirm] -> Encoding
toEncodingList :: [RequestConfirm] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestConfirm") RequestConfirm
type ResponseConfirm :: Type
newtype ResponseConfirm = MkResponseConfirm
{ ResponseConfirm -> ()
responseConfirmUnit :: ()
}
deriving stock (ResponseConfirm -> ResponseConfirm -> Bool
(ResponseConfirm -> ResponseConfirm -> Bool)
-> (ResponseConfirm -> ResponseConfirm -> Bool)
-> Eq ResponseConfirm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseConfirm -> ResponseConfirm -> Bool
== :: ResponseConfirm -> ResponseConfirm -> Bool
$c/= :: ResponseConfirm -> ResponseConfirm -> Bool
/= :: ResponseConfirm -> ResponseConfirm -> Bool
Eq, (forall x. ResponseConfirm -> Rep ResponseConfirm x)
-> (forall x. Rep ResponseConfirm x -> ResponseConfirm)
-> Generic ResponseConfirm
forall x. Rep ResponseConfirm x -> ResponseConfirm
forall x. ResponseConfirm -> Rep ResponseConfirm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseConfirm -> Rep ResponseConfirm x
from :: forall x. ResponseConfirm -> Rep ResponseConfirm x
$cto :: forall x. Rep ResponseConfirm x -> ResponseConfirm
to :: forall x. Rep ResponseConfirm x -> ResponseConfirm
Generic, Eq ResponseConfirm
Eq ResponseConfirm =>
(ResponseConfirm -> ResponseConfirm -> Ordering)
-> (ResponseConfirm -> ResponseConfirm -> Bool)
-> (ResponseConfirm -> ResponseConfirm -> Bool)
-> (ResponseConfirm -> ResponseConfirm -> Bool)
-> (ResponseConfirm -> ResponseConfirm -> Bool)
-> (ResponseConfirm -> ResponseConfirm -> ResponseConfirm)
-> (ResponseConfirm -> ResponseConfirm -> ResponseConfirm)
-> Ord ResponseConfirm
ResponseConfirm -> ResponseConfirm -> Bool
ResponseConfirm -> ResponseConfirm -> Ordering
ResponseConfirm -> ResponseConfirm -> ResponseConfirm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseConfirm -> ResponseConfirm -> Ordering
compare :: ResponseConfirm -> ResponseConfirm -> Ordering
$c< :: ResponseConfirm -> ResponseConfirm -> Bool
< :: ResponseConfirm -> ResponseConfirm -> Bool
$c<= :: ResponseConfirm -> ResponseConfirm -> Bool
<= :: ResponseConfirm -> ResponseConfirm -> Bool
$c> :: ResponseConfirm -> ResponseConfirm -> Bool
> :: ResponseConfirm -> ResponseConfirm -> Bool
$c>= :: ResponseConfirm -> ResponseConfirm -> Bool
>= :: ResponseConfirm -> ResponseConfirm -> Bool
$cmax :: ResponseConfirm -> ResponseConfirm -> ResponseConfirm
max :: ResponseConfirm -> ResponseConfirm -> ResponseConfirm
$cmin :: ResponseConfirm -> ResponseConfirm -> ResponseConfirm
min :: ResponseConfirm -> ResponseConfirm -> ResponseConfirm
Ord, ReadPrec [ResponseConfirm]
ReadPrec ResponseConfirm
Int -> ReadS ResponseConfirm
ReadS [ResponseConfirm]
(Int -> ReadS ResponseConfirm)
-> ReadS [ResponseConfirm]
-> ReadPrec ResponseConfirm
-> ReadPrec [ResponseConfirm]
-> Read ResponseConfirm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseConfirm
readsPrec :: Int -> ReadS ResponseConfirm
$creadList :: ReadS [ResponseConfirm]
readList :: ReadS [ResponseConfirm]
$creadPrec :: ReadPrec ResponseConfirm
readPrec :: ReadPrec ResponseConfirm
$creadListPrec :: ReadPrec [ResponseConfirm]
readListPrec :: ReadPrec [ResponseConfirm]
Read, Int -> ResponseConfirm -> ShowS
[ResponseConfirm] -> ShowS
ResponseConfirm -> String
(Int -> ResponseConfirm -> ShowS)
-> (ResponseConfirm -> String)
-> ([ResponseConfirm] -> ShowS)
-> Show ResponseConfirm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseConfirm -> ShowS
showsPrec :: Int -> ResponseConfirm -> ShowS
$cshow :: ResponseConfirm -> String
show :: ResponseConfirm -> String
$cshowList :: [ResponseConfirm] -> ShowS
showList :: [ResponseConfirm] -> ShowS
Show)
deriving
(Value -> Parser [ResponseConfirm]
Value -> Parser ResponseConfirm
(Value -> Parser ResponseConfirm)
-> (Value -> Parser [ResponseConfirm]) -> FromJSON ResponseConfirm
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseConfirm
parseJSON :: Value -> Parser ResponseConfirm
$cparseJSONList :: Value -> Parser [ResponseConfirm]
parseJSONList :: Value -> Parser [ResponseConfirm]
A.FromJSON, [ResponseConfirm] -> Value
[ResponseConfirm] -> Encoding
ResponseConfirm -> Value
ResponseConfirm -> Encoding
(ResponseConfirm -> Value)
-> (ResponseConfirm -> Encoding)
-> ([ResponseConfirm] -> Value)
-> ([ResponseConfirm] -> Encoding)
-> ToJSON ResponseConfirm
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseConfirm -> Value
toJSON :: ResponseConfirm -> Value
$ctoEncoding :: ResponseConfirm -> Encoding
toEncoding :: ResponseConfirm -> Encoding
$ctoJSONList :: [ResponseConfirm] -> Value
toJSONList :: [ResponseConfirm] -> Value
$ctoEncodingList :: [ResponseConfirm] -> Encoding
toEncodingList :: [ResponseConfirm] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseConfirm") ResponseConfirm
type RequestNotifications :: Type
newtype RequestNotifications = MkRequestNotifications
{ RequestNotifications -> Maybe Bool
requestNotificationsReceiveEmailNotifications :: Maybe Bool
}
deriving stock (RequestNotifications -> RequestNotifications -> Bool
(RequestNotifications -> RequestNotifications -> Bool)
-> (RequestNotifications -> RequestNotifications -> Bool)
-> Eq RequestNotifications
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestNotifications -> RequestNotifications -> Bool
== :: RequestNotifications -> RequestNotifications -> Bool
$c/= :: RequestNotifications -> RequestNotifications -> Bool
/= :: RequestNotifications -> RequestNotifications -> Bool
Eq, (forall x. RequestNotifications -> Rep RequestNotifications x)
-> (forall x. Rep RequestNotifications x -> RequestNotifications)
-> Generic RequestNotifications
forall x. Rep RequestNotifications x -> RequestNotifications
forall x. RequestNotifications -> Rep RequestNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestNotifications -> Rep RequestNotifications x
from :: forall x. RequestNotifications -> Rep RequestNotifications x
$cto :: forall x. Rep RequestNotifications x -> RequestNotifications
to :: forall x. Rep RequestNotifications x -> RequestNotifications
Generic, Eq RequestNotifications
Eq RequestNotifications =>
(RequestNotifications -> RequestNotifications -> Ordering)
-> (RequestNotifications -> RequestNotifications -> Bool)
-> (RequestNotifications -> RequestNotifications -> Bool)
-> (RequestNotifications -> RequestNotifications -> Bool)
-> (RequestNotifications -> RequestNotifications -> Bool)
-> (RequestNotifications
-> RequestNotifications -> RequestNotifications)
-> (RequestNotifications
-> RequestNotifications -> RequestNotifications)
-> Ord RequestNotifications
RequestNotifications -> RequestNotifications -> Bool
RequestNotifications -> RequestNotifications -> Ordering
RequestNotifications
-> RequestNotifications -> RequestNotifications
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RequestNotifications -> RequestNotifications -> Ordering
compare :: RequestNotifications -> RequestNotifications -> Ordering
$c< :: RequestNotifications -> RequestNotifications -> Bool
< :: RequestNotifications -> RequestNotifications -> Bool
$c<= :: RequestNotifications -> RequestNotifications -> Bool
<= :: RequestNotifications -> RequestNotifications -> Bool
$c> :: RequestNotifications -> RequestNotifications -> Bool
> :: RequestNotifications -> RequestNotifications -> Bool
$c>= :: RequestNotifications -> RequestNotifications -> Bool
>= :: RequestNotifications -> RequestNotifications -> Bool
$cmax :: RequestNotifications
-> RequestNotifications -> RequestNotifications
max :: RequestNotifications
-> RequestNotifications -> RequestNotifications
$cmin :: RequestNotifications
-> RequestNotifications -> RequestNotifications
min :: RequestNotifications
-> RequestNotifications -> RequestNotifications
Ord, ReadPrec [RequestNotifications]
ReadPrec RequestNotifications
Int -> ReadS RequestNotifications
ReadS [RequestNotifications]
(Int -> ReadS RequestNotifications)
-> ReadS [RequestNotifications]
-> ReadPrec RequestNotifications
-> ReadPrec [RequestNotifications]
-> Read RequestNotifications
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestNotifications
readsPrec :: Int -> ReadS RequestNotifications
$creadList :: ReadS [RequestNotifications]
readList :: ReadS [RequestNotifications]
$creadPrec :: ReadPrec RequestNotifications
readPrec :: ReadPrec RequestNotifications
$creadListPrec :: ReadPrec [RequestNotifications]
readListPrec :: ReadPrec [RequestNotifications]
Read, Int -> RequestNotifications -> ShowS
[RequestNotifications] -> ShowS
RequestNotifications -> String
(Int -> RequestNotifications -> ShowS)
-> (RequestNotifications -> String)
-> ([RequestNotifications] -> ShowS)
-> Show RequestNotifications
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestNotifications -> ShowS
showsPrec :: Int -> RequestNotifications -> ShowS
$cshow :: RequestNotifications -> String
show :: RequestNotifications -> String
$cshowList :: [RequestNotifications] -> ShowS
showList :: [RequestNotifications] -> ShowS
Show)
deriving
(Value -> Parser [RequestNotifications]
Value -> Parser RequestNotifications
(Value -> Parser RequestNotifications)
-> (Value -> Parser [RequestNotifications])
-> FromJSON RequestNotifications
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestNotifications
parseJSON :: Value -> Parser RequestNotifications
$cparseJSONList :: Value -> Parser [RequestNotifications]
parseJSONList :: Value -> Parser [RequestNotifications]
A.FromJSON, [RequestNotifications] -> Value
[RequestNotifications] -> Encoding
RequestNotifications -> Value
RequestNotifications -> Encoding
(RequestNotifications -> Value)
-> (RequestNotifications -> Encoding)
-> ([RequestNotifications] -> Value)
-> ([RequestNotifications] -> Encoding)
-> ToJSON RequestNotifications
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestNotifications -> Value
toJSON :: RequestNotifications -> Value
$ctoEncoding :: RequestNotifications -> Encoding
toEncoding :: RequestNotifications -> Encoding
$ctoJSONList :: [RequestNotifications] -> Value
toJSONList :: [RequestNotifications] -> Value
$ctoEncodingList :: [RequestNotifications] -> Encoding
toEncodingList :: [RequestNotifications] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestNotifications") RequestNotifications
type ResponseNotifications :: Type
newtype ResponseNotifications = MkResponseNotifications
{ ResponseNotifications -> Bool
responseNotificationsReceiveEmailNotifications :: Bool
}
deriving stock (ResponseNotifications -> ResponseNotifications -> Bool
(ResponseNotifications -> ResponseNotifications -> Bool)
-> (ResponseNotifications -> ResponseNotifications -> Bool)
-> Eq ResponseNotifications
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseNotifications -> ResponseNotifications -> Bool
== :: ResponseNotifications -> ResponseNotifications -> Bool
$c/= :: ResponseNotifications -> ResponseNotifications -> Bool
/= :: ResponseNotifications -> ResponseNotifications -> Bool
Eq, (forall x. ResponseNotifications -> Rep ResponseNotifications x)
-> (forall x. Rep ResponseNotifications x -> ResponseNotifications)
-> Generic ResponseNotifications
forall x. Rep ResponseNotifications x -> ResponseNotifications
forall x. ResponseNotifications -> Rep ResponseNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseNotifications -> Rep ResponseNotifications x
from :: forall x. ResponseNotifications -> Rep ResponseNotifications x
$cto :: forall x. Rep ResponseNotifications x -> ResponseNotifications
to :: forall x. Rep ResponseNotifications x -> ResponseNotifications
Generic, Eq ResponseNotifications
Eq ResponseNotifications =>
(ResponseNotifications -> ResponseNotifications -> Ordering)
-> (ResponseNotifications -> ResponseNotifications -> Bool)
-> (ResponseNotifications -> ResponseNotifications -> Bool)
-> (ResponseNotifications -> ResponseNotifications -> Bool)
-> (ResponseNotifications -> ResponseNotifications -> Bool)
-> (ResponseNotifications
-> ResponseNotifications -> ResponseNotifications)
-> (ResponseNotifications
-> ResponseNotifications -> ResponseNotifications)
-> Ord ResponseNotifications
ResponseNotifications -> ResponseNotifications -> Bool
ResponseNotifications -> ResponseNotifications -> Ordering
ResponseNotifications
-> ResponseNotifications -> ResponseNotifications
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseNotifications -> ResponseNotifications -> Ordering
compare :: ResponseNotifications -> ResponseNotifications -> Ordering
$c< :: ResponseNotifications -> ResponseNotifications -> Bool
< :: ResponseNotifications -> ResponseNotifications -> Bool
$c<= :: ResponseNotifications -> ResponseNotifications -> Bool
<= :: ResponseNotifications -> ResponseNotifications -> Bool
$c> :: ResponseNotifications -> ResponseNotifications -> Bool
> :: ResponseNotifications -> ResponseNotifications -> Bool
$c>= :: ResponseNotifications -> ResponseNotifications -> Bool
>= :: ResponseNotifications -> ResponseNotifications -> Bool
$cmax :: ResponseNotifications
-> ResponseNotifications -> ResponseNotifications
max :: ResponseNotifications
-> ResponseNotifications -> ResponseNotifications
$cmin :: ResponseNotifications
-> ResponseNotifications -> ResponseNotifications
min :: ResponseNotifications
-> ResponseNotifications -> ResponseNotifications
Ord, ReadPrec [ResponseNotifications]
ReadPrec ResponseNotifications
Int -> ReadS ResponseNotifications
ReadS [ResponseNotifications]
(Int -> ReadS ResponseNotifications)
-> ReadS [ResponseNotifications]
-> ReadPrec ResponseNotifications
-> ReadPrec [ResponseNotifications]
-> Read ResponseNotifications
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseNotifications
readsPrec :: Int -> ReadS ResponseNotifications
$creadList :: ReadS [ResponseNotifications]
readList :: ReadS [ResponseNotifications]
$creadPrec :: ReadPrec ResponseNotifications
readPrec :: ReadPrec ResponseNotifications
$creadListPrec :: ReadPrec [ResponseNotifications]
readListPrec :: ReadPrec [ResponseNotifications]
Read, Int -> ResponseNotifications -> ShowS
[ResponseNotifications] -> ShowS
ResponseNotifications -> String
(Int -> ResponseNotifications -> ShowS)
-> (ResponseNotifications -> String)
-> ([ResponseNotifications] -> ShowS)
-> Show ResponseNotifications
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseNotifications -> ShowS
showsPrec :: Int -> ResponseNotifications -> ShowS
$cshow :: ResponseNotifications -> String
show :: ResponseNotifications -> String
$cshowList :: [ResponseNotifications] -> ShowS
showList :: [ResponseNotifications] -> ShowS
Show)
deriving
(Value -> Parser [ResponseNotifications]
Value -> Parser ResponseNotifications
(Value -> Parser ResponseNotifications)
-> (Value -> Parser [ResponseNotifications])
-> FromJSON ResponseNotifications
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseNotifications
parseJSON :: Value -> Parser ResponseNotifications
$cparseJSONList :: Value -> Parser [ResponseNotifications]
parseJSONList :: Value -> Parser [ResponseNotifications]
A.FromJSON, [ResponseNotifications] -> Value
[ResponseNotifications] -> Encoding
ResponseNotifications -> Value
ResponseNotifications -> Encoding
(ResponseNotifications -> Value)
-> (ResponseNotifications -> Encoding)
-> ([ResponseNotifications] -> Value)
-> ([ResponseNotifications] -> Encoding)
-> ToJSON ResponseNotifications
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseNotifications -> Value
toJSON :: ResponseNotifications -> Value
$ctoEncoding :: ResponseNotifications -> Encoding
toEncoding :: ResponseNotifications -> Encoding
$ctoJSONList :: [ResponseNotifications] -> Value
toJSONList :: [ResponseNotifications] -> Value
$ctoEncodingList :: [ResponseNotifications] -> Encoding
toEncodingList :: [ResponseNotifications] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseNotifications") ResponseNotifications
type RequestProfile :: Type
newtype RequestProfile = MkRequestProfile
{ RequestProfile -> NameOrIdentifier Username IdentifierUser
requestProfileUser :: NameOrIdentifier Username IdentifierUser
}
deriving stock (RequestProfile -> RequestProfile -> Bool
(RequestProfile -> RequestProfile -> Bool)
-> (RequestProfile -> RequestProfile -> Bool) -> Eq RequestProfile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestProfile -> RequestProfile -> Bool
== :: RequestProfile -> RequestProfile -> Bool
$c/= :: RequestProfile -> RequestProfile -> Bool
/= :: RequestProfile -> RequestProfile -> Bool
Eq, (forall x. RequestProfile -> Rep RequestProfile x)
-> (forall x. Rep RequestProfile x -> RequestProfile)
-> Generic RequestProfile
forall x. Rep RequestProfile x -> RequestProfile
forall x. RequestProfile -> Rep RequestProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestProfile -> Rep RequestProfile x
from :: forall x. RequestProfile -> Rep RequestProfile x
$cto :: forall x. Rep RequestProfile x -> RequestProfile
to :: forall x. Rep RequestProfile x -> RequestProfile
Generic, Eq RequestProfile
Eq RequestProfile =>
(RequestProfile -> RequestProfile -> Ordering)
-> (RequestProfile -> RequestProfile -> Bool)
-> (RequestProfile -> RequestProfile -> Bool)
-> (RequestProfile -> RequestProfile -> Bool)
-> (RequestProfile -> RequestProfile -> Bool)
-> (RequestProfile -> RequestProfile -> RequestProfile)
-> (RequestProfile -> RequestProfile -> RequestProfile)
-> Ord RequestProfile
RequestProfile -> RequestProfile -> Bool
RequestProfile -> RequestProfile -> Ordering
RequestProfile -> RequestProfile -> RequestProfile
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RequestProfile -> RequestProfile -> Ordering
compare :: RequestProfile -> RequestProfile -> Ordering
$c< :: RequestProfile -> RequestProfile -> Bool
< :: RequestProfile -> RequestProfile -> Bool
$c<= :: RequestProfile -> RequestProfile -> Bool
<= :: RequestProfile -> RequestProfile -> Bool
$c> :: RequestProfile -> RequestProfile -> Bool
> :: RequestProfile -> RequestProfile -> Bool
$c>= :: RequestProfile -> RequestProfile -> Bool
>= :: RequestProfile -> RequestProfile -> Bool
$cmax :: RequestProfile -> RequestProfile -> RequestProfile
max :: RequestProfile -> RequestProfile -> RequestProfile
$cmin :: RequestProfile -> RequestProfile -> RequestProfile
min :: RequestProfile -> RequestProfile -> RequestProfile
Ord, ReadPrec [RequestProfile]
ReadPrec RequestProfile
Int -> ReadS RequestProfile
ReadS [RequestProfile]
(Int -> ReadS RequestProfile)
-> ReadS [RequestProfile]
-> ReadPrec RequestProfile
-> ReadPrec [RequestProfile]
-> Read RequestProfile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestProfile
readsPrec :: Int -> ReadS RequestProfile
$creadList :: ReadS [RequestProfile]
readList :: ReadS [RequestProfile]
$creadPrec :: ReadPrec RequestProfile
readPrec :: ReadPrec RequestProfile
$creadListPrec :: ReadPrec [RequestProfile]
readListPrec :: ReadPrec [RequestProfile]
Read, Int -> RequestProfile -> ShowS
[RequestProfile] -> ShowS
RequestProfile -> String
(Int -> RequestProfile -> ShowS)
-> (RequestProfile -> String)
-> ([RequestProfile] -> ShowS)
-> Show RequestProfile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestProfile -> ShowS
showsPrec :: Int -> RequestProfile -> ShowS
$cshow :: RequestProfile -> String
show :: RequestProfile -> String
$cshowList :: [RequestProfile] -> ShowS
showList :: [RequestProfile] -> ShowS
Show)
deriving
(Value -> Parser [RequestProfile]
Value -> Parser RequestProfile
(Value -> Parser RequestProfile)
-> (Value -> Parser [RequestProfile]) -> FromJSON RequestProfile
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestProfile
parseJSON :: Value -> Parser RequestProfile
$cparseJSONList :: Value -> Parser [RequestProfile]
parseJSONList :: Value -> Parser [RequestProfile]
A.FromJSON, [RequestProfile] -> Value
[RequestProfile] -> Encoding
RequestProfile -> Value
RequestProfile -> Encoding
(RequestProfile -> Value)
-> (RequestProfile -> Encoding)
-> ([RequestProfile] -> Value)
-> ([RequestProfile] -> Encoding)
-> ToJSON RequestProfile
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestProfile -> Value
toJSON :: RequestProfile -> Value
$ctoEncoding :: RequestProfile -> Encoding
toEncoding :: RequestProfile -> Encoding
$ctoJSONList :: [RequestProfile] -> Value
toJSONList :: [RequestProfile] -> Value
$ctoEncodingList :: [RequestProfile] -> Encoding
toEncodingList :: [RequestProfile] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestProfile") RequestProfile
type ResponseProfile :: Type
data ResponseProfile = MkResponseProfile
{ ResponseProfile -> IdentifierUser
responseProfileId :: IdentifierUser
, ResponseProfile -> Username
responseProfileName :: Username
, ResponseProfile -> Maybe EmailAddress
responseProfileEmail :: Maybe EmailAddress
, ResponseProfile -> Bool
responseProfileEmailVerified :: Bool
}
deriving stock (ResponseProfile -> ResponseProfile -> Bool
(ResponseProfile -> ResponseProfile -> Bool)
-> (ResponseProfile -> ResponseProfile -> Bool)
-> Eq ResponseProfile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseProfile -> ResponseProfile -> Bool
== :: ResponseProfile -> ResponseProfile -> Bool
$c/= :: ResponseProfile -> ResponseProfile -> Bool
/= :: ResponseProfile -> ResponseProfile -> Bool
Eq, (forall x. ResponseProfile -> Rep ResponseProfile x)
-> (forall x. Rep ResponseProfile x -> ResponseProfile)
-> Generic ResponseProfile
forall x. Rep ResponseProfile x -> ResponseProfile
forall x. ResponseProfile -> Rep ResponseProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseProfile -> Rep ResponseProfile x
from :: forall x. ResponseProfile -> Rep ResponseProfile x
$cto :: forall x. Rep ResponseProfile x -> ResponseProfile
to :: forall x. Rep ResponseProfile x -> ResponseProfile
Generic, Eq ResponseProfile
Eq ResponseProfile =>
(ResponseProfile -> ResponseProfile -> Ordering)
-> (ResponseProfile -> ResponseProfile -> Bool)
-> (ResponseProfile -> ResponseProfile -> Bool)
-> (ResponseProfile -> ResponseProfile -> Bool)
-> (ResponseProfile -> ResponseProfile -> Bool)
-> (ResponseProfile -> ResponseProfile -> ResponseProfile)
-> (ResponseProfile -> ResponseProfile -> ResponseProfile)
-> Ord ResponseProfile
ResponseProfile -> ResponseProfile -> Bool
ResponseProfile -> ResponseProfile -> Ordering
ResponseProfile -> ResponseProfile -> ResponseProfile
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ResponseProfile -> ResponseProfile -> Ordering
compare :: ResponseProfile -> ResponseProfile -> Ordering
$c< :: ResponseProfile -> ResponseProfile -> Bool
< :: ResponseProfile -> ResponseProfile -> Bool
$c<= :: ResponseProfile -> ResponseProfile -> Bool
<= :: ResponseProfile -> ResponseProfile -> Bool
$c> :: ResponseProfile -> ResponseProfile -> Bool
> :: ResponseProfile -> ResponseProfile -> Bool
$c>= :: ResponseProfile -> ResponseProfile -> Bool
>= :: ResponseProfile -> ResponseProfile -> Bool
$cmax :: ResponseProfile -> ResponseProfile -> ResponseProfile
max :: ResponseProfile -> ResponseProfile -> ResponseProfile
$cmin :: ResponseProfile -> ResponseProfile -> ResponseProfile
min :: ResponseProfile -> ResponseProfile -> ResponseProfile
Ord, ReadPrec [ResponseProfile]
ReadPrec ResponseProfile
Int -> ReadS ResponseProfile
ReadS [ResponseProfile]
(Int -> ReadS ResponseProfile)
-> ReadS [ResponseProfile]
-> ReadPrec ResponseProfile
-> ReadPrec [ResponseProfile]
-> Read ResponseProfile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseProfile
readsPrec :: Int -> ReadS ResponseProfile
$creadList :: ReadS [ResponseProfile]
readList :: ReadS [ResponseProfile]
$creadPrec :: ReadPrec ResponseProfile
readPrec :: ReadPrec ResponseProfile
$creadListPrec :: ReadPrec [ResponseProfile]
readListPrec :: ReadPrec [ResponseProfile]
Read, Int -> ResponseProfile -> ShowS
[ResponseProfile] -> ShowS
ResponseProfile -> String
(Int -> ResponseProfile -> ShowS)
-> (ResponseProfile -> String)
-> ([ResponseProfile] -> ShowS)
-> Show ResponseProfile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseProfile -> ShowS
showsPrec :: Int -> ResponseProfile -> ShowS
$cshow :: ResponseProfile -> String
show :: ResponseProfile -> String
$cshowList :: [ResponseProfile] -> ShowS
showList :: [ResponseProfile] -> ShowS
Show)
deriving
(Value -> Parser [ResponseProfile]
Value -> Parser ResponseProfile
(Value -> Parser ResponseProfile)
-> (Value -> Parser [ResponseProfile]) -> FromJSON ResponseProfile
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseProfile
parseJSON :: Value -> Parser ResponseProfile
$cparseJSONList :: Value -> Parser [ResponseProfile]
parseJSONList :: Value -> Parser [ResponseProfile]
A.FromJSON, [ResponseProfile] -> Value
[ResponseProfile] -> Encoding
ResponseProfile -> Value
ResponseProfile -> Encoding
(ResponseProfile -> Value)
-> (ResponseProfile -> Encoding)
-> ([ResponseProfile] -> Value)
-> ([ResponseProfile] -> Encoding)
-> ToJSON ResponseProfile
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseProfile -> Value
toJSON :: ResponseProfile -> Value
$ctoEncoding :: ResponseProfile -> Encoding
toEncoding :: ResponseProfile -> Encoding
$ctoJSONList :: [ResponseProfile] -> Value
toJSONList :: [ResponseProfile] -> Value
$ctoEncodingList :: [ResponseProfile] -> Encoding
toEncodingList :: [ResponseProfile] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseProfile") ResponseProfile