module Mensam.API.Route.Api.Space where
import Mensam.API.Aeson
import Mensam.API.Aeson.StaticText
import Mensam.API.Data.Desk
import Mensam.API.Data.Reservation
import Mensam.API.Data.Space
import Mensam.API.Data.Space.Permission
import Mensam.API.Data.User
import Mensam.API.Order
import Mensam.API.Update
import Data.Aeson qualified as A
import Data.Kind
import Data.Set qualified as S
import Data.Text qualified as T
import Data.Time qualified as T
import Data.Time.Zones.All qualified as T
import Deriving.Aeson qualified as A
import GHC.Generics
import Numeric.Natural
import Servant.API hiding (BasicAuth)
import Servant.API.ImageJpeg
import Servant.Auth
import Servant.Auth.JWT.WithSession
type Routes :: Type -> Type
data Routes route = Routes
{ forall route.
Routes route
-> route
:- (Summary "Create Space"
:> (Description
"Create a new space.\nYou will be an administrator of this newly created space.\n"
:> ("space"
:> ("create"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceCreate
:> UVerb
'PUT
'[JSON]
'[WithStatus 201 ResponseSpaceCreate,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 500 ()]))))))
routeSpaceCreate ::
route
:- Summary "Create Space"
:> Description
"Create a new space.\n\
\You will be an administrator of this newly created space.\n"
:> "space"
:> "create"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceCreate
:> UVerb
PUT
'[JSON]
[ WithStatus 201 ResponseSpaceCreate
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Delete Space"
:> (Description
"Delete a space irreversibly.\nThis also purges data associated with this space including reservations, desks and member roles.\n"
:> ("space"
:> ("delete"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceDelete
:> UVerb
'DELETE
'[JSON]
'[WithStatus 200 ResponseSpaceDelete,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditSpace),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceDelete ::
route
:- Summary "Delete Space"
:> Description
"Delete a space irreversibly.\n\
\This also purges data associated with this space including reservations, desks and member roles.\n"
:> "space"
:> "delete"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceDelete
:> UVerb
DELETE
'[JSON]
[ WithStatus 200 ResponseSpaceDelete
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditSpace)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Edit Space"
:> (Description "Update the configuration of a space.\n"
:> ("space"
:> ("edit"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceEdit
:> UVerb
'PATCH
'[JSON]
'[WithStatus 200 ResponseSpaceEdit,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditSpace),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceEdit ::
route
:- Summary "Edit Space"
:> Description
"Update the configuration of a space.\n"
:> "space"
:> "edit"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceEdit
:> UVerb
PATCH
'[JSON]
[ WithStatus 200 ResponseSpaceEdit
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditSpace)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Change Space Picture"
:> (Description
"Upload a new space logo.\nThis overwrites any old space logo.\n"
:> ("space"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> (ReqBody' '[Lenient, Required] '[ImageJpeg] ImageJpegBytes
:> UVerb
'PUT
'[JSON]
'[WithStatus 200 (StaticText "Uploaded space picture."),
WithStatus 400 ErrorParseBodyJpeg,
WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditSpace),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()])))))))
routePictureUpload ::
route
:- Summary "Change Space Picture"
:> Description
"Upload a new space logo.\n\
\This overwrites any old space logo.\n"
:> "space"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> ReqBody' '[Lenient, Required] '[ImageJpeg] ImageJpegBytes
:> UVerb
PUT
'[JSON]
[ WithStatus 200 (StaticText "Uploaded space picture.")
, WithStatus 400 ErrorParseBodyJpeg
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditSpace)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Delete Space Picture"
:> (Description "Delete the current space logo.\n"
:> ("space"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> UVerb
'DELETE
'[JSON]
'[WithStatus 200 (StaticText "Deleted space picture."),
WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditSpace),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routePictureDelete ::
route
:- Summary "Delete Space Picture"
:> Description
"Delete the current space logo.\n"
:> "space"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> UVerb
DELETE
'[JSON]
[ WithStatus 200 (StaticText "Deleted space picture.")
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditSpace)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "View Space Picture"
:> (Description "View a space logo.\n"
:> ("space"
:> ("picture"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> Get '[ImageJpeg] ImageJpegBytes))))))
routePictureDownload ::
route
:- Summary "View Space Picture"
:> Description
"View a space logo.\n"
:> "space"
:> "picture"
:> Auth '[JWTWithSession] UserAuthenticated
:> QueryParam' '[Lenient, Required] "space" IdentifierSpace
:> Get '[ImageJpeg] ImageJpegBytes
, forall route.
Routes route
-> route
:- (Summary "Join Space"
:> (Description "Become a member of a space.\n"
:> ("space"
:> ("join"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceJoin
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceJoin,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403
(StaticTexts
'["Role is inaccessible.", "Wrong role password."]),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceJoin ::
route
:- Summary "Join Space"
:> Description
"Become a member of a space.\n"
:> "space"
:> "join"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceJoin
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceJoin
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (StaticTexts ["Role is inaccessible.", "Wrong role password."])
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Leave Space"
:> (Description "Abandon membership of a space.\n"
:> ("space"
:> ("leave"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceLeave
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceLeave,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 403 (StaticText "Owner cannot leave space."),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceLeave ::
route
:- Summary "Leave Space"
:> Description
"Abandon membership of a space.\n"
:> "space"
:> "leave"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceLeave
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceLeave
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (StaticText "Owner cannot leave space.")
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Kick User from Space"
:> (Description
"Kick a user out of a space.\nYou need the `edit-user` permission for that space to remove users.\n"
:> ("space"
:> ("kick"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceKick
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceKick,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditUser),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceKick ::
route
:- Summary "Kick User from Space"
:> Description
"Kick a user out of a space.\n\
\You need the `edit-user` permission for that space to remove users.\n"
:> "space"
:> "kick"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceKick
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceKick
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditUser)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Set User Role for Space"
:> (Description
"Give a new role to a user of a space.\nYou need the `edit-user` permission for that space to redefine user roles.\n"
:> ("space"
:> ("user"
:> ("role"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceUserRole
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceUserRole,
WithStatus 400 ErrorParseBodyJson,
WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditUser),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()])))))))
routeSpaceUserRole ::
route
:- Summary "Set User Role for Space"
:> Description
"Give a new role to a user of a space.\n\
\You need the `edit-user` permission for that space to redefine user roles.\n"
:> "space"
:> "user"
:> "role"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceUserRole
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceUserRole
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditUser)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "View Space"
:> (Description "View a single space in detail.\n"
:> ("space"
:> ("view"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceView
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceView,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 403 ResponseSpaceView403,
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeSpaceView ::
route
:- Summary "View Space"
:> Description
"View a single space in detail.\n"
:> "space"
:> "view"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceView
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceView
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 ResponseSpaceView403
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "List Spaces"
:> (Description "List visible spaces.\n"
:> ("space"
:> ("list"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestSpaceList
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseSpaceList,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus 500 ()]))))))
routeSpaceList ::
route
:- Summary "List Spaces"
:> Description
"List visible spaces.\n"
:> "space"
:> "list"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestSpaceList
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseSpaceList
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Create Role"
:> (Description
"Create a new role.\nThis role will be a way to access the given space.\nYou need the `edit-role` permission for that space to create roles.\n"
:> ("role"
:> ("create"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestRoleCreate
:> UVerb
'PUT
'[JSON]
'[WithStatus 201 ResponseRoleCreate,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditRole),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeRoleCreate ::
route
:- Summary "Create Role"
:> Description
"Create a new role.\n\
\This role will be a way to access the given space.\n\
\You need the `edit-role` permission for that space to create roles.\n"
:> "role"
:> "create"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestRoleCreate
:> UVerb
PUT
'[JSON]
[ WithStatus 201 ResponseRoleCreate
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditRole)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Edit Role"
:> (Description
"Update settings of a role.\nYou need the `edit-role` permission for the space to edit roles.\n"
:> ("role"
:> ("edit"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestRoleEdit
:> UVerb
'PATCH
'[JSON]
'[WithStatus 200 ResponseRoleEdit,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditRole),
WithStatus 500 ()]))))))
routeRoleEdit ::
route
:- Summary "Edit Role"
:> Description
"Update settings of a role.\n\
\You need the `edit-role` permission for the space to edit roles.\n"
:> "role"
:> "edit"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestRoleEdit
:> UVerb
PATCH
'[JSON]
[ WithStatus 200 ResponseRoleEdit
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditRole)
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Delete Role"
:> (Description
"Delete a role.\nYou have to provide a fallback role to reassign members to that fallback role.\nYou need the `edit-role` permission for the space to delete roles.\n"
:> ("role"
:> ("delete"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestRoleDelete
:> UVerb
'DELETE
'[JSON]
'[WithStatus 200 ResponseRoleDelete,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditRole),
WithStatus 500 ()]))))))
routeRoleDelete ::
route
:- Summary "Delete Role"
:> Description
"Delete a role.\n\
\You have to provide a fallback role to reassign members to that fallback role.\n\
\You need the `edit-role` permission for the space to delete roles.\n"
:> "role"
:> "delete"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestRoleDelete
:> UVerb
DELETE
'[JSON]
[ WithStatus 200 ResponseRoleDelete
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditRole)
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Create Desk"
:> (Description
"Create a new desk.\nThis desk will belong to the given space.\nYou need the `edit-desk` permission for that space to create desks.\n"
:> ("desk"
:> ("create"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestDeskCreate
:> UVerb
'PUT
'[JSON]
'[WithStatus 201 ResponseDeskCreate,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditDesk),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeDeskCreate ::
route
:- Summary "Create Desk"
:> Description
"Create a new desk.\n\
\This desk will belong to the given space.\n\
\You need the `edit-desk` permission for that space to create desks.\n"
:> "desk"
:> "create"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestDeskCreate
:> UVerb
PUT
'[JSON]
[ WithStatus 201 ResponseDeskCreate
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditDesk)
, WithStatus 404 (StaticText "Space not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Delete Desk"
:> (Description
"Delete a desk.\nYou need the `edit-desk` permission for that space to delete desks.\n"
:> ("desk"
:> ("delete"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestDeskDelete
:> UVerb
'DELETE
'[JSON]
'[WithStatus 200 ResponseDeskDelete,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditDesk),
WithStatus 404 (StaticText "Desk not found."),
WithStatus 500 ()]))))))
routeDeskDelete ::
route
:- Summary "Delete Desk"
:> Description
"Delete a desk.\n\
\You need the `edit-desk` permission for that space to delete desks.\n"
:> "desk"
:> "delete"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestDeskDelete
:> UVerb
DELETE
'[JSON]
[ WithStatus 200 ResponseDeskDelete
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditDesk)
, WithStatus 404 (StaticText "Desk not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "Edit Desk"
:> (Description
"Update a desk.\nYou need the `edit-desk` permission for that space to edit desks.\n"
:> ("desk"
:> ("edit"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestDeskEdit
:> UVerb
'PATCH
'[JSON]
'[WithStatus 200 ResponseDeskEdit,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionEditDesk),
WithStatus 404 (StaticText "Desk not found."),
WithStatus 500 ()]))))))
routeDeskEdit ::
route
:- Summary "Edit Desk"
:> Description
"Update a desk.\n\
\You need the `edit-desk` permission for that space to edit desks.\n"
:> "desk"
:> "edit"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestDeskEdit
:> UVerb
PATCH
'[JSON]
[ WithStatus 200 ResponseDeskEdit
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionEditDesk)
, WithStatus 404 (StaticText "Desk not found.")
, WithStatus 500 ()
]
, forall route.
Routes route
-> route
:- (Summary "List Desks"
:> (Description
"List desks.\nUse the time-window to restrict the reservations in the result to overlapping time frames.\n"
:> ("desk"
:> ("list"
:> (Auth '[JWTWithSession] UserAuthenticated
:> (ReqBody' '[Lenient, Required] '[JSON] RequestDeskList
:> UVerb
'POST
'[JSON]
'[WithStatus 200 ResponseDeskList,
WithStatus 400 ErrorParseBodyJson, WithStatus 401 ErrorBearerAuth,
WithStatus
403 (ErrorInsufficientPermission 'MkPermissionViewSpace),
WithStatus 404 (StaticText "Space not found."),
WithStatus 500 ()]))))))
routeDeskList ::
route
:- Summary "List Desks"
:> Description
"List desks.\n\
\Use the time-window to restrict the reservations in the result to overlapping time frames.\n"
:> "desk"
:> "list"
:> Auth '[JWTWithSession] UserAuthenticated
:> ReqBody' '[Lenient, Required] '[JSON] RequestDeskList
:> UVerb
POST
'[JSON]
[ WithStatus 200 ResponseDeskList
, WithStatus 400 ErrorParseBodyJson
, WithStatus 401 ErrorBearerAuth
, WithStatus 403 (ErrorInsufficientPermission MkPermissionViewSpace)
, WithStatus 404 (StaticText "Space not found.")
, 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 RequestSpaceCreate :: Type
data RequestSpaceCreate = MkRequestSpaceCreate
{ RequestSpaceCreate -> NameSpace
requestSpaceCreateName :: NameSpace
, RequestSpaceCreate -> TZLabel
requestSpaceCreateTimezone :: T.TZLabel
, RequestSpaceCreate -> VisibilitySpace
requestSpaceCreateVisibility :: VisibilitySpace
}
deriving stock (RequestSpaceCreate -> RequestSpaceCreate -> Bool
(RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> (RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> Eq RequestSpaceCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
== :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
$c/= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
/= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
Eq, (forall x. RequestSpaceCreate -> Rep RequestSpaceCreate x)
-> (forall x. Rep RequestSpaceCreate x -> RequestSpaceCreate)
-> Generic RequestSpaceCreate
forall x. Rep RequestSpaceCreate x -> RequestSpaceCreate
forall x. RequestSpaceCreate -> Rep RequestSpaceCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceCreate -> Rep RequestSpaceCreate x
from :: forall x. RequestSpaceCreate -> Rep RequestSpaceCreate x
$cto :: forall x. Rep RequestSpaceCreate x -> RequestSpaceCreate
to :: forall x. Rep RequestSpaceCreate x -> RequestSpaceCreate
Generic, Eq RequestSpaceCreate
Eq RequestSpaceCreate =>
(RequestSpaceCreate -> RequestSpaceCreate -> Ordering)
-> (RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> (RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> (RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> (RequestSpaceCreate -> RequestSpaceCreate -> Bool)
-> (RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate)
-> (RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate)
-> Ord RequestSpaceCreate
RequestSpaceCreate -> RequestSpaceCreate -> Bool
RequestSpaceCreate -> RequestSpaceCreate -> Ordering
RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate
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 :: RequestSpaceCreate -> RequestSpaceCreate -> Ordering
compare :: RequestSpaceCreate -> RequestSpaceCreate -> Ordering
$c< :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
< :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
$c<= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
<= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
$c> :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
> :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
$c>= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
>= :: RequestSpaceCreate -> RequestSpaceCreate -> Bool
$cmax :: RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate
max :: RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate
$cmin :: RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate
min :: RequestSpaceCreate -> RequestSpaceCreate -> RequestSpaceCreate
Ord, ReadPrec [RequestSpaceCreate]
ReadPrec RequestSpaceCreate
Int -> ReadS RequestSpaceCreate
ReadS [RequestSpaceCreate]
(Int -> ReadS RequestSpaceCreate)
-> ReadS [RequestSpaceCreate]
-> ReadPrec RequestSpaceCreate
-> ReadPrec [RequestSpaceCreate]
-> Read RequestSpaceCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceCreate
readsPrec :: Int -> ReadS RequestSpaceCreate
$creadList :: ReadS [RequestSpaceCreate]
readList :: ReadS [RequestSpaceCreate]
$creadPrec :: ReadPrec RequestSpaceCreate
readPrec :: ReadPrec RequestSpaceCreate
$creadListPrec :: ReadPrec [RequestSpaceCreate]
readListPrec :: ReadPrec [RequestSpaceCreate]
Read, Int -> RequestSpaceCreate -> ShowS
[RequestSpaceCreate] -> ShowS
RequestSpaceCreate -> String
(Int -> RequestSpaceCreate -> ShowS)
-> (RequestSpaceCreate -> String)
-> ([RequestSpaceCreate] -> ShowS)
-> Show RequestSpaceCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceCreate -> ShowS
showsPrec :: Int -> RequestSpaceCreate -> ShowS
$cshow :: RequestSpaceCreate -> String
show :: RequestSpaceCreate -> String
$cshowList :: [RequestSpaceCreate] -> ShowS
showList :: [RequestSpaceCreate] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceCreate]
Value -> Parser RequestSpaceCreate
(Value -> Parser RequestSpaceCreate)
-> (Value -> Parser [RequestSpaceCreate])
-> FromJSON RequestSpaceCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceCreate
parseJSON :: Value -> Parser RequestSpaceCreate
$cparseJSONList :: Value -> Parser [RequestSpaceCreate]
parseJSONList :: Value -> Parser [RequestSpaceCreate]
A.FromJSON, [RequestSpaceCreate] -> Value
[RequestSpaceCreate] -> Encoding
RequestSpaceCreate -> Value
RequestSpaceCreate -> Encoding
(RequestSpaceCreate -> Value)
-> (RequestSpaceCreate -> Encoding)
-> ([RequestSpaceCreate] -> Value)
-> ([RequestSpaceCreate] -> Encoding)
-> ToJSON RequestSpaceCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceCreate -> Value
toJSON :: RequestSpaceCreate -> Value
$ctoEncoding :: RequestSpaceCreate -> Encoding
toEncoding :: RequestSpaceCreate -> Encoding
$ctoJSONList :: [RequestSpaceCreate] -> Value
toJSONList :: [RequestSpaceCreate] -> Value
$ctoEncodingList :: [RequestSpaceCreate] -> Encoding
toEncodingList :: [RequestSpaceCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceCreate") RequestSpaceCreate
type ResponseSpaceCreate :: Type
newtype ResponseSpaceCreate = MkResponseSpaceCreate
{ ResponseSpaceCreate -> IdentifierSpace
responseSpaceCreateId :: IdentifierSpace
}
deriving stock (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
(ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> Eq ResponseSpaceCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
== :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
$c/= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
/= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
Eq, (forall x. ResponseSpaceCreate -> Rep ResponseSpaceCreate x)
-> (forall x. Rep ResponseSpaceCreate x -> ResponseSpaceCreate)
-> Generic ResponseSpaceCreate
forall x. Rep ResponseSpaceCreate x -> ResponseSpaceCreate
forall x. ResponseSpaceCreate -> Rep ResponseSpaceCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceCreate -> Rep ResponseSpaceCreate x
from :: forall x. ResponseSpaceCreate -> Rep ResponseSpaceCreate x
$cto :: forall x. Rep ResponseSpaceCreate x -> ResponseSpaceCreate
to :: forall x. Rep ResponseSpaceCreate x -> ResponseSpaceCreate
Generic, Eq ResponseSpaceCreate
Eq ResponseSpaceCreate =>
(ResponseSpaceCreate -> ResponseSpaceCreate -> Ordering)
-> (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> (ResponseSpaceCreate -> ResponseSpaceCreate -> Bool)
-> (ResponseSpaceCreate
-> ResponseSpaceCreate -> ResponseSpaceCreate)
-> (ResponseSpaceCreate
-> ResponseSpaceCreate -> ResponseSpaceCreate)
-> Ord ResponseSpaceCreate
ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
ResponseSpaceCreate -> ResponseSpaceCreate -> Ordering
ResponseSpaceCreate -> ResponseSpaceCreate -> ResponseSpaceCreate
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 :: ResponseSpaceCreate -> ResponseSpaceCreate -> Ordering
compare :: ResponseSpaceCreate -> ResponseSpaceCreate -> Ordering
$c< :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
< :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
$c<= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
<= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
$c> :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
> :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
$c>= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
>= :: ResponseSpaceCreate -> ResponseSpaceCreate -> Bool
$cmax :: ResponseSpaceCreate -> ResponseSpaceCreate -> ResponseSpaceCreate
max :: ResponseSpaceCreate -> ResponseSpaceCreate -> ResponseSpaceCreate
$cmin :: ResponseSpaceCreate -> ResponseSpaceCreate -> ResponseSpaceCreate
min :: ResponseSpaceCreate -> ResponseSpaceCreate -> ResponseSpaceCreate
Ord, ReadPrec [ResponseSpaceCreate]
ReadPrec ResponseSpaceCreate
Int -> ReadS ResponseSpaceCreate
ReadS [ResponseSpaceCreate]
(Int -> ReadS ResponseSpaceCreate)
-> ReadS [ResponseSpaceCreate]
-> ReadPrec ResponseSpaceCreate
-> ReadPrec [ResponseSpaceCreate]
-> Read ResponseSpaceCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceCreate
readsPrec :: Int -> ReadS ResponseSpaceCreate
$creadList :: ReadS [ResponseSpaceCreate]
readList :: ReadS [ResponseSpaceCreate]
$creadPrec :: ReadPrec ResponseSpaceCreate
readPrec :: ReadPrec ResponseSpaceCreate
$creadListPrec :: ReadPrec [ResponseSpaceCreate]
readListPrec :: ReadPrec [ResponseSpaceCreate]
Read, Int -> ResponseSpaceCreate -> ShowS
[ResponseSpaceCreate] -> ShowS
ResponseSpaceCreate -> String
(Int -> ResponseSpaceCreate -> ShowS)
-> (ResponseSpaceCreate -> String)
-> ([ResponseSpaceCreate] -> ShowS)
-> Show ResponseSpaceCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceCreate -> ShowS
showsPrec :: Int -> ResponseSpaceCreate -> ShowS
$cshow :: ResponseSpaceCreate -> String
show :: ResponseSpaceCreate -> String
$cshowList :: [ResponseSpaceCreate] -> ShowS
showList :: [ResponseSpaceCreate] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceCreate]
Value -> Parser ResponseSpaceCreate
(Value -> Parser ResponseSpaceCreate)
-> (Value -> Parser [ResponseSpaceCreate])
-> FromJSON ResponseSpaceCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceCreate
parseJSON :: Value -> Parser ResponseSpaceCreate
$cparseJSONList :: Value -> Parser [ResponseSpaceCreate]
parseJSONList :: Value -> Parser [ResponseSpaceCreate]
A.FromJSON, [ResponseSpaceCreate] -> Value
[ResponseSpaceCreate] -> Encoding
ResponseSpaceCreate -> Value
ResponseSpaceCreate -> Encoding
(ResponseSpaceCreate -> Value)
-> (ResponseSpaceCreate -> Encoding)
-> ([ResponseSpaceCreate] -> Value)
-> ([ResponseSpaceCreate] -> Encoding)
-> ToJSON ResponseSpaceCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceCreate -> Value
toJSON :: ResponseSpaceCreate -> Value
$ctoEncoding :: ResponseSpaceCreate -> Encoding
toEncoding :: ResponseSpaceCreate -> Encoding
$ctoJSONList :: [ResponseSpaceCreate] -> Value
toJSONList :: [ResponseSpaceCreate] -> Value
$ctoEncodingList :: [ResponseSpaceCreate] -> Encoding
toEncodingList :: [ResponseSpaceCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceCreate") ResponseSpaceCreate
type RequestSpaceDelete :: Type
newtype RequestSpaceDelete = MkRequestSpaceDelete
{ RequestSpaceDelete -> IdentifierSpace
requestSpaceDeleteId :: IdentifierSpace
}
deriving stock (RequestSpaceDelete -> RequestSpaceDelete -> Bool
(RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> (RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> Eq RequestSpaceDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
== :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
$c/= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
/= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
Eq, (forall x. RequestSpaceDelete -> Rep RequestSpaceDelete x)
-> (forall x. Rep RequestSpaceDelete x -> RequestSpaceDelete)
-> Generic RequestSpaceDelete
forall x. Rep RequestSpaceDelete x -> RequestSpaceDelete
forall x. RequestSpaceDelete -> Rep RequestSpaceDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceDelete -> Rep RequestSpaceDelete x
from :: forall x. RequestSpaceDelete -> Rep RequestSpaceDelete x
$cto :: forall x. Rep RequestSpaceDelete x -> RequestSpaceDelete
to :: forall x. Rep RequestSpaceDelete x -> RequestSpaceDelete
Generic, Eq RequestSpaceDelete
Eq RequestSpaceDelete =>
(RequestSpaceDelete -> RequestSpaceDelete -> Ordering)
-> (RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> (RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> (RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> (RequestSpaceDelete -> RequestSpaceDelete -> Bool)
-> (RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete)
-> (RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete)
-> Ord RequestSpaceDelete
RequestSpaceDelete -> RequestSpaceDelete -> Bool
RequestSpaceDelete -> RequestSpaceDelete -> Ordering
RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete
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 :: RequestSpaceDelete -> RequestSpaceDelete -> Ordering
compare :: RequestSpaceDelete -> RequestSpaceDelete -> Ordering
$c< :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
< :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
$c<= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
<= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
$c> :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
> :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
$c>= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
>= :: RequestSpaceDelete -> RequestSpaceDelete -> Bool
$cmax :: RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete
max :: RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete
$cmin :: RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete
min :: RequestSpaceDelete -> RequestSpaceDelete -> RequestSpaceDelete
Ord, ReadPrec [RequestSpaceDelete]
ReadPrec RequestSpaceDelete
Int -> ReadS RequestSpaceDelete
ReadS [RequestSpaceDelete]
(Int -> ReadS RequestSpaceDelete)
-> ReadS [RequestSpaceDelete]
-> ReadPrec RequestSpaceDelete
-> ReadPrec [RequestSpaceDelete]
-> Read RequestSpaceDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceDelete
readsPrec :: Int -> ReadS RequestSpaceDelete
$creadList :: ReadS [RequestSpaceDelete]
readList :: ReadS [RequestSpaceDelete]
$creadPrec :: ReadPrec RequestSpaceDelete
readPrec :: ReadPrec RequestSpaceDelete
$creadListPrec :: ReadPrec [RequestSpaceDelete]
readListPrec :: ReadPrec [RequestSpaceDelete]
Read, Int -> RequestSpaceDelete -> ShowS
[RequestSpaceDelete] -> ShowS
RequestSpaceDelete -> String
(Int -> RequestSpaceDelete -> ShowS)
-> (RequestSpaceDelete -> String)
-> ([RequestSpaceDelete] -> ShowS)
-> Show RequestSpaceDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceDelete -> ShowS
showsPrec :: Int -> RequestSpaceDelete -> ShowS
$cshow :: RequestSpaceDelete -> String
show :: RequestSpaceDelete -> String
$cshowList :: [RequestSpaceDelete] -> ShowS
showList :: [RequestSpaceDelete] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceDelete]
Value -> Parser RequestSpaceDelete
(Value -> Parser RequestSpaceDelete)
-> (Value -> Parser [RequestSpaceDelete])
-> FromJSON RequestSpaceDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceDelete
parseJSON :: Value -> Parser RequestSpaceDelete
$cparseJSONList :: Value -> Parser [RequestSpaceDelete]
parseJSONList :: Value -> Parser [RequestSpaceDelete]
A.FromJSON, [RequestSpaceDelete] -> Value
[RequestSpaceDelete] -> Encoding
RequestSpaceDelete -> Value
RequestSpaceDelete -> Encoding
(RequestSpaceDelete -> Value)
-> (RequestSpaceDelete -> Encoding)
-> ([RequestSpaceDelete] -> Value)
-> ([RequestSpaceDelete] -> Encoding)
-> ToJSON RequestSpaceDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceDelete -> Value
toJSON :: RequestSpaceDelete -> Value
$ctoEncoding :: RequestSpaceDelete -> Encoding
toEncoding :: RequestSpaceDelete -> Encoding
$ctoJSONList :: [RequestSpaceDelete] -> Value
toJSONList :: [RequestSpaceDelete] -> Value
$ctoEncodingList :: [RequestSpaceDelete] -> Encoding
toEncodingList :: [RequestSpaceDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceDelete") RequestSpaceDelete
type ResponseSpaceDelete :: Type
newtype ResponseSpaceDelete = MkResponseSpaceDelete
{ ResponseSpaceDelete -> ()
responseSpaceDeleteUnit :: ()
}
deriving stock (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
(ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> Eq ResponseSpaceDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
== :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
$c/= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
/= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
Eq, (forall x. ResponseSpaceDelete -> Rep ResponseSpaceDelete x)
-> (forall x. Rep ResponseSpaceDelete x -> ResponseSpaceDelete)
-> Generic ResponseSpaceDelete
forall x. Rep ResponseSpaceDelete x -> ResponseSpaceDelete
forall x. ResponseSpaceDelete -> Rep ResponseSpaceDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceDelete -> Rep ResponseSpaceDelete x
from :: forall x. ResponseSpaceDelete -> Rep ResponseSpaceDelete x
$cto :: forall x. Rep ResponseSpaceDelete x -> ResponseSpaceDelete
to :: forall x. Rep ResponseSpaceDelete x -> ResponseSpaceDelete
Generic, Eq ResponseSpaceDelete
Eq ResponseSpaceDelete =>
(ResponseSpaceDelete -> ResponseSpaceDelete -> Ordering)
-> (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> (ResponseSpaceDelete -> ResponseSpaceDelete -> Bool)
-> (ResponseSpaceDelete
-> ResponseSpaceDelete -> ResponseSpaceDelete)
-> (ResponseSpaceDelete
-> ResponseSpaceDelete -> ResponseSpaceDelete)
-> Ord ResponseSpaceDelete
ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
ResponseSpaceDelete -> ResponseSpaceDelete -> Ordering
ResponseSpaceDelete -> ResponseSpaceDelete -> ResponseSpaceDelete
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 :: ResponseSpaceDelete -> ResponseSpaceDelete -> Ordering
compare :: ResponseSpaceDelete -> ResponseSpaceDelete -> Ordering
$c< :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
< :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
$c<= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
<= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
$c> :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
> :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
$c>= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
>= :: ResponseSpaceDelete -> ResponseSpaceDelete -> Bool
$cmax :: ResponseSpaceDelete -> ResponseSpaceDelete -> ResponseSpaceDelete
max :: ResponseSpaceDelete -> ResponseSpaceDelete -> ResponseSpaceDelete
$cmin :: ResponseSpaceDelete -> ResponseSpaceDelete -> ResponseSpaceDelete
min :: ResponseSpaceDelete -> ResponseSpaceDelete -> ResponseSpaceDelete
Ord, ReadPrec [ResponseSpaceDelete]
ReadPrec ResponseSpaceDelete
Int -> ReadS ResponseSpaceDelete
ReadS [ResponseSpaceDelete]
(Int -> ReadS ResponseSpaceDelete)
-> ReadS [ResponseSpaceDelete]
-> ReadPrec ResponseSpaceDelete
-> ReadPrec [ResponseSpaceDelete]
-> Read ResponseSpaceDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceDelete
readsPrec :: Int -> ReadS ResponseSpaceDelete
$creadList :: ReadS [ResponseSpaceDelete]
readList :: ReadS [ResponseSpaceDelete]
$creadPrec :: ReadPrec ResponseSpaceDelete
readPrec :: ReadPrec ResponseSpaceDelete
$creadListPrec :: ReadPrec [ResponseSpaceDelete]
readListPrec :: ReadPrec [ResponseSpaceDelete]
Read, Int -> ResponseSpaceDelete -> ShowS
[ResponseSpaceDelete] -> ShowS
ResponseSpaceDelete -> String
(Int -> ResponseSpaceDelete -> ShowS)
-> (ResponseSpaceDelete -> String)
-> ([ResponseSpaceDelete] -> ShowS)
-> Show ResponseSpaceDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceDelete -> ShowS
showsPrec :: Int -> ResponseSpaceDelete -> ShowS
$cshow :: ResponseSpaceDelete -> String
show :: ResponseSpaceDelete -> String
$cshowList :: [ResponseSpaceDelete] -> ShowS
showList :: [ResponseSpaceDelete] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceDelete]
Value -> Parser ResponseSpaceDelete
(Value -> Parser ResponseSpaceDelete)
-> (Value -> Parser [ResponseSpaceDelete])
-> FromJSON ResponseSpaceDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceDelete
parseJSON :: Value -> Parser ResponseSpaceDelete
$cparseJSONList :: Value -> Parser [ResponseSpaceDelete]
parseJSONList :: Value -> Parser [ResponseSpaceDelete]
A.FromJSON, [ResponseSpaceDelete] -> Value
[ResponseSpaceDelete] -> Encoding
ResponseSpaceDelete -> Value
ResponseSpaceDelete -> Encoding
(ResponseSpaceDelete -> Value)
-> (ResponseSpaceDelete -> Encoding)
-> ([ResponseSpaceDelete] -> Value)
-> ([ResponseSpaceDelete] -> Encoding)
-> ToJSON ResponseSpaceDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceDelete -> Value
toJSON :: ResponseSpaceDelete -> Value
$ctoEncoding :: ResponseSpaceDelete -> Encoding
toEncoding :: ResponseSpaceDelete -> Encoding
$ctoJSONList :: [ResponseSpaceDelete] -> Value
toJSONList :: [ResponseSpaceDelete] -> Value
$ctoEncodingList :: [ResponseSpaceDelete] -> Encoding
toEncodingList :: [ResponseSpaceDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceDelete") ResponseSpaceDelete
type RequestSpaceEdit :: Type
data RequestSpaceEdit = MkRequestSpaceEdit
{ RequestSpaceEdit -> IdentifierSpace
requestSpaceEditId :: IdentifierSpace
, RequestSpaceEdit -> Updatable NameSpace
requestSpaceEditName :: Updatable NameSpace
, RequestSpaceEdit -> Updatable TZLabel
requestSpaceEditTimezone :: Updatable T.TZLabel
, RequestSpaceEdit -> Updatable VisibilitySpace
requestSpaceEditVisibility :: Updatable VisibilitySpace
}
deriving stock (RequestSpaceEdit -> RequestSpaceEdit -> Bool
(RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> (RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> Eq RequestSpaceEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
== :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
$c/= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
/= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
Eq, (forall x. RequestSpaceEdit -> Rep RequestSpaceEdit x)
-> (forall x. Rep RequestSpaceEdit x -> RequestSpaceEdit)
-> Generic RequestSpaceEdit
forall x. Rep RequestSpaceEdit x -> RequestSpaceEdit
forall x. RequestSpaceEdit -> Rep RequestSpaceEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceEdit -> Rep RequestSpaceEdit x
from :: forall x. RequestSpaceEdit -> Rep RequestSpaceEdit x
$cto :: forall x. Rep RequestSpaceEdit x -> RequestSpaceEdit
to :: forall x. Rep RequestSpaceEdit x -> RequestSpaceEdit
Generic, Eq RequestSpaceEdit
Eq RequestSpaceEdit =>
(RequestSpaceEdit -> RequestSpaceEdit -> Ordering)
-> (RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> (RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> (RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> (RequestSpaceEdit -> RequestSpaceEdit -> Bool)
-> (RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit)
-> (RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit)
-> Ord RequestSpaceEdit
RequestSpaceEdit -> RequestSpaceEdit -> Bool
RequestSpaceEdit -> RequestSpaceEdit -> Ordering
RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit
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 :: RequestSpaceEdit -> RequestSpaceEdit -> Ordering
compare :: RequestSpaceEdit -> RequestSpaceEdit -> Ordering
$c< :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
< :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
$c<= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
<= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
$c> :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
> :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
$c>= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
>= :: RequestSpaceEdit -> RequestSpaceEdit -> Bool
$cmax :: RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit
max :: RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit
$cmin :: RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit
min :: RequestSpaceEdit -> RequestSpaceEdit -> RequestSpaceEdit
Ord, ReadPrec [RequestSpaceEdit]
ReadPrec RequestSpaceEdit
Int -> ReadS RequestSpaceEdit
ReadS [RequestSpaceEdit]
(Int -> ReadS RequestSpaceEdit)
-> ReadS [RequestSpaceEdit]
-> ReadPrec RequestSpaceEdit
-> ReadPrec [RequestSpaceEdit]
-> Read RequestSpaceEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceEdit
readsPrec :: Int -> ReadS RequestSpaceEdit
$creadList :: ReadS [RequestSpaceEdit]
readList :: ReadS [RequestSpaceEdit]
$creadPrec :: ReadPrec RequestSpaceEdit
readPrec :: ReadPrec RequestSpaceEdit
$creadListPrec :: ReadPrec [RequestSpaceEdit]
readListPrec :: ReadPrec [RequestSpaceEdit]
Read, Int -> RequestSpaceEdit -> ShowS
[RequestSpaceEdit] -> ShowS
RequestSpaceEdit -> String
(Int -> RequestSpaceEdit -> ShowS)
-> (RequestSpaceEdit -> String)
-> ([RequestSpaceEdit] -> ShowS)
-> Show RequestSpaceEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceEdit -> ShowS
showsPrec :: Int -> RequestSpaceEdit -> ShowS
$cshow :: RequestSpaceEdit -> String
show :: RequestSpaceEdit -> String
$cshowList :: [RequestSpaceEdit] -> ShowS
showList :: [RequestSpaceEdit] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceEdit]
Value -> Parser RequestSpaceEdit
(Value -> Parser RequestSpaceEdit)
-> (Value -> Parser [RequestSpaceEdit])
-> FromJSON RequestSpaceEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceEdit
parseJSON :: Value -> Parser RequestSpaceEdit
$cparseJSONList :: Value -> Parser [RequestSpaceEdit]
parseJSONList :: Value -> Parser [RequestSpaceEdit]
A.FromJSON, [RequestSpaceEdit] -> Value
[RequestSpaceEdit] -> Encoding
RequestSpaceEdit -> Value
RequestSpaceEdit -> Encoding
(RequestSpaceEdit -> Value)
-> (RequestSpaceEdit -> Encoding)
-> ([RequestSpaceEdit] -> Value)
-> ([RequestSpaceEdit] -> Encoding)
-> ToJSON RequestSpaceEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceEdit -> Value
toJSON :: RequestSpaceEdit -> Value
$ctoEncoding :: RequestSpaceEdit -> Encoding
toEncoding :: RequestSpaceEdit -> Encoding
$ctoJSONList :: [RequestSpaceEdit] -> Value
toJSONList :: [RequestSpaceEdit] -> Value
$ctoEncodingList :: [RequestSpaceEdit] -> Encoding
toEncodingList :: [RequestSpaceEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceEdit") RequestSpaceEdit
type ResponseSpaceEdit :: Type
data ResponseSpaceEdit = MkResponseSpaceEdit
{ ResponseSpaceEdit -> IdentifierSpace
responseSpaceEditId :: IdentifierSpace
, ResponseSpaceEdit -> NameSpace
responseSpaceEditName :: NameSpace
, ResponseSpaceEdit -> TZLabel
responseSpaceEditTimezone :: T.TZLabel
, ResponseSpaceEdit -> VisibilitySpace
responseSpaceEditVisibility :: VisibilitySpace
}
deriving stock (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
(ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> Eq ResponseSpaceEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
== :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
$c/= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
/= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
Eq, (forall x. ResponseSpaceEdit -> Rep ResponseSpaceEdit x)
-> (forall x. Rep ResponseSpaceEdit x -> ResponseSpaceEdit)
-> Generic ResponseSpaceEdit
forall x. Rep ResponseSpaceEdit x -> ResponseSpaceEdit
forall x. ResponseSpaceEdit -> Rep ResponseSpaceEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceEdit -> Rep ResponseSpaceEdit x
from :: forall x. ResponseSpaceEdit -> Rep ResponseSpaceEdit x
$cto :: forall x. Rep ResponseSpaceEdit x -> ResponseSpaceEdit
to :: forall x. Rep ResponseSpaceEdit x -> ResponseSpaceEdit
Generic, Eq ResponseSpaceEdit
Eq ResponseSpaceEdit =>
(ResponseSpaceEdit -> ResponseSpaceEdit -> Ordering)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> Bool)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit)
-> (ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit)
-> Ord ResponseSpaceEdit
ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
ResponseSpaceEdit -> ResponseSpaceEdit -> Ordering
ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit
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 :: ResponseSpaceEdit -> ResponseSpaceEdit -> Ordering
compare :: ResponseSpaceEdit -> ResponseSpaceEdit -> Ordering
$c< :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
< :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
$c<= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
<= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
$c> :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
> :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
$c>= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
>= :: ResponseSpaceEdit -> ResponseSpaceEdit -> Bool
$cmax :: ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit
max :: ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit
$cmin :: ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit
min :: ResponseSpaceEdit -> ResponseSpaceEdit -> ResponseSpaceEdit
Ord, ReadPrec [ResponseSpaceEdit]
ReadPrec ResponseSpaceEdit
Int -> ReadS ResponseSpaceEdit
ReadS [ResponseSpaceEdit]
(Int -> ReadS ResponseSpaceEdit)
-> ReadS [ResponseSpaceEdit]
-> ReadPrec ResponseSpaceEdit
-> ReadPrec [ResponseSpaceEdit]
-> Read ResponseSpaceEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceEdit
readsPrec :: Int -> ReadS ResponseSpaceEdit
$creadList :: ReadS [ResponseSpaceEdit]
readList :: ReadS [ResponseSpaceEdit]
$creadPrec :: ReadPrec ResponseSpaceEdit
readPrec :: ReadPrec ResponseSpaceEdit
$creadListPrec :: ReadPrec [ResponseSpaceEdit]
readListPrec :: ReadPrec [ResponseSpaceEdit]
Read, Int -> ResponseSpaceEdit -> ShowS
[ResponseSpaceEdit] -> ShowS
ResponseSpaceEdit -> String
(Int -> ResponseSpaceEdit -> ShowS)
-> (ResponseSpaceEdit -> String)
-> ([ResponseSpaceEdit] -> ShowS)
-> Show ResponseSpaceEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceEdit -> ShowS
showsPrec :: Int -> ResponseSpaceEdit -> ShowS
$cshow :: ResponseSpaceEdit -> String
show :: ResponseSpaceEdit -> String
$cshowList :: [ResponseSpaceEdit] -> ShowS
showList :: [ResponseSpaceEdit] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceEdit]
Value -> Parser ResponseSpaceEdit
(Value -> Parser ResponseSpaceEdit)
-> (Value -> Parser [ResponseSpaceEdit])
-> FromJSON ResponseSpaceEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceEdit
parseJSON :: Value -> Parser ResponseSpaceEdit
$cparseJSONList :: Value -> Parser [ResponseSpaceEdit]
parseJSONList :: Value -> Parser [ResponseSpaceEdit]
A.FromJSON, [ResponseSpaceEdit] -> Value
[ResponseSpaceEdit] -> Encoding
ResponseSpaceEdit -> Value
ResponseSpaceEdit -> Encoding
(ResponseSpaceEdit -> Value)
-> (ResponseSpaceEdit -> Encoding)
-> ([ResponseSpaceEdit] -> Value)
-> ([ResponseSpaceEdit] -> Encoding)
-> ToJSON ResponseSpaceEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceEdit -> Value
toJSON :: ResponseSpaceEdit -> Value
$ctoEncoding :: ResponseSpaceEdit -> Encoding
toEncoding :: ResponseSpaceEdit -> Encoding
$ctoJSONList :: [ResponseSpaceEdit] -> Value
toJSONList :: [ResponseSpaceEdit] -> Value
$ctoEncodingList :: [ResponseSpaceEdit] -> Encoding
toEncodingList :: [ResponseSpaceEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceEdit") ResponseSpaceEdit
type RequestSpaceJoin :: Type
data RequestSpaceJoin = MkRequestSpaceJoin
{ RequestSpaceJoin -> NameOrIdentifier NameSpace IdentifierSpace
requestSpaceJoinSpace :: NameOrIdentifier NameSpace IdentifierSpace
, RequestSpaceJoin -> NameOrIdentifier NameRole IdentifierRole
requestSpaceJoinRole :: NameOrIdentifier NameRole IdentifierRole
, RequestSpaceJoin -> Maybe Text
requestSpaceJoinPassword :: Maybe T.Text
}
deriving stock (RequestSpaceJoin -> RequestSpaceJoin -> Bool
(RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> (RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> Eq RequestSpaceJoin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
== :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
$c/= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
/= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
Eq, (forall x. RequestSpaceJoin -> Rep RequestSpaceJoin x)
-> (forall x. Rep RequestSpaceJoin x -> RequestSpaceJoin)
-> Generic RequestSpaceJoin
forall x. Rep RequestSpaceJoin x -> RequestSpaceJoin
forall x. RequestSpaceJoin -> Rep RequestSpaceJoin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceJoin -> Rep RequestSpaceJoin x
from :: forall x. RequestSpaceJoin -> Rep RequestSpaceJoin x
$cto :: forall x. Rep RequestSpaceJoin x -> RequestSpaceJoin
to :: forall x. Rep RequestSpaceJoin x -> RequestSpaceJoin
Generic, Eq RequestSpaceJoin
Eq RequestSpaceJoin =>
(RequestSpaceJoin -> RequestSpaceJoin -> Ordering)
-> (RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> (RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> (RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> (RequestSpaceJoin -> RequestSpaceJoin -> Bool)
-> (RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin)
-> (RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin)
-> Ord RequestSpaceJoin
RequestSpaceJoin -> RequestSpaceJoin -> Bool
RequestSpaceJoin -> RequestSpaceJoin -> Ordering
RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin
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 :: RequestSpaceJoin -> RequestSpaceJoin -> Ordering
compare :: RequestSpaceJoin -> RequestSpaceJoin -> Ordering
$c< :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
< :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
$c<= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
<= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
$c> :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
> :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
$c>= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
>= :: RequestSpaceJoin -> RequestSpaceJoin -> Bool
$cmax :: RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin
max :: RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin
$cmin :: RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin
min :: RequestSpaceJoin -> RequestSpaceJoin -> RequestSpaceJoin
Ord, ReadPrec [RequestSpaceJoin]
ReadPrec RequestSpaceJoin
Int -> ReadS RequestSpaceJoin
ReadS [RequestSpaceJoin]
(Int -> ReadS RequestSpaceJoin)
-> ReadS [RequestSpaceJoin]
-> ReadPrec RequestSpaceJoin
-> ReadPrec [RequestSpaceJoin]
-> Read RequestSpaceJoin
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceJoin
readsPrec :: Int -> ReadS RequestSpaceJoin
$creadList :: ReadS [RequestSpaceJoin]
readList :: ReadS [RequestSpaceJoin]
$creadPrec :: ReadPrec RequestSpaceJoin
readPrec :: ReadPrec RequestSpaceJoin
$creadListPrec :: ReadPrec [RequestSpaceJoin]
readListPrec :: ReadPrec [RequestSpaceJoin]
Read, Int -> RequestSpaceJoin -> ShowS
[RequestSpaceJoin] -> ShowS
RequestSpaceJoin -> String
(Int -> RequestSpaceJoin -> ShowS)
-> (RequestSpaceJoin -> String)
-> ([RequestSpaceJoin] -> ShowS)
-> Show RequestSpaceJoin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceJoin -> ShowS
showsPrec :: Int -> RequestSpaceJoin -> ShowS
$cshow :: RequestSpaceJoin -> String
show :: RequestSpaceJoin -> String
$cshowList :: [RequestSpaceJoin] -> ShowS
showList :: [RequestSpaceJoin] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceJoin]
Value -> Parser RequestSpaceJoin
(Value -> Parser RequestSpaceJoin)
-> (Value -> Parser [RequestSpaceJoin])
-> FromJSON RequestSpaceJoin
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceJoin
parseJSON :: Value -> Parser RequestSpaceJoin
$cparseJSONList :: Value -> Parser [RequestSpaceJoin]
parseJSONList :: Value -> Parser [RequestSpaceJoin]
A.FromJSON, [RequestSpaceJoin] -> Value
[RequestSpaceJoin] -> Encoding
RequestSpaceJoin -> Value
RequestSpaceJoin -> Encoding
(RequestSpaceJoin -> Value)
-> (RequestSpaceJoin -> Encoding)
-> ([RequestSpaceJoin] -> Value)
-> ([RequestSpaceJoin] -> Encoding)
-> ToJSON RequestSpaceJoin
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceJoin -> Value
toJSON :: RequestSpaceJoin -> Value
$ctoEncoding :: RequestSpaceJoin -> Encoding
toEncoding :: RequestSpaceJoin -> Encoding
$ctoJSONList :: [RequestSpaceJoin] -> Value
toJSONList :: [RequestSpaceJoin] -> Value
$ctoEncodingList :: [RequestSpaceJoin] -> Encoding
toEncodingList :: [RequestSpaceJoin] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceJoin") RequestSpaceJoin
type ResponseSpaceJoin :: Type
newtype ResponseSpaceJoin = MkResponseSpaceJoin
{ ResponseSpaceJoin -> ()
responseSpaceJoinUnit :: ()
}
deriving stock (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
(ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> Eq ResponseSpaceJoin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
== :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
$c/= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
/= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
Eq, (forall x. ResponseSpaceJoin -> Rep ResponseSpaceJoin x)
-> (forall x. Rep ResponseSpaceJoin x -> ResponseSpaceJoin)
-> Generic ResponseSpaceJoin
forall x. Rep ResponseSpaceJoin x -> ResponseSpaceJoin
forall x. ResponseSpaceJoin -> Rep ResponseSpaceJoin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceJoin -> Rep ResponseSpaceJoin x
from :: forall x. ResponseSpaceJoin -> Rep ResponseSpaceJoin x
$cto :: forall x. Rep ResponseSpaceJoin x -> ResponseSpaceJoin
to :: forall x. Rep ResponseSpaceJoin x -> ResponseSpaceJoin
Generic, Eq ResponseSpaceJoin
Eq ResponseSpaceJoin =>
(ResponseSpaceJoin -> ResponseSpaceJoin -> Ordering)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> Bool)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin)
-> (ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin)
-> Ord ResponseSpaceJoin
ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
ResponseSpaceJoin -> ResponseSpaceJoin -> Ordering
ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin
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 :: ResponseSpaceJoin -> ResponseSpaceJoin -> Ordering
compare :: ResponseSpaceJoin -> ResponseSpaceJoin -> Ordering
$c< :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
< :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
$c<= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
<= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
$c> :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
> :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
$c>= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
>= :: ResponseSpaceJoin -> ResponseSpaceJoin -> Bool
$cmax :: ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin
max :: ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin
$cmin :: ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin
min :: ResponseSpaceJoin -> ResponseSpaceJoin -> ResponseSpaceJoin
Ord, ReadPrec [ResponseSpaceJoin]
ReadPrec ResponseSpaceJoin
Int -> ReadS ResponseSpaceJoin
ReadS [ResponseSpaceJoin]
(Int -> ReadS ResponseSpaceJoin)
-> ReadS [ResponseSpaceJoin]
-> ReadPrec ResponseSpaceJoin
-> ReadPrec [ResponseSpaceJoin]
-> Read ResponseSpaceJoin
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceJoin
readsPrec :: Int -> ReadS ResponseSpaceJoin
$creadList :: ReadS [ResponseSpaceJoin]
readList :: ReadS [ResponseSpaceJoin]
$creadPrec :: ReadPrec ResponseSpaceJoin
readPrec :: ReadPrec ResponseSpaceJoin
$creadListPrec :: ReadPrec [ResponseSpaceJoin]
readListPrec :: ReadPrec [ResponseSpaceJoin]
Read, Int -> ResponseSpaceJoin -> ShowS
[ResponseSpaceJoin] -> ShowS
ResponseSpaceJoin -> String
(Int -> ResponseSpaceJoin -> ShowS)
-> (ResponseSpaceJoin -> String)
-> ([ResponseSpaceJoin] -> ShowS)
-> Show ResponseSpaceJoin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceJoin -> ShowS
showsPrec :: Int -> ResponseSpaceJoin -> ShowS
$cshow :: ResponseSpaceJoin -> String
show :: ResponseSpaceJoin -> String
$cshowList :: [ResponseSpaceJoin] -> ShowS
showList :: [ResponseSpaceJoin] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceJoin]
Value -> Parser ResponseSpaceJoin
(Value -> Parser ResponseSpaceJoin)
-> (Value -> Parser [ResponseSpaceJoin])
-> FromJSON ResponseSpaceJoin
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceJoin
parseJSON :: Value -> Parser ResponseSpaceJoin
$cparseJSONList :: Value -> Parser [ResponseSpaceJoin]
parseJSONList :: Value -> Parser [ResponseSpaceJoin]
A.FromJSON, [ResponseSpaceJoin] -> Value
[ResponseSpaceJoin] -> Encoding
ResponseSpaceJoin -> Value
ResponseSpaceJoin -> Encoding
(ResponseSpaceJoin -> Value)
-> (ResponseSpaceJoin -> Encoding)
-> ([ResponseSpaceJoin] -> Value)
-> ([ResponseSpaceJoin] -> Encoding)
-> ToJSON ResponseSpaceJoin
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceJoin -> Value
toJSON :: ResponseSpaceJoin -> Value
$ctoEncoding :: ResponseSpaceJoin -> Encoding
toEncoding :: ResponseSpaceJoin -> Encoding
$ctoJSONList :: [ResponseSpaceJoin] -> Value
toJSONList :: [ResponseSpaceJoin] -> Value
$ctoEncodingList :: [ResponseSpaceJoin] -> Encoding
toEncodingList :: [ResponseSpaceJoin] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceJoin") ResponseSpaceJoin
type RequestSpaceLeave :: Type
newtype RequestSpaceLeave = MkRequestSpaceLeave
{ RequestSpaceLeave -> NameOrIdentifier NameSpace IdentifierSpace
requestSpaceLeaveSpace :: NameOrIdentifier NameSpace IdentifierSpace
}
deriving stock (RequestSpaceLeave -> RequestSpaceLeave -> Bool
(RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> (RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> Eq RequestSpaceLeave
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
== :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
$c/= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
/= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
Eq, (forall x. RequestSpaceLeave -> Rep RequestSpaceLeave x)
-> (forall x. Rep RequestSpaceLeave x -> RequestSpaceLeave)
-> Generic RequestSpaceLeave
forall x. Rep RequestSpaceLeave x -> RequestSpaceLeave
forall x. RequestSpaceLeave -> Rep RequestSpaceLeave x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceLeave -> Rep RequestSpaceLeave x
from :: forall x. RequestSpaceLeave -> Rep RequestSpaceLeave x
$cto :: forall x. Rep RequestSpaceLeave x -> RequestSpaceLeave
to :: forall x. Rep RequestSpaceLeave x -> RequestSpaceLeave
Generic, Eq RequestSpaceLeave
Eq RequestSpaceLeave =>
(RequestSpaceLeave -> RequestSpaceLeave -> Ordering)
-> (RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> (RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> (RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> (RequestSpaceLeave -> RequestSpaceLeave -> Bool)
-> (RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave)
-> (RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave)
-> Ord RequestSpaceLeave
RequestSpaceLeave -> RequestSpaceLeave -> Bool
RequestSpaceLeave -> RequestSpaceLeave -> Ordering
RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave
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 :: RequestSpaceLeave -> RequestSpaceLeave -> Ordering
compare :: RequestSpaceLeave -> RequestSpaceLeave -> Ordering
$c< :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
< :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
$c<= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
<= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
$c> :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
> :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
$c>= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
>= :: RequestSpaceLeave -> RequestSpaceLeave -> Bool
$cmax :: RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave
max :: RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave
$cmin :: RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave
min :: RequestSpaceLeave -> RequestSpaceLeave -> RequestSpaceLeave
Ord, ReadPrec [RequestSpaceLeave]
ReadPrec RequestSpaceLeave
Int -> ReadS RequestSpaceLeave
ReadS [RequestSpaceLeave]
(Int -> ReadS RequestSpaceLeave)
-> ReadS [RequestSpaceLeave]
-> ReadPrec RequestSpaceLeave
-> ReadPrec [RequestSpaceLeave]
-> Read RequestSpaceLeave
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceLeave
readsPrec :: Int -> ReadS RequestSpaceLeave
$creadList :: ReadS [RequestSpaceLeave]
readList :: ReadS [RequestSpaceLeave]
$creadPrec :: ReadPrec RequestSpaceLeave
readPrec :: ReadPrec RequestSpaceLeave
$creadListPrec :: ReadPrec [RequestSpaceLeave]
readListPrec :: ReadPrec [RequestSpaceLeave]
Read, Int -> RequestSpaceLeave -> ShowS
[RequestSpaceLeave] -> ShowS
RequestSpaceLeave -> String
(Int -> RequestSpaceLeave -> ShowS)
-> (RequestSpaceLeave -> String)
-> ([RequestSpaceLeave] -> ShowS)
-> Show RequestSpaceLeave
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceLeave -> ShowS
showsPrec :: Int -> RequestSpaceLeave -> ShowS
$cshow :: RequestSpaceLeave -> String
show :: RequestSpaceLeave -> String
$cshowList :: [RequestSpaceLeave] -> ShowS
showList :: [RequestSpaceLeave] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceLeave]
Value -> Parser RequestSpaceLeave
(Value -> Parser RequestSpaceLeave)
-> (Value -> Parser [RequestSpaceLeave])
-> FromJSON RequestSpaceLeave
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceLeave
parseJSON :: Value -> Parser RequestSpaceLeave
$cparseJSONList :: Value -> Parser [RequestSpaceLeave]
parseJSONList :: Value -> Parser [RequestSpaceLeave]
A.FromJSON, [RequestSpaceLeave] -> Value
[RequestSpaceLeave] -> Encoding
RequestSpaceLeave -> Value
RequestSpaceLeave -> Encoding
(RequestSpaceLeave -> Value)
-> (RequestSpaceLeave -> Encoding)
-> ([RequestSpaceLeave] -> Value)
-> ([RequestSpaceLeave] -> Encoding)
-> ToJSON RequestSpaceLeave
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceLeave -> Value
toJSON :: RequestSpaceLeave -> Value
$ctoEncoding :: RequestSpaceLeave -> Encoding
toEncoding :: RequestSpaceLeave -> Encoding
$ctoJSONList :: [RequestSpaceLeave] -> Value
toJSONList :: [RequestSpaceLeave] -> Value
$ctoEncodingList :: [RequestSpaceLeave] -> Encoding
toEncodingList :: [RequestSpaceLeave] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceLeave") RequestSpaceLeave
type ResponseSpaceLeave :: Type
newtype ResponseSpaceLeave = MkResponseSpaceLeave
{ ResponseSpaceLeave -> ()
responseSpaceLeaveUnit :: ()
}
deriving stock (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
(ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> Eq ResponseSpaceLeave
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
== :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
$c/= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
/= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
Eq, (forall x. ResponseSpaceLeave -> Rep ResponseSpaceLeave x)
-> (forall x. Rep ResponseSpaceLeave x -> ResponseSpaceLeave)
-> Generic ResponseSpaceLeave
forall x. Rep ResponseSpaceLeave x -> ResponseSpaceLeave
forall x. ResponseSpaceLeave -> Rep ResponseSpaceLeave x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceLeave -> Rep ResponseSpaceLeave x
from :: forall x. ResponseSpaceLeave -> Rep ResponseSpaceLeave x
$cto :: forall x. Rep ResponseSpaceLeave x -> ResponseSpaceLeave
to :: forall x. Rep ResponseSpaceLeave x -> ResponseSpaceLeave
Generic, Eq ResponseSpaceLeave
Eq ResponseSpaceLeave =>
(ResponseSpaceLeave -> ResponseSpaceLeave -> Ordering)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> Bool)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave)
-> (ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave)
-> Ord ResponseSpaceLeave
ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
ResponseSpaceLeave -> ResponseSpaceLeave -> Ordering
ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave
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 :: ResponseSpaceLeave -> ResponseSpaceLeave -> Ordering
compare :: ResponseSpaceLeave -> ResponseSpaceLeave -> Ordering
$c< :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
< :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
$c<= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
<= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
$c> :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
> :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
$c>= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
>= :: ResponseSpaceLeave -> ResponseSpaceLeave -> Bool
$cmax :: ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave
max :: ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave
$cmin :: ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave
min :: ResponseSpaceLeave -> ResponseSpaceLeave -> ResponseSpaceLeave
Ord, ReadPrec [ResponseSpaceLeave]
ReadPrec ResponseSpaceLeave
Int -> ReadS ResponseSpaceLeave
ReadS [ResponseSpaceLeave]
(Int -> ReadS ResponseSpaceLeave)
-> ReadS [ResponseSpaceLeave]
-> ReadPrec ResponseSpaceLeave
-> ReadPrec [ResponseSpaceLeave]
-> Read ResponseSpaceLeave
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceLeave
readsPrec :: Int -> ReadS ResponseSpaceLeave
$creadList :: ReadS [ResponseSpaceLeave]
readList :: ReadS [ResponseSpaceLeave]
$creadPrec :: ReadPrec ResponseSpaceLeave
readPrec :: ReadPrec ResponseSpaceLeave
$creadListPrec :: ReadPrec [ResponseSpaceLeave]
readListPrec :: ReadPrec [ResponseSpaceLeave]
Read, Int -> ResponseSpaceLeave -> ShowS
[ResponseSpaceLeave] -> ShowS
ResponseSpaceLeave -> String
(Int -> ResponseSpaceLeave -> ShowS)
-> (ResponseSpaceLeave -> String)
-> ([ResponseSpaceLeave] -> ShowS)
-> Show ResponseSpaceLeave
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceLeave -> ShowS
showsPrec :: Int -> ResponseSpaceLeave -> ShowS
$cshow :: ResponseSpaceLeave -> String
show :: ResponseSpaceLeave -> String
$cshowList :: [ResponseSpaceLeave] -> ShowS
showList :: [ResponseSpaceLeave] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceLeave]
Value -> Parser ResponseSpaceLeave
(Value -> Parser ResponseSpaceLeave)
-> (Value -> Parser [ResponseSpaceLeave])
-> FromJSON ResponseSpaceLeave
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceLeave
parseJSON :: Value -> Parser ResponseSpaceLeave
$cparseJSONList :: Value -> Parser [ResponseSpaceLeave]
parseJSONList :: Value -> Parser [ResponseSpaceLeave]
A.FromJSON, [ResponseSpaceLeave] -> Value
[ResponseSpaceLeave] -> Encoding
ResponseSpaceLeave -> Value
ResponseSpaceLeave -> Encoding
(ResponseSpaceLeave -> Value)
-> (ResponseSpaceLeave -> Encoding)
-> ([ResponseSpaceLeave] -> Value)
-> ([ResponseSpaceLeave] -> Encoding)
-> ToJSON ResponseSpaceLeave
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceLeave -> Value
toJSON :: ResponseSpaceLeave -> Value
$ctoEncoding :: ResponseSpaceLeave -> Encoding
toEncoding :: ResponseSpaceLeave -> Encoding
$ctoJSONList :: [ResponseSpaceLeave] -> Value
toJSONList :: [ResponseSpaceLeave] -> Value
$ctoEncodingList :: [ResponseSpaceLeave] -> Encoding
toEncodingList :: [ResponseSpaceLeave] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceLeave") ResponseSpaceLeave
type RequestSpaceKick :: Type
data RequestSpaceKick = MkRequestSpaceKick
{ RequestSpaceKick -> IdentifierSpace
requestSpaceKickSpace :: IdentifierSpace
, RequestSpaceKick -> IdentifierUser
requestSpaceKickUser :: IdentifierUser
}
deriving stock (RequestSpaceKick -> RequestSpaceKick -> Bool
(RequestSpaceKick -> RequestSpaceKick -> Bool)
-> (RequestSpaceKick -> RequestSpaceKick -> Bool)
-> Eq RequestSpaceKick
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceKick -> RequestSpaceKick -> Bool
== :: RequestSpaceKick -> RequestSpaceKick -> Bool
$c/= :: RequestSpaceKick -> RequestSpaceKick -> Bool
/= :: RequestSpaceKick -> RequestSpaceKick -> Bool
Eq, (forall x. RequestSpaceKick -> Rep RequestSpaceKick x)
-> (forall x. Rep RequestSpaceKick x -> RequestSpaceKick)
-> Generic RequestSpaceKick
forall x. Rep RequestSpaceKick x -> RequestSpaceKick
forall x. RequestSpaceKick -> Rep RequestSpaceKick x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceKick -> Rep RequestSpaceKick x
from :: forall x. RequestSpaceKick -> Rep RequestSpaceKick x
$cto :: forall x. Rep RequestSpaceKick x -> RequestSpaceKick
to :: forall x. Rep RequestSpaceKick x -> RequestSpaceKick
Generic, Eq RequestSpaceKick
Eq RequestSpaceKick =>
(RequestSpaceKick -> RequestSpaceKick -> Ordering)
-> (RequestSpaceKick -> RequestSpaceKick -> Bool)
-> (RequestSpaceKick -> RequestSpaceKick -> Bool)
-> (RequestSpaceKick -> RequestSpaceKick -> Bool)
-> (RequestSpaceKick -> RequestSpaceKick -> Bool)
-> (RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick)
-> (RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick)
-> Ord RequestSpaceKick
RequestSpaceKick -> RequestSpaceKick -> Bool
RequestSpaceKick -> RequestSpaceKick -> Ordering
RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick
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 :: RequestSpaceKick -> RequestSpaceKick -> Ordering
compare :: RequestSpaceKick -> RequestSpaceKick -> Ordering
$c< :: RequestSpaceKick -> RequestSpaceKick -> Bool
< :: RequestSpaceKick -> RequestSpaceKick -> Bool
$c<= :: RequestSpaceKick -> RequestSpaceKick -> Bool
<= :: RequestSpaceKick -> RequestSpaceKick -> Bool
$c> :: RequestSpaceKick -> RequestSpaceKick -> Bool
> :: RequestSpaceKick -> RequestSpaceKick -> Bool
$c>= :: RequestSpaceKick -> RequestSpaceKick -> Bool
>= :: RequestSpaceKick -> RequestSpaceKick -> Bool
$cmax :: RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick
max :: RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick
$cmin :: RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick
min :: RequestSpaceKick -> RequestSpaceKick -> RequestSpaceKick
Ord, ReadPrec [RequestSpaceKick]
ReadPrec RequestSpaceKick
Int -> ReadS RequestSpaceKick
ReadS [RequestSpaceKick]
(Int -> ReadS RequestSpaceKick)
-> ReadS [RequestSpaceKick]
-> ReadPrec RequestSpaceKick
-> ReadPrec [RequestSpaceKick]
-> Read RequestSpaceKick
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceKick
readsPrec :: Int -> ReadS RequestSpaceKick
$creadList :: ReadS [RequestSpaceKick]
readList :: ReadS [RequestSpaceKick]
$creadPrec :: ReadPrec RequestSpaceKick
readPrec :: ReadPrec RequestSpaceKick
$creadListPrec :: ReadPrec [RequestSpaceKick]
readListPrec :: ReadPrec [RequestSpaceKick]
Read, Int -> RequestSpaceKick -> ShowS
[RequestSpaceKick] -> ShowS
RequestSpaceKick -> String
(Int -> RequestSpaceKick -> ShowS)
-> (RequestSpaceKick -> String)
-> ([RequestSpaceKick] -> ShowS)
-> Show RequestSpaceKick
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceKick -> ShowS
showsPrec :: Int -> RequestSpaceKick -> ShowS
$cshow :: RequestSpaceKick -> String
show :: RequestSpaceKick -> String
$cshowList :: [RequestSpaceKick] -> ShowS
showList :: [RequestSpaceKick] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceKick]
Value -> Parser RequestSpaceKick
(Value -> Parser RequestSpaceKick)
-> (Value -> Parser [RequestSpaceKick])
-> FromJSON RequestSpaceKick
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceKick
parseJSON :: Value -> Parser RequestSpaceKick
$cparseJSONList :: Value -> Parser [RequestSpaceKick]
parseJSONList :: Value -> Parser [RequestSpaceKick]
A.FromJSON, [RequestSpaceKick] -> Value
[RequestSpaceKick] -> Encoding
RequestSpaceKick -> Value
RequestSpaceKick -> Encoding
(RequestSpaceKick -> Value)
-> (RequestSpaceKick -> Encoding)
-> ([RequestSpaceKick] -> Value)
-> ([RequestSpaceKick] -> Encoding)
-> ToJSON RequestSpaceKick
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceKick -> Value
toJSON :: RequestSpaceKick -> Value
$ctoEncoding :: RequestSpaceKick -> Encoding
toEncoding :: RequestSpaceKick -> Encoding
$ctoJSONList :: [RequestSpaceKick] -> Value
toJSONList :: [RequestSpaceKick] -> Value
$ctoEncodingList :: [RequestSpaceKick] -> Encoding
toEncodingList :: [RequestSpaceKick] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceKick") RequestSpaceKick
type ResponseSpaceKick :: Type
newtype ResponseSpaceKick = MkResponseSpaceKick
{ ResponseSpaceKick -> ()
responseSpaceKickUnit :: ()
}
deriving stock (ResponseSpaceKick -> ResponseSpaceKick -> Bool
(ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> (ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> Eq ResponseSpaceKick
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
== :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
$c/= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
/= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
Eq, (forall x. ResponseSpaceKick -> Rep ResponseSpaceKick x)
-> (forall x. Rep ResponseSpaceKick x -> ResponseSpaceKick)
-> Generic ResponseSpaceKick
forall x. Rep ResponseSpaceKick x -> ResponseSpaceKick
forall x. ResponseSpaceKick -> Rep ResponseSpaceKick x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceKick -> Rep ResponseSpaceKick x
from :: forall x. ResponseSpaceKick -> Rep ResponseSpaceKick x
$cto :: forall x. Rep ResponseSpaceKick x -> ResponseSpaceKick
to :: forall x. Rep ResponseSpaceKick x -> ResponseSpaceKick
Generic, Eq ResponseSpaceKick
Eq ResponseSpaceKick =>
(ResponseSpaceKick -> ResponseSpaceKick -> Ordering)
-> (ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> (ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> (ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> (ResponseSpaceKick -> ResponseSpaceKick -> Bool)
-> (ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick)
-> (ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick)
-> Ord ResponseSpaceKick
ResponseSpaceKick -> ResponseSpaceKick -> Bool
ResponseSpaceKick -> ResponseSpaceKick -> Ordering
ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick
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 :: ResponseSpaceKick -> ResponseSpaceKick -> Ordering
compare :: ResponseSpaceKick -> ResponseSpaceKick -> Ordering
$c< :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
< :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
$c<= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
<= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
$c> :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
> :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
$c>= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
>= :: ResponseSpaceKick -> ResponseSpaceKick -> Bool
$cmax :: ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick
max :: ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick
$cmin :: ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick
min :: ResponseSpaceKick -> ResponseSpaceKick -> ResponseSpaceKick
Ord, ReadPrec [ResponseSpaceKick]
ReadPrec ResponseSpaceKick
Int -> ReadS ResponseSpaceKick
ReadS [ResponseSpaceKick]
(Int -> ReadS ResponseSpaceKick)
-> ReadS [ResponseSpaceKick]
-> ReadPrec ResponseSpaceKick
-> ReadPrec [ResponseSpaceKick]
-> Read ResponseSpaceKick
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceKick
readsPrec :: Int -> ReadS ResponseSpaceKick
$creadList :: ReadS [ResponseSpaceKick]
readList :: ReadS [ResponseSpaceKick]
$creadPrec :: ReadPrec ResponseSpaceKick
readPrec :: ReadPrec ResponseSpaceKick
$creadListPrec :: ReadPrec [ResponseSpaceKick]
readListPrec :: ReadPrec [ResponseSpaceKick]
Read, Int -> ResponseSpaceKick -> ShowS
[ResponseSpaceKick] -> ShowS
ResponseSpaceKick -> String
(Int -> ResponseSpaceKick -> ShowS)
-> (ResponseSpaceKick -> String)
-> ([ResponseSpaceKick] -> ShowS)
-> Show ResponseSpaceKick
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceKick -> ShowS
showsPrec :: Int -> ResponseSpaceKick -> ShowS
$cshow :: ResponseSpaceKick -> String
show :: ResponseSpaceKick -> String
$cshowList :: [ResponseSpaceKick] -> ShowS
showList :: [ResponseSpaceKick] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceKick]
Value -> Parser ResponseSpaceKick
(Value -> Parser ResponseSpaceKick)
-> (Value -> Parser [ResponseSpaceKick])
-> FromJSON ResponseSpaceKick
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceKick
parseJSON :: Value -> Parser ResponseSpaceKick
$cparseJSONList :: Value -> Parser [ResponseSpaceKick]
parseJSONList :: Value -> Parser [ResponseSpaceKick]
A.FromJSON, [ResponseSpaceKick] -> Value
[ResponseSpaceKick] -> Encoding
ResponseSpaceKick -> Value
ResponseSpaceKick -> Encoding
(ResponseSpaceKick -> Value)
-> (ResponseSpaceKick -> Encoding)
-> ([ResponseSpaceKick] -> Value)
-> ([ResponseSpaceKick] -> Encoding)
-> ToJSON ResponseSpaceKick
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceKick -> Value
toJSON :: ResponseSpaceKick -> Value
$ctoEncoding :: ResponseSpaceKick -> Encoding
toEncoding :: ResponseSpaceKick -> Encoding
$ctoJSONList :: [ResponseSpaceKick] -> Value
toJSONList :: [ResponseSpaceKick] -> Value
$ctoEncodingList :: [ResponseSpaceKick] -> Encoding
toEncodingList :: [ResponseSpaceKick] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceKick") ResponseSpaceKick
type RequestSpaceUserRole :: Type
data RequestSpaceUserRole = MkRequestSpaceUserRole
{ RequestSpaceUserRole -> IdentifierSpace
requestSpaceUserRoleSpace :: IdentifierSpace
, RequestSpaceUserRole -> IdentifierUser
requestSpaceUserRoleUser :: IdentifierUser
, RequestSpaceUserRole -> IdentifierRole
requestSpaceUserRoleRole :: IdentifierRole
}
deriving stock (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
(RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> Eq RequestSpaceUserRole
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
== :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
$c/= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
/= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
Eq, (forall x. RequestSpaceUserRole -> Rep RequestSpaceUserRole x)
-> (forall x. Rep RequestSpaceUserRole x -> RequestSpaceUserRole)
-> Generic RequestSpaceUserRole
forall x. Rep RequestSpaceUserRole x -> RequestSpaceUserRole
forall x. RequestSpaceUserRole -> Rep RequestSpaceUserRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceUserRole -> Rep RequestSpaceUserRole x
from :: forall x. RequestSpaceUserRole -> Rep RequestSpaceUserRole x
$cto :: forall x. Rep RequestSpaceUserRole x -> RequestSpaceUserRole
to :: forall x. Rep RequestSpaceUserRole x -> RequestSpaceUserRole
Generic, Eq RequestSpaceUserRole
Eq RequestSpaceUserRole =>
(RequestSpaceUserRole -> RequestSpaceUserRole -> Ordering)
-> (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> (RequestSpaceUserRole -> RequestSpaceUserRole -> Bool)
-> (RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole)
-> (RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole)
-> Ord RequestSpaceUserRole
RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
RequestSpaceUserRole -> RequestSpaceUserRole -> Ordering
RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole
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 :: RequestSpaceUserRole -> RequestSpaceUserRole -> Ordering
compare :: RequestSpaceUserRole -> RequestSpaceUserRole -> Ordering
$c< :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
< :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
$c<= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
<= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
$c> :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
> :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
$c>= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
>= :: RequestSpaceUserRole -> RequestSpaceUserRole -> Bool
$cmax :: RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole
max :: RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole
$cmin :: RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole
min :: RequestSpaceUserRole
-> RequestSpaceUserRole -> RequestSpaceUserRole
Ord, ReadPrec [RequestSpaceUserRole]
ReadPrec RequestSpaceUserRole
Int -> ReadS RequestSpaceUserRole
ReadS [RequestSpaceUserRole]
(Int -> ReadS RequestSpaceUserRole)
-> ReadS [RequestSpaceUserRole]
-> ReadPrec RequestSpaceUserRole
-> ReadPrec [RequestSpaceUserRole]
-> Read RequestSpaceUserRole
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceUserRole
readsPrec :: Int -> ReadS RequestSpaceUserRole
$creadList :: ReadS [RequestSpaceUserRole]
readList :: ReadS [RequestSpaceUserRole]
$creadPrec :: ReadPrec RequestSpaceUserRole
readPrec :: ReadPrec RequestSpaceUserRole
$creadListPrec :: ReadPrec [RequestSpaceUserRole]
readListPrec :: ReadPrec [RequestSpaceUserRole]
Read, Int -> RequestSpaceUserRole -> ShowS
[RequestSpaceUserRole] -> ShowS
RequestSpaceUserRole -> String
(Int -> RequestSpaceUserRole -> ShowS)
-> (RequestSpaceUserRole -> String)
-> ([RequestSpaceUserRole] -> ShowS)
-> Show RequestSpaceUserRole
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceUserRole -> ShowS
showsPrec :: Int -> RequestSpaceUserRole -> ShowS
$cshow :: RequestSpaceUserRole -> String
show :: RequestSpaceUserRole -> String
$cshowList :: [RequestSpaceUserRole] -> ShowS
showList :: [RequestSpaceUserRole] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceUserRole]
Value -> Parser RequestSpaceUserRole
(Value -> Parser RequestSpaceUserRole)
-> (Value -> Parser [RequestSpaceUserRole])
-> FromJSON RequestSpaceUserRole
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceUserRole
parseJSON :: Value -> Parser RequestSpaceUserRole
$cparseJSONList :: Value -> Parser [RequestSpaceUserRole]
parseJSONList :: Value -> Parser [RequestSpaceUserRole]
A.FromJSON, [RequestSpaceUserRole] -> Value
[RequestSpaceUserRole] -> Encoding
RequestSpaceUserRole -> Value
RequestSpaceUserRole -> Encoding
(RequestSpaceUserRole -> Value)
-> (RequestSpaceUserRole -> Encoding)
-> ([RequestSpaceUserRole] -> Value)
-> ([RequestSpaceUserRole] -> Encoding)
-> ToJSON RequestSpaceUserRole
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceUserRole -> Value
toJSON :: RequestSpaceUserRole -> Value
$ctoEncoding :: RequestSpaceUserRole -> Encoding
toEncoding :: RequestSpaceUserRole -> Encoding
$ctoJSONList :: [RequestSpaceUserRole] -> Value
toJSONList :: [RequestSpaceUserRole] -> Value
$ctoEncodingList :: [RequestSpaceUserRole] -> Encoding
toEncodingList :: [RequestSpaceUserRole] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceUserRole") RequestSpaceUserRole
type ResponseSpaceUserRole :: Type
newtype ResponseSpaceUserRole = MkResponseSpaceUserRole
{ ResponseSpaceUserRole -> ()
responseSpaceUserRoleUnit :: ()
}
deriving stock (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
(ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> Eq ResponseSpaceUserRole
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
== :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
$c/= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
/= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
Eq, (forall x. ResponseSpaceUserRole -> Rep ResponseSpaceUserRole x)
-> (forall x. Rep ResponseSpaceUserRole x -> ResponseSpaceUserRole)
-> Generic ResponseSpaceUserRole
forall x. Rep ResponseSpaceUserRole x -> ResponseSpaceUserRole
forall x. ResponseSpaceUserRole -> Rep ResponseSpaceUserRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceUserRole -> Rep ResponseSpaceUserRole x
from :: forall x. ResponseSpaceUserRole -> Rep ResponseSpaceUserRole x
$cto :: forall x. Rep ResponseSpaceUserRole x -> ResponseSpaceUserRole
to :: forall x. Rep ResponseSpaceUserRole x -> ResponseSpaceUserRole
Generic, Eq ResponseSpaceUserRole
Eq ResponseSpaceUserRole =>
(ResponseSpaceUserRole -> ResponseSpaceUserRole -> Ordering)
-> (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> (ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool)
-> (ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole)
-> (ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole)
-> Ord ResponseSpaceUserRole
ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
ResponseSpaceUserRole -> ResponseSpaceUserRole -> Ordering
ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole
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 :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Ordering
compare :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Ordering
$c< :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
< :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
$c<= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
<= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
$c> :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
> :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
$c>= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
>= :: ResponseSpaceUserRole -> ResponseSpaceUserRole -> Bool
$cmax :: ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole
max :: ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole
$cmin :: ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole
min :: ResponseSpaceUserRole
-> ResponseSpaceUserRole -> ResponseSpaceUserRole
Ord, ReadPrec [ResponseSpaceUserRole]
ReadPrec ResponseSpaceUserRole
Int -> ReadS ResponseSpaceUserRole
ReadS [ResponseSpaceUserRole]
(Int -> ReadS ResponseSpaceUserRole)
-> ReadS [ResponseSpaceUserRole]
-> ReadPrec ResponseSpaceUserRole
-> ReadPrec [ResponseSpaceUserRole]
-> Read ResponseSpaceUserRole
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceUserRole
readsPrec :: Int -> ReadS ResponseSpaceUserRole
$creadList :: ReadS [ResponseSpaceUserRole]
readList :: ReadS [ResponseSpaceUserRole]
$creadPrec :: ReadPrec ResponseSpaceUserRole
readPrec :: ReadPrec ResponseSpaceUserRole
$creadListPrec :: ReadPrec [ResponseSpaceUserRole]
readListPrec :: ReadPrec [ResponseSpaceUserRole]
Read, Int -> ResponseSpaceUserRole -> ShowS
[ResponseSpaceUserRole] -> ShowS
ResponseSpaceUserRole -> String
(Int -> ResponseSpaceUserRole -> ShowS)
-> (ResponseSpaceUserRole -> String)
-> ([ResponseSpaceUserRole] -> ShowS)
-> Show ResponseSpaceUserRole
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceUserRole -> ShowS
showsPrec :: Int -> ResponseSpaceUserRole -> ShowS
$cshow :: ResponseSpaceUserRole -> String
show :: ResponseSpaceUserRole -> String
$cshowList :: [ResponseSpaceUserRole] -> ShowS
showList :: [ResponseSpaceUserRole] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceUserRole]
Value -> Parser ResponseSpaceUserRole
(Value -> Parser ResponseSpaceUserRole)
-> (Value -> Parser [ResponseSpaceUserRole])
-> FromJSON ResponseSpaceUserRole
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceUserRole
parseJSON :: Value -> Parser ResponseSpaceUserRole
$cparseJSONList :: Value -> Parser [ResponseSpaceUserRole]
parseJSONList :: Value -> Parser [ResponseSpaceUserRole]
A.FromJSON, [ResponseSpaceUserRole] -> Value
[ResponseSpaceUserRole] -> Encoding
ResponseSpaceUserRole -> Value
ResponseSpaceUserRole -> Encoding
(ResponseSpaceUserRole -> Value)
-> (ResponseSpaceUserRole -> Encoding)
-> ([ResponseSpaceUserRole] -> Value)
-> ([ResponseSpaceUserRole] -> Encoding)
-> ToJSON ResponseSpaceUserRole
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceUserRole -> Value
toJSON :: ResponseSpaceUserRole -> Value
$ctoEncoding :: ResponseSpaceUserRole -> Encoding
toEncoding :: ResponseSpaceUserRole -> Encoding
$ctoJSONList :: [ResponseSpaceUserRole] -> Value
toJSONList :: [ResponseSpaceUserRole] -> Value
$ctoEncodingList :: [ResponseSpaceUserRole] -> Encoding
toEncodingList :: [ResponseSpaceUserRole] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceUserRole") ResponseSpaceUserRole
type RequestSpaceView :: Type
newtype RequestSpaceView = MkRequestSpaceView
{ RequestSpaceView -> IdentifierSpace
requestSpaceViewId :: IdentifierSpace
}
deriving stock (RequestSpaceView -> RequestSpaceView -> Bool
(RequestSpaceView -> RequestSpaceView -> Bool)
-> (RequestSpaceView -> RequestSpaceView -> Bool)
-> Eq RequestSpaceView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceView -> RequestSpaceView -> Bool
== :: RequestSpaceView -> RequestSpaceView -> Bool
$c/= :: RequestSpaceView -> RequestSpaceView -> Bool
/= :: RequestSpaceView -> RequestSpaceView -> Bool
Eq, (forall x. RequestSpaceView -> Rep RequestSpaceView x)
-> (forall x. Rep RequestSpaceView x -> RequestSpaceView)
-> Generic RequestSpaceView
forall x. Rep RequestSpaceView x -> RequestSpaceView
forall x. RequestSpaceView -> Rep RequestSpaceView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceView -> Rep RequestSpaceView x
from :: forall x. RequestSpaceView -> Rep RequestSpaceView x
$cto :: forall x. Rep RequestSpaceView x -> RequestSpaceView
to :: forall x. Rep RequestSpaceView x -> RequestSpaceView
Generic, Eq RequestSpaceView
Eq RequestSpaceView =>
(RequestSpaceView -> RequestSpaceView -> Ordering)
-> (RequestSpaceView -> RequestSpaceView -> Bool)
-> (RequestSpaceView -> RequestSpaceView -> Bool)
-> (RequestSpaceView -> RequestSpaceView -> Bool)
-> (RequestSpaceView -> RequestSpaceView -> Bool)
-> (RequestSpaceView -> RequestSpaceView -> RequestSpaceView)
-> (RequestSpaceView -> RequestSpaceView -> RequestSpaceView)
-> Ord RequestSpaceView
RequestSpaceView -> RequestSpaceView -> Bool
RequestSpaceView -> RequestSpaceView -> Ordering
RequestSpaceView -> RequestSpaceView -> RequestSpaceView
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 :: RequestSpaceView -> RequestSpaceView -> Ordering
compare :: RequestSpaceView -> RequestSpaceView -> Ordering
$c< :: RequestSpaceView -> RequestSpaceView -> Bool
< :: RequestSpaceView -> RequestSpaceView -> Bool
$c<= :: RequestSpaceView -> RequestSpaceView -> Bool
<= :: RequestSpaceView -> RequestSpaceView -> Bool
$c> :: RequestSpaceView -> RequestSpaceView -> Bool
> :: RequestSpaceView -> RequestSpaceView -> Bool
$c>= :: RequestSpaceView -> RequestSpaceView -> Bool
>= :: RequestSpaceView -> RequestSpaceView -> Bool
$cmax :: RequestSpaceView -> RequestSpaceView -> RequestSpaceView
max :: RequestSpaceView -> RequestSpaceView -> RequestSpaceView
$cmin :: RequestSpaceView -> RequestSpaceView -> RequestSpaceView
min :: RequestSpaceView -> RequestSpaceView -> RequestSpaceView
Ord, ReadPrec [RequestSpaceView]
ReadPrec RequestSpaceView
Int -> ReadS RequestSpaceView
ReadS [RequestSpaceView]
(Int -> ReadS RequestSpaceView)
-> ReadS [RequestSpaceView]
-> ReadPrec RequestSpaceView
-> ReadPrec [RequestSpaceView]
-> Read RequestSpaceView
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceView
readsPrec :: Int -> ReadS RequestSpaceView
$creadList :: ReadS [RequestSpaceView]
readList :: ReadS [RequestSpaceView]
$creadPrec :: ReadPrec RequestSpaceView
readPrec :: ReadPrec RequestSpaceView
$creadListPrec :: ReadPrec [RequestSpaceView]
readListPrec :: ReadPrec [RequestSpaceView]
Read, Int -> RequestSpaceView -> ShowS
[RequestSpaceView] -> ShowS
RequestSpaceView -> String
(Int -> RequestSpaceView -> ShowS)
-> (RequestSpaceView -> String)
-> ([RequestSpaceView] -> ShowS)
-> Show RequestSpaceView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceView -> ShowS
showsPrec :: Int -> RequestSpaceView -> ShowS
$cshow :: RequestSpaceView -> String
show :: RequestSpaceView -> String
$cshowList :: [RequestSpaceView] -> ShowS
showList :: [RequestSpaceView] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceView]
Value -> Parser RequestSpaceView
(Value -> Parser RequestSpaceView)
-> (Value -> Parser [RequestSpaceView])
-> FromJSON RequestSpaceView
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceView
parseJSON :: Value -> Parser RequestSpaceView
$cparseJSONList :: Value -> Parser [RequestSpaceView]
parseJSONList :: Value -> Parser [RequestSpaceView]
A.FromJSON, [RequestSpaceView] -> Value
[RequestSpaceView] -> Encoding
RequestSpaceView -> Value
RequestSpaceView -> Encoding
(RequestSpaceView -> Value)
-> (RequestSpaceView -> Encoding)
-> ([RequestSpaceView] -> Value)
-> ([RequestSpaceView] -> Encoding)
-> ToJSON RequestSpaceView
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceView -> Value
toJSON :: RequestSpaceView -> Value
$ctoEncoding :: RequestSpaceView -> Encoding
toEncoding :: RequestSpaceView -> Encoding
$ctoJSONList :: [RequestSpaceView] -> Value
toJSONList :: [RequestSpaceView] -> Value
$ctoEncodingList :: [RequestSpaceView] -> Encoding
toEncodingList :: [RequestSpaceView] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceView") RequestSpaceView
type ResponseSpaceView :: Type
data ResponseSpaceView = MkResponseSpaceView
{ ResponseSpaceView -> IdentifierSpace
responseSpaceViewId :: IdentifierSpace
, ResponseSpaceView -> NameSpace
responseSpaceViewName :: NameSpace
, ResponseSpaceView -> TZLabel
responseSpaceViewTimezone :: T.TZLabel
, ResponseSpaceView -> VisibilitySpace
responseSpaceViewVisibility :: VisibilitySpace
, ResponseSpaceView -> IdentifierUser
responseSpaceViewOwner :: IdentifierUser
, ResponseSpaceView -> Set Role
responseSpaceViewRoles :: S.Set Role
, ResponseSpaceView -> Set SpaceUser
responseSpaceViewUsers :: S.Set SpaceUser
, ResponseSpaceView -> Maybe IdentifierRole
responseSpaceViewYourRole :: Maybe IdentifierRole
}
deriving stock (ResponseSpaceView -> ResponseSpaceView -> Bool
(ResponseSpaceView -> ResponseSpaceView -> Bool)
-> (ResponseSpaceView -> ResponseSpaceView -> Bool)
-> Eq ResponseSpaceView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceView -> ResponseSpaceView -> Bool
== :: ResponseSpaceView -> ResponseSpaceView -> Bool
$c/= :: ResponseSpaceView -> ResponseSpaceView -> Bool
/= :: ResponseSpaceView -> ResponseSpaceView -> Bool
Eq, (forall x. ResponseSpaceView -> Rep ResponseSpaceView x)
-> (forall x. Rep ResponseSpaceView x -> ResponseSpaceView)
-> Generic ResponseSpaceView
forall x. Rep ResponseSpaceView x -> ResponseSpaceView
forall x. ResponseSpaceView -> Rep ResponseSpaceView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceView -> Rep ResponseSpaceView x
from :: forall x. ResponseSpaceView -> Rep ResponseSpaceView x
$cto :: forall x. Rep ResponseSpaceView x -> ResponseSpaceView
to :: forall x. Rep ResponseSpaceView x -> ResponseSpaceView
Generic, Eq ResponseSpaceView
Eq ResponseSpaceView =>
(ResponseSpaceView -> ResponseSpaceView -> Ordering)
-> (ResponseSpaceView -> ResponseSpaceView -> Bool)
-> (ResponseSpaceView -> ResponseSpaceView -> Bool)
-> (ResponseSpaceView -> ResponseSpaceView -> Bool)
-> (ResponseSpaceView -> ResponseSpaceView -> Bool)
-> (ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView)
-> (ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView)
-> Ord ResponseSpaceView
ResponseSpaceView -> ResponseSpaceView -> Bool
ResponseSpaceView -> ResponseSpaceView -> Ordering
ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView
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 :: ResponseSpaceView -> ResponseSpaceView -> Ordering
compare :: ResponseSpaceView -> ResponseSpaceView -> Ordering
$c< :: ResponseSpaceView -> ResponseSpaceView -> Bool
< :: ResponseSpaceView -> ResponseSpaceView -> Bool
$c<= :: ResponseSpaceView -> ResponseSpaceView -> Bool
<= :: ResponseSpaceView -> ResponseSpaceView -> Bool
$c> :: ResponseSpaceView -> ResponseSpaceView -> Bool
> :: ResponseSpaceView -> ResponseSpaceView -> Bool
$c>= :: ResponseSpaceView -> ResponseSpaceView -> Bool
>= :: ResponseSpaceView -> ResponseSpaceView -> Bool
$cmax :: ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView
max :: ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView
$cmin :: ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView
min :: ResponseSpaceView -> ResponseSpaceView -> ResponseSpaceView
Ord, ReadPrec [ResponseSpaceView]
ReadPrec ResponseSpaceView
Int -> ReadS ResponseSpaceView
ReadS [ResponseSpaceView]
(Int -> ReadS ResponseSpaceView)
-> ReadS [ResponseSpaceView]
-> ReadPrec ResponseSpaceView
-> ReadPrec [ResponseSpaceView]
-> Read ResponseSpaceView
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceView
readsPrec :: Int -> ReadS ResponseSpaceView
$creadList :: ReadS [ResponseSpaceView]
readList :: ReadS [ResponseSpaceView]
$creadPrec :: ReadPrec ResponseSpaceView
readPrec :: ReadPrec ResponseSpaceView
$creadListPrec :: ReadPrec [ResponseSpaceView]
readListPrec :: ReadPrec [ResponseSpaceView]
Read, Int -> ResponseSpaceView -> ShowS
[ResponseSpaceView] -> ShowS
ResponseSpaceView -> String
(Int -> ResponseSpaceView -> ShowS)
-> (ResponseSpaceView -> String)
-> ([ResponseSpaceView] -> ShowS)
-> Show ResponseSpaceView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceView -> ShowS
showsPrec :: Int -> ResponseSpaceView -> ShowS
$cshow :: ResponseSpaceView -> String
show :: ResponseSpaceView -> String
$cshowList :: [ResponseSpaceView] -> ShowS
showList :: [ResponseSpaceView] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceView]
Value -> Parser ResponseSpaceView
(Value -> Parser ResponseSpaceView)
-> (Value -> Parser [ResponseSpaceView])
-> FromJSON ResponseSpaceView
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceView
parseJSON :: Value -> Parser ResponseSpaceView
$cparseJSONList :: Value -> Parser [ResponseSpaceView]
parseJSONList :: Value -> Parser [ResponseSpaceView]
A.FromJSON, [ResponseSpaceView] -> Value
[ResponseSpaceView] -> Encoding
ResponseSpaceView -> Value
ResponseSpaceView -> Encoding
(ResponseSpaceView -> Value)
-> (ResponseSpaceView -> Encoding)
-> ([ResponseSpaceView] -> Value)
-> ([ResponseSpaceView] -> Encoding)
-> ToJSON ResponseSpaceView
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceView -> Value
toJSON :: ResponseSpaceView -> Value
$ctoEncoding :: ResponseSpaceView -> Encoding
toEncoding :: ResponseSpaceView -> Encoding
$ctoJSONList :: [ResponseSpaceView] -> Value
toJSONList :: [ResponseSpaceView] -> Value
$ctoEncodingList :: [ResponseSpaceView] -> Encoding
toEncodingList :: [ResponseSpaceView] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceView") ResponseSpaceView
type ResponseSpaceView403 :: Type
data ResponseSpaceView403 = MkResponseSpaceView403
{ ResponseSpaceView403 -> IdentifierSpace
responseSpaceView403Id :: IdentifierSpace
, ResponseSpaceView403 -> NameSpace
responseSpaceView403Name :: NameSpace
, ResponseSpaceView403 -> TZLabel
responseSpaceView403Timezone :: T.TZLabel
, ResponseSpaceView403 -> VisibilitySpace
responseSpaceView403Visibility :: VisibilitySpace
, ResponseSpaceView403 -> Set Role
responseSpaceView403Roles :: S.Set Role
, ResponseSpaceView403 -> Maybe IdentifierRole
responseSpaceView403YourRole :: Maybe IdentifierRole
}
deriving stock (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
(ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> Eq ResponseSpaceView403
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
== :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
$c/= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
/= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
Eq, (forall x. ResponseSpaceView403 -> Rep ResponseSpaceView403 x)
-> (forall x. Rep ResponseSpaceView403 x -> ResponseSpaceView403)
-> Generic ResponseSpaceView403
forall x. Rep ResponseSpaceView403 x -> ResponseSpaceView403
forall x. ResponseSpaceView403 -> Rep ResponseSpaceView403 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceView403 -> Rep ResponseSpaceView403 x
from :: forall x. ResponseSpaceView403 -> Rep ResponseSpaceView403 x
$cto :: forall x. Rep ResponseSpaceView403 x -> ResponseSpaceView403
to :: forall x. Rep ResponseSpaceView403 x -> ResponseSpaceView403
Generic, Eq ResponseSpaceView403
Eq ResponseSpaceView403 =>
(ResponseSpaceView403 -> ResponseSpaceView403 -> Ordering)
-> (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> (ResponseSpaceView403 -> ResponseSpaceView403 -> Bool)
-> (ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403)
-> (ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403)
-> Ord ResponseSpaceView403
ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
ResponseSpaceView403 -> ResponseSpaceView403 -> Ordering
ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403
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 :: ResponseSpaceView403 -> ResponseSpaceView403 -> Ordering
compare :: ResponseSpaceView403 -> ResponseSpaceView403 -> Ordering
$c< :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
< :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
$c<= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
<= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
$c> :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
> :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
$c>= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
>= :: ResponseSpaceView403 -> ResponseSpaceView403 -> Bool
$cmax :: ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403
max :: ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403
$cmin :: ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403
min :: ResponseSpaceView403
-> ResponseSpaceView403 -> ResponseSpaceView403
Ord, ReadPrec [ResponseSpaceView403]
ReadPrec ResponseSpaceView403
Int -> ReadS ResponseSpaceView403
ReadS [ResponseSpaceView403]
(Int -> ReadS ResponseSpaceView403)
-> ReadS [ResponseSpaceView403]
-> ReadPrec ResponseSpaceView403
-> ReadPrec [ResponseSpaceView403]
-> Read ResponseSpaceView403
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceView403
readsPrec :: Int -> ReadS ResponseSpaceView403
$creadList :: ReadS [ResponseSpaceView403]
readList :: ReadS [ResponseSpaceView403]
$creadPrec :: ReadPrec ResponseSpaceView403
readPrec :: ReadPrec ResponseSpaceView403
$creadListPrec :: ReadPrec [ResponseSpaceView403]
readListPrec :: ReadPrec [ResponseSpaceView403]
Read, Int -> ResponseSpaceView403 -> ShowS
[ResponseSpaceView403] -> ShowS
ResponseSpaceView403 -> String
(Int -> ResponseSpaceView403 -> ShowS)
-> (ResponseSpaceView403 -> String)
-> ([ResponseSpaceView403] -> ShowS)
-> Show ResponseSpaceView403
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceView403 -> ShowS
showsPrec :: Int -> ResponseSpaceView403 -> ShowS
$cshow :: ResponseSpaceView403 -> String
show :: ResponseSpaceView403 -> String
$cshowList :: [ResponseSpaceView403] -> ShowS
showList :: [ResponseSpaceView403] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceView403]
Value -> Parser ResponseSpaceView403
(Value -> Parser ResponseSpaceView403)
-> (Value -> Parser [ResponseSpaceView403])
-> FromJSON ResponseSpaceView403
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceView403
parseJSON :: Value -> Parser ResponseSpaceView403
$cparseJSONList :: Value -> Parser [ResponseSpaceView403]
parseJSONList :: Value -> Parser [ResponseSpaceView403]
A.FromJSON, [ResponseSpaceView403] -> Value
[ResponseSpaceView403] -> Encoding
ResponseSpaceView403 -> Value
ResponseSpaceView403 -> Encoding
(ResponseSpaceView403 -> Value)
-> (ResponseSpaceView403 -> Encoding)
-> ([ResponseSpaceView403] -> Value)
-> ([ResponseSpaceView403] -> Encoding)
-> ToJSON ResponseSpaceView403
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceView403 -> Value
toJSON :: ResponseSpaceView403 -> Value
$ctoEncoding :: ResponseSpaceView403 -> Encoding
toEncoding :: ResponseSpaceView403 -> Encoding
$ctoJSONList :: [ResponseSpaceView403] -> Value
toJSONList :: [ResponseSpaceView403] -> Value
$ctoEncodingList :: [ResponseSpaceView403] -> Encoding
toEncodingList :: [ResponseSpaceView403] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceView403") ResponseSpaceView403
type RequestSpaceList :: Type
data RequestSpaceList = MkRequestSpaceList
{ RequestSpaceList -> OrderByCategories SpaceOrderCategory
requestSpaceListOrder :: OrderByCategories SpaceOrderCategory
, RequestSpaceList -> Maybe Bool
requestSpaceListMember :: Maybe Bool
}
deriving stock (RequestSpaceList -> RequestSpaceList -> Bool
(RequestSpaceList -> RequestSpaceList -> Bool)
-> (RequestSpaceList -> RequestSpaceList -> Bool)
-> Eq RequestSpaceList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestSpaceList -> RequestSpaceList -> Bool
== :: RequestSpaceList -> RequestSpaceList -> Bool
$c/= :: RequestSpaceList -> RequestSpaceList -> Bool
/= :: RequestSpaceList -> RequestSpaceList -> Bool
Eq, (forall x. RequestSpaceList -> Rep RequestSpaceList x)
-> (forall x. Rep RequestSpaceList x -> RequestSpaceList)
-> Generic RequestSpaceList
forall x. Rep RequestSpaceList x -> RequestSpaceList
forall x. RequestSpaceList -> Rep RequestSpaceList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestSpaceList -> Rep RequestSpaceList x
from :: forall x. RequestSpaceList -> Rep RequestSpaceList x
$cto :: forall x. Rep RequestSpaceList x -> RequestSpaceList
to :: forall x. Rep RequestSpaceList x -> RequestSpaceList
Generic, Eq RequestSpaceList
Eq RequestSpaceList =>
(RequestSpaceList -> RequestSpaceList -> Ordering)
-> (RequestSpaceList -> RequestSpaceList -> Bool)
-> (RequestSpaceList -> RequestSpaceList -> Bool)
-> (RequestSpaceList -> RequestSpaceList -> Bool)
-> (RequestSpaceList -> RequestSpaceList -> Bool)
-> (RequestSpaceList -> RequestSpaceList -> RequestSpaceList)
-> (RequestSpaceList -> RequestSpaceList -> RequestSpaceList)
-> Ord RequestSpaceList
RequestSpaceList -> RequestSpaceList -> Bool
RequestSpaceList -> RequestSpaceList -> Ordering
RequestSpaceList -> RequestSpaceList -> RequestSpaceList
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 :: RequestSpaceList -> RequestSpaceList -> Ordering
compare :: RequestSpaceList -> RequestSpaceList -> Ordering
$c< :: RequestSpaceList -> RequestSpaceList -> Bool
< :: RequestSpaceList -> RequestSpaceList -> Bool
$c<= :: RequestSpaceList -> RequestSpaceList -> Bool
<= :: RequestSpaceList -> RequestSpaceList -> Bool
$c> :: RequestSpaceList -> RequestSpaceList -> Bool
> :: RequestSpaceList -> RequestSpaceList -> Bool
$c>= :: RequestSpaceList -> RequestSpaceList -> Bool
>= :: RequestSpaceList -> RequestSpaceList -> Bool
$cmax :: RequestSpaceList -> RequestSpaceList -> RequestSpaceList
max :: RequestSpaceList -> RequestSpaceList -> RequestSpaceList
$cmin :: RequestSpaceList -> RequestSpaceList -> RequestSpaceList
min :: RequestSpaceList -> RequestSpaceList -> RequestSpaceList
Ord, ReadPrec [RequestSpaceList]
ReadPrec RequestSpaceList
Int -> ReadS RequestSpaceList
ReadS [RequestSpaceList]
(Int -> ReadS RequestSpaceList)
-> ReadS [RequestSpaceList]
-> ReadPrec RequestSpaceList
-> ReadPrec [RequestSpaceList]
-> Read RequestSpaceList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestSpaceList
readsPrec :: Int -> ReadS RequestSpaceList
$creadList :: ReadS [RequestSpaceList]
readList :: ReadS [RequestSpaceList]
$creadPrec :: ReadPrec RequestSpaceList
readPrec :: ReadPrec RequestSpaceList
$creadListPrec :: ReadPrec [RequestSpaceList]
readListPrec :: ReadPrec [RequestSpaceList]
Read, Int -> RequestSpaceList -> ShowS
[RequestSpaceList] -> ShowS
RequestSpaceList -> String
(Int -> RequestSpaceList -> ShowS)
-> (RequestSpaceList -> String)
-> ([RequestSpaceList] -> ShowS)
-> Show RequestSpaceList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestSpaceList -> ShowS
showsPrec :: Int -> RequestSpaceList -> ShowS
$cshow :: RequestSpaceList -> String
show :: RequestSpaceList -> String
$cshowList :: [RequestSpaceList] -> ShowS
showList :: [RequestSpaceList] -> ShowS
Show)
deriving
(Value -> Parser [RequestSpaceList]
Value -> Parser RequestSpaceList
(Value -> Parser RequestSpaceList)
-> (Value -> Parser [RequestSpaceList])
-> FromJSON RequestSpaceList
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestSpaceList
parseJSON :: Value -> Parser RequestSpaceList
$cparseJSONList :: Value -> Parser [RequestSpaceList]
parseJSONList :: Value -> Parser [RequestSpaceList]
A.FromJSON, [RequestSpaceList] -> Value
[RequestSpaceList] -> Encoding
RequestSpaceList -> Value
RequestSpaceList -> Encoding
(RequestSpaceList -> Value)
-> (RequestSpaceList -> Encoding)
-> ([RequestSpaceList] -> Value)
-> ([RequestSpaceList] -> Encoding)
-> ToJSON RequestSpaceList
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestSpaceList -> Value
toJSON :: RequestSpaceList -> Value
$ctoEncoding :: RequestSpaceList -> Encoding
toEncoding :: RequestSpaceList -> Encoding
$ctoJSONList :: [RequestSpaceList] -> Value
toJSONList :: [RequestSpaceList] -> Value
$ctoEncodingList :: [RequestSpaceList] -> Encoding
toEncodingList :: [RequestSpaceList] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestSpaceList") RequestSpaceList
type ResponseSpaceList :: Type
newtype ResponseSpaceList = MkResponseSpaceList
{ ResponseSpaceList -> [SpaceListSpace]
responseSpaceListSpaces :: [SpaceListSpace]
}
deriving stock (ResponseSpaceList -> ResponseSpaceList -> Bool
(ResponseSpaceList -> ResponseSpaceList -> Bool)
-> (ResponseSpaceList -> ResponseSpaceList -> Bool)
-> Eq ResponseSpaceList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseSpaceList -> ResponseSpaceList -> Bool
== :: ResponseSpaceList -> ResponseSpaceList -> Bool
$c/= :: ResponseSpaceList -> ResponseSpaceList -> Bool
/= :: ResponseSpaceList -> ResponseSpaceList -> Bool
Eq, (forall x. ResponseSpaceList -> Rep ResponseSpaceList x)
-> (forall x. Rep ResponseSpaceList x -> ResponseSpaceList)
-> Generic ResponseSpaceList
forall x. Rep ResponseSpaceList x -> ResponseSpaceList
forall x. ResponseSpaceList -> Rep ResponseSpaceList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseSpaceList -> Rep ResponseSpaceList x
from :: forall x. ResponseSpaceList -> Rep ResponseSpaceList x
$cto :: forall x. Rep ResponseSpaceList x -> ResponseSpaceList
to :: forall x. Rep ResponseSpaceList x -> ResponseSpaceList
Generic, Eq ResponseSpaceList
Eq ResponseSpaceList =>
(ResponseSpaceList -> ResponseSpaceList -> Ordering)
-> (ResponseSpaceList -> ResponseSpaceList -> Bool)
-> (ResponseSpaceList -> ResponseSpaceList -> Bool)
-> (ResponseSpaceList -> ResponseSpaceList -> Bool)
-> (ResponseSpaceList -> ResponseSpaceList -> Bool)
-> (ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList)
-> (ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList)
-> Ord ResponseSpaceList
ResponseSpaceList -> ResponseSpaceList -> Bool
ResponseSpaceList -> ResponseSpaceList -> Ordering
ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList
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 :: ResponseSpaceList -> ResponseSpaceList -> Ordering
compare :: ResponseSpaceList -> ResponseSpaceList -> Ordering
$c< :: ResponseSpaceList -> ResponseSpaceList -> Bool
< :: ResponseSpaceList -> ResponseSpaceList -> Bool
$c<= :: ResponseSpaceList -> ResponseSpaceList -> Bool
<= :: ResponseSpaceList -> ResponseSpaceList -> Bool
$c> :: ResponseSpaceList -> ResponseSpaceList -> Bool
> :: ResponseSpaceList -> ResponseSpaceList -> Bool
$c>= :: ResponseSpaceList -> ResponseSpaceList -> Bool
>= :: ResponseSpaceList -> ResponseSpaceList -> Bool
$cmax :: ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList
max :: ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList
$cmin :: ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList
min :: ResponseSpaceList -> ResponseSpaceList -> ResponseSpaceList
Ord, ReadPrec [ResponseSpaceList]
ReadPrec ResponseSpaceList
Int -> ReadS ResponseSpaceList
ReadS [ResponseSpaceList]
(Int -> ReadS ResponseSpaceList)
-> ReadS [ResponseSpaceList]
-> ReadPrec ResponseSpaceList
-> ReadPrec [ResponseSpaceList]
-> Read ResponseSpaceList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseSpaceList
readsPrec :: Int -> ReadS ResponseSpaceList
$creadList :: ReadS [ResponseSpaceList]
readList :: ReadS [ResponseSpaceList]
$creadPrec :: ReadPrec ResponseSpaceList
readPrec :: ReadPrec ResponseSpaceList
$creadListPrec :: ReadPrec [ResponseSpaceList]
readListPrec :: ReadPrec [ResponseSpaceList]
Read, Int -> ResponseSpaceList -> ShowS
[ResponseSpaceList] -> ShowS
ResponseSpaceList -> String
(Int -> ResponseSpaceList -> ShowS)
-> (ResponseSpaceList -> String)
-> ([ResponseSpaceList] -> ShowS)
-> Show ResponseSpaceList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseSpaceList -> ShowS
showsPrec :: Int -> ResponseSpaceList -> ShowS
$cshow :: ResponseSpaceList -> String
show :: ResponseSpaceList -> String
$cshowList :: [ResponseSpaceList] -> ShowS
showList :: [ResponseSpaceList] -> ShowS
Show)
deriving
(Value -> Parser [ResponseSpaceList]
Value -> Parser ResponseSpaceList
(Value -> Parser ResponseSpaceList)
-> (Value -> Parser [ResponseSpaceList])
-> FromJSON ResponseSpaceList
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseSpaceList
parseJSON :: Value -> Parser ResponseSpaceList
$cparseJSONList :: Value -> Parser [ResponseSpaceList]
parseJSONList :: Value -> Parser [ResponseSpaceList]
A.FromJSON, [ResponseSpaceList] -> Value
[ResponseSpaceList] -> Encoding
ResponseSpaceList -> Value
ResponseSpaceList -> Encoding
(ResponseSpaceList -> Value)
-> (ResponseSpaceList -> Encoding)
-> ([ResponseSpaceList] -> Value)
-> ([ResponseSpaceList] -> Encoding)
-> ToJSON ResponseSpaceList
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseSpaceList -> Value
toJSON :: ResponseSpaceList -> Value
$ctoEncoding :: ResponseSpaceList -> Encoding
toEncoding :: ResponseSpaceList -> Encoding
$ctoJSONList :: [ResponseSpaceList] -> Value
toJSONList :: [ResponseSpaceList] -> Value
$ctoEncodingList :: [ResponseSpaceList] -> Encoding
toEncodingList :: [ResponseSpaceList] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseSpaceList") ResponseSpaceList
type SpaceListSpace :: Type
data SpaceListSpace = MkSpaceListSpace
{ SpaceListSpace -> IdentifierSpace
spaceListSpaceId :: IdentifierSpace
, SpaceListSpace -> NameSpace
spaceListSpaceName :: NameSpace
, SpaceListSpace -> TZLabel
spaceListSpaceTimezone :: T.TZLabel
, SpaceListSpace -> IdentifierUser
spaceListSpaceOwner :: IdentifierUser
, SpaceListSpace -> Natural
spaceListSpaceUsers :: Natural
, SpaceListSpace -> Natural
spaceListSpaceDesks :: Natural
}
deriving stock (SpaceListSpace -> SpaceListSpace -> Bool
(SpaceListSpace -> SpaceListSpace -> Bool)
-> (SpaceListSpace -> SpaceListSpace -> Bool) -> Eq SpaceListSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpaceListSpace -> SpaceListSpace -> Bool
== :: SpaceListSpace -> SpaceListSpace -> Bool
$c/= :: SpaceListSpace -> SpaceListSpace -> Bool
/= :: SpaceListSpace -> SpaceListSpace -> Bool
Eq, (forall x. SpaceListSpace -> Rep SpaceListSpace x)
-> (forall x. Rep SpaceListSpace x -> SpaceListSpace)
-> Generic SpaceListSpace
forall x. Rep SpaceListSpace x -> SpaceListSpace
forall x. SpaceListSpace -> Rep SpaceListSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SpaceListSpace -> Rep SpaceListSpace x
from :: forall x. SpaceListSpace -> Rep SpaceListSpace x
$cto :: forall x. Rep SpaceListSpace x -> SpaceListSpace
to :: forall x. Rep SpaceListSpace x -> SpaceListSpace
Generic, Eq SpaceListSpace
Eq SpaceListSpace =>
(SpaceListSpace -> SpaceListSpace -> Ordering)
-> (SpaceListSpace -> SpaceListSpace -> Bool)
-> (SpaceListSpace -> SpaceListSpace -> Bool)
-> (SpaceListSpace -> SpaceListSpace -> Bool)
-> (SpaceListSpace -> SpaceListSpace -> Bool)
-> (SpaceListSpace -> SpaceListSpace -> SpaceListSpace)
-> (SpaceListSpace -> SpaceListSpace -> SpaceListSpace)
-> Ord SpaceListSpace
SpaceListSpace -> SpaceListSpace -> Bool
SpaceListSpace -> SpaceListSpace -> Ordering
SpaceListSpace -> SpaceListSpace -> SpaceListSpace
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 :: SpaceListSpace -> SpaceListSpace -> Ordering
compare :: SpaceListSpace -> SpaceListSpace -> Ordering
$c< :: SpaceListSpace -> SpaceListSpace -> Bool
< :: SpaceListSpace -> SpaceListSpace -> Bool
$c<= :: SpaceListSpace -> SpaceListSpace -> Bool
<= :: SpaceListSpace -> SpaceListSpace -> Bool
$c> :: SpaceListSpace -> SpaceListSpace -> Bool
> :: SpaceListSpace -> SpaceListSpace -> Bool
$c>= :: SpaceListSpace -> SpaceListSpace -> Bool
>= :: SpaceListSpace -> SpaceListSpace -> Bool
$cmax :: SpaceListSpace -> SpaceListSpace -> SpaceListSpace
max :: SpaceListSpace -> SpaceListSpace -> SpaceListSpace
$cmin :: SpaceListSpace -> SpaceListSpace -> SpaceListSpace
min :: SpaceListSpace -> SpaceListSpace -> SpaceListSpace
Ord, ReadPrec [SpaceListSpace]
ReadPrec SpaceListSpace
Int -> ReadS SpaceListSpace
ReadS [SpaceListSpace]
(Int -> ReadS SpaceListSpace)
-> ReadS [SpaceListSpace]
-> ReadPrec SpaceListSpace
-> ReadPrec [SpaceListSpace]
-> Read SpaceListSpace
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SpaceListSpace
readsPrec :: Int -> ReadS SpaceListSpace
$creadList :: ReadS [SpaceListSpace]
readList :: ReadS [SpaceListSpace]
$creadPrec :: ReadPrec SpaceListSpace
readPrec :: ReadPrec SpaceListSpace
$creadListPrec :: ReadPrec [SpaceListSpace]
readListPrec :: ReadPrec [SpaceListSpace]
Read, Int -> SpaceListSpace -> ShowS
[SpaceListSpace] -> ShowS
SpaceListSpace -> String
(Int -> SpaceListSpace -> ShowS)
-> (SpaceListSpace -> String)
-> ([SpaceListSpace] -> ShowS)
-> Show SpaceListSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpaceListSpace -> ShowS
showsPrec :: Int -> SpaceListSpace -> ShowS
$cshow :: SpaceListSpace -> String
show :: SpaceListSpace -> String
$cshowList :: [SpaceListSpace] -> ShowS
showList :: [SpaceListSpace] -> ShowS
Show)
deriving
(Value -> Parser [SpaceListSpace]
Value -> Parser SpaceListSpace
(Value -> Parser SpaceListSpace)
-> (Value -> Parser [SpaceListSpace]) -> FromJSON SpaceListSpace
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser SpaceListSpace
parseJSON :: Value -> Parser SpaceListSpace
$cparseJSONList :: Value -> Parser [SpaceListSpace]
parseJSONList :: Value -> Parser [SpaceListSpace]
A.FromJSON, [SpaceListSpace] -> Value
[SpaceListSpace] -> Encoding
SpaceListSpace -> Value
SpaceListSpace -> Encoding
(SpaceListSpace -> Value)
-> (SpaceListSpace -> Encoding)
-> ([SpaceListSpace] -> Value)
-> ([SpaceListSpace] -> Encoding)
-> ToJSON SpaceListSpace
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: SpaceListSpace -> Value
toJSON :: SpaceListSpace -> Value
$ctoEncoding :: SpaceListSpace -> Encoding
toEncoding :: SpaceListSpace -> Encoding
$ctoJSONList :: [SpaceListSpace] -> Value
toJSONList :: [SpaceListSpace] -> Value
$ctoEncodingList :: [SpaceListSpace] -> Encoding
toEncodingList :: [SpaceListSpace] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "Mk" "spaceListSpace") SpaceListSpace
type RequestRoleCreate :: Type
data RequestRoleCreate = MkRequestRoleCreate
{ RequestRoleCreate -> IdentifierSpace
requestRoleCreateSpace :: IdentifierSpace
, RequestRoleCreate -> NameRole
requestRoleCreateName :: NameRole
, RequestRoleCreate -> AccessibilityRole
requestRoleCreateAccessibility :: AccessibilityRole
, RequestRoleCreate -> Maybe Text
requestRoleCreatePassword :: Maybe T.Text
, RequestRoleCreate -> Set Permission
requestRoleCreatePermissions :: S.Set Permission
}
deriving stock (RequestRoleCreate -> RequestRoleCreate -> Bool
(RequestRoleCreate -> RequestRoleCreate -> Bool)
-> (RequestRoleCreate -> RequestRoleCreate -> Bool)
-> Eq RequestRoleCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestRoleCreate -> RequestRoleCreate -> Bool
== :: RequestRoleCreate -> RequestRoleCreate -> Bool
$c/= :: RequestRoleCreate -> RequestRoleCreate -> Bool
/= :: RequestRoleCreate -> RequestRoleCreate -> Bool
Eq, (forall x. RequestRoleCreate -> Rep RequestRoleCreate x)
-> (forall x. Rep RequestRoleCreate x -> RequestRoleCreate)
-> Generic RequestRoleCreate
forall x. Rep RequestRoleCreate x -> RequestRoleCreate
forall x. RequestRoleCreate -> Rep RequestRoleCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestRoleCreate -> Rep RequestRoleCreate x
from :: forall x. RequestRoleCreate -> Rep RequestRoleCreate x
$cto :: forall x. Rep RequestRoleCreate x -> RequestRoleCreate
to :: forall x. Rep RequestRoleCreate x -> RequestRoleCreate
Generic, Eq RequestRoleCreate
Eq RequestRoleCreate =>
(RequestRoleCreate -> RequestRoleCreate -> Ordering)
-> (RequestRoleCreate -> RequestRoleCreate -> Bool)
-> (RequestRoleCreate -> RequestRoleCreate -> Bool)
-> (RequestRoleCreate -> RequestRoleCreate -> Bool)
-> (RequestRoleCreate -> RequestRoleCreate -> Bool)
-> (RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate)
-> (RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate)
-> Ord RequestRoleCreate
RequestRoleCreate -> RequestRoleCreate -> Bool
RequestRoleCreate -> RequestRoleCreate -> Ordering
RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate
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 :: RequestRoleCreate -> RequestRoleCreate -> Ordering
compare :: RequestRoleCreate -> RequestRoleCreate -> Ordering
$c< :: RequestRoleCreate -> RequestRoleCreate -> Bool
< :: RequestRoleCreate -> RequestRoleCreate -> Bool
$c<= :: RequestRoleCreate -> RequestRoleCreate -> Bool
<= :: RequestRoleCreate -> RequestRoleCreate -> Bool
$c> :: RequestRoleCreate -> RequestRoleCreate -> Bool
> :: RequestRoleCreate -> RequestRoleCreate -> Bool
$c>= :: RequestRoleCreate -> RequestRoleCreate -> Bool
>= :: RequestRoleCreate -> RequestRoleCreate -> Bool
$cmax :: RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate
max :: RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate
$cmin :: RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate
min :: RequestRoleCreate -> RequestRoleCreate -> RequestRoleCreate
Ord, ReadPrec [RequestRoleCreate]
ReadPrec RequestRoleCreate
Int -> ReadS RequestRoleCreate
ReadS [RequestRoleCreate]
(Int -> ReadS RequestRoleCreate)
-> ReadS [RequestRoleCreate]
-> ReadPrec RequestRoleCreate
-> ReadPrec [RequestRoleCreate]
-> Read RequestRoleCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestRoleCreate
readsPrec :: Int -> ReadS RequestRoleCreate
$creadList :: ReadS [RequestRoleCreate]
readList :: ReadS [RequestRoleCreate]
$creadPrec :: ReadPrec RequestRoleCreate
readPrec :: ReadPrec RequestRoleCreate
$creadListPrec :: ReadPrec [RequestRoleCreate]
readListPrec :: ReadPrec [RequestRoleCreate]
Read, Int -> RequestRoleCreate -> ShowS
[RequestRoleCreate] -> ShowS
RequestRoleCreate -> String
(Int -> RequestRoleCreate -> ShowS)
-> (RequestRoleCreate -> String)
-> ([RequestRoleCreate] -> ShowS)
-> Show RequestRoleCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestRoleCreate -> ShowS
showsPrec :: Int -> RequestRoleCreate -> ShowS
$cshow :: RequestRoleCreate -> String
show :: RequestRoleCreate -> String
$cshowList :: [RequestRoleCreate] -> ShowS
showList :: [RequestRoleCreate] -> ShowS
Show)
deriving
(Value -> Parser [RequestRoleCreate]
Value -> Parser RequestRoleCreate
(Value -> Parser RequestRoleCreate)
-> (Value -> Parser [RequestRoleCreate])
-> FromJSON RequestRoleCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestRoleCreate
parseJSON :: Value -> Parser RequestRoleCreate
$cparseJSONList :: Value -> Parser [RequestRoleCreate]
parseJSONList :: Value -> Parser [RequestRoleCreate]
A.FromJSON, [RequestRoleCreate] -> Value
[RequestRoleCreate] -> Encoding
RequestRoleCreate -> Value
RequestRoleCreate -> Encoding
(RequestRoleCreate -> Value)
-> (RequestRoleCreate -> Encoding)
-> ([RequestRoleCreate] -> Value)
-> ([RequestRoleCreate] -> Encoding)
-> ToJSON RequestRoleCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestRoleCreate -> Value
toJSON :: RequestRoleCreate -> Value
$ctoEncoding :: RequestRoleCreate -> Encoding
toEncoding :: RequestRoleCreate -> Encoding
$ctoJSONList :: [RequestRoleCreate] -> Value
toJSONList :: [RequestRoleCreate] -> Value
$ctoEncodingList :: [RequestRoleCreate] -> Encoding
toEncodingList :: [RequestRoleCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestRoleCreate") RequestRoleCreate
type ResponseRoleCreate :: Type
newtype ResponseRoleCreate = MkResponseRoleCreate
{ ResponseRoleCreate -> IdentifierRole
responseRoleCreateId :: IdentifierRole
}
deriving stock (ResponseRoleCreate -> ResponseRoleCreate -> Bool
(ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> (ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> Eq ResponseRoleCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
== :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
$c/= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
/= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
Eq, (forall x. ResponseRoleCreate -> Rep ResponseRoleCreate x)
-> (forall x. Rep ResponseRoleCreate x -> ResponseRoleCreate)
-> Generic ResponseRoleCreate
forall x. Rep ResponseRoleCreate x -> ResponseRoleCreate
forall x. ResponseRoleCreate -> Rep ResponseRoleCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseRoleCreate -> Rep ResponseRoleCreate x
from :: forall x. ResponseRoleCreate -> Rep ResponseRoleCreate x
$cto :: forall x. Rep ResponseRoleCreate x -> ResponseRoleCreate
to :: forall x. Rep ResponseRoleCreate x -> ResponseRoleCreate
Generic, Eq ResponseRoleCreate
Eq ResponseRoleCreate =>
(ResponseRoleCreate -> ResponseRoleCreate -> Ordering)
-> (ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> (ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> (ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> (ResponseRoleCreate -> ResponseRoleCreate -> Bool)
-> (ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate)
-> (ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate)
-> Ord ResponseRoleCreate
ResponseRoleCreate -> ResponseRoleCreate -> Bool
ResponseRoleCreate -> ResponseRoleCreate -> Ordering
ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate
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 :: ResponseRoleCreate -> ResponseRoleCreate -> Ordering
compare :: ResponseRoleCreate -> ResponseRoleCreate -> Ordering
$c< :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
< :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
$c<= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
<= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
$c> :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
> :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
$c>= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
>= :: ResponseRoleCreate -> ResponseRoleCreate -> Bool
$cmax :: ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate
max :: ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate
$cmin :: ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate
min :: ResponseRoleCreate -> ResponseRoleCreate -> ResponseRoleCreate
Ord, ReadPrec [ResponseRoleCreate]
ReadPrec ResponseRoleCreate
Int -> ReadS ResponseRoleCreate
ReadS [ResponseRoleCreate]
(Int -> ReadS ResponseRoleCreate)
-> ReadS [ResponseRoleCreate]
-> ReadPrec ResponseRoleCreate
-> ReadPrec [ResponseRoleCreate]
-> Read ResponseRoleCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseRoleCreate
readsPrec :: Int -> ReadS ResponseRoleCreate
$creadList :: ReadS [ResponseRoleCreate]
readList :: ReadS [ResponseRoleCreate]
$creadPrec :: ReadPrec ResponseRoleCreate
readPrec :: ReadPrec ResponseRoleCreate
$creadListPrec :: ReadPrec [ResponseRoleCreate]
readListPrec :: ReadPrec [ResponseRoleCreate]
Read, Int -> ResponseRoleCreate -> ShowS
[ResponseRoleCreate] -> ShowS
ResponseRoleCreate -> String
(Int -> ResponseRoleCreate -> ShowS)
-> (ResponseRoleCreate -> String)
-> ([ResponseRoleCreate] -> ShowS)
-> Show ResponseRoleCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseRoleCreate -> ShowS
showsPrec :: Int -> ResponseRoleCreate -> ShowS
$cshow :: ResponseRoleCreate -> String
show :: ResponseRoleCreate -> String
$cshowList :: [ResponseRoleCreate] -> ShowS
showList :: [ResponseRoleCreate] -> ShowS
Show)
deriving
(Value -> Parser [ResponseRoleCreate]
Value -> Parser ResponseRoleCreate
(Value -> Parser ResponseRoleCreate)
-> (Value -> Parser [ResponseRoleCreate])
-> FromJSON ResponseRoleCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseRoleCreate
parseJSON :: Value -> Parser ResponseRoleCreate
$cparseJSONList :: Value -> Parser [ResponseRoleCreate]
parseJSONList :: Value -> Parser [ResponseRoleCreate]
A.FromJSON, [ResponseRoleCreate] -> Value
[ResponseRoleCreate] -> Encoding
ResponseRoleCreate -> Value
ResponseRoleCreate -> Encoding
(ResponseRoleCreate -> Value)
-> (ResponseRoleCreate -> Encoding)
-> ([ResponseRoleCreate] -> Value)
-> ([ResponseRoleCreate] -> Encoding)
-> ToJSON ResponseRoleCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseRoleCreate -> Value
toJSON :: ResponseRoleCreate -> Value
$ctoEncoding :: ResponseRoleCreate -> Encoding
toEncoding :: ResponseRoleCreate -> Encoding
$ctoJSONList :: [ResponseRoleCreate] -> Value
toJSONList :: [ResponseRoleCreate] -> Value
$ctoEncodingList :: [ResponseRoleCreate] -> Encoding
toEncodingList :: [ResponseRoleCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseRoleCreate") ResponseRoleCreate
type RequestRoleEdit :: Type
data RequestRoleEdit = MkRequestRoleEdit
{ RequestRoleEdit -> IdentifierRole
requestRoleEditId :: IdentifierRole
, RequestRoleEdit -> Updatable NameRole
requestRoleEditName :: Updatable NameRole
, RequestRoleEdit -> Updatable RoleEditAccessibilityAndPassword
requestRoleEditAccessibilityAndPassword :: Updatable RoleEditAccessibilityAndPassword
, RequestRoleEdit -> Updatable (Set Permission)
requestRoleEditPermissions :: Updatable (S.Set Permission)
}
deriving stock (RequestRoleEdit -> RequestRoleEdit -> Bool
(RequestRoleEdit -> RequestRoleEdit -> Bool)
-> (RequestRoleEdit -> RequestRoleEdit -> Bool)
-> Eq RequestRoleEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestRoleEdit -> RequestRoleEdit -> Bool
== :: RequestRoleEdit -> RequestRoleEdit -> Bool
$c/= :: RequestRoleEdit -> RequestRoleEdit -> Bool
/= :: RequestRoleEdit -> RequestRoleEdit -> Bool
Eq, (forall x. RequestRoleEdit -> Rep RequestRoleEdit x)
-> (forall x. Rep RequestRoleEdit x -> RequestRoleEdit)
-> Generic RequestRoleEdit
forall x. Rep RequestRoleEdit x -> RequestRoleEdit
forall x. RequestRoleEdit -> Rep RequestRoleEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestRoleEdit -> Rep RequestRoleEdit x
from :: forall x. RequestRoleEdit -> Rep RequestRoleEdit x
$cto :: forall x. Rep RequestRoleEdit x -> RequestRoleEdit
to :: forall x. Rep RequestRoleEdit x -> RequestRoleEdit
Generic, Eq RequestRoleEdit
Eq RequestRoleEdit =>
(RequestRoleEdit -> RequestRoleEdit -> Ordering)
-> (RequestRoleEdit -> RequestRoleEdit -> Bool)
-> (RequestRoleEdit -> RequestRoleEdit -> Bool)
-> (RequestRoleEdit -> RequestRoleEdit -> Bool)
-> (RequestRoleEdit -> RequestRoleEdit -> Bool)
-> (RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit)
-> (RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit)
-> Ord RequestRoleEdit
RequestRoleEdit -> RequestRoleEdit -> Bool
RequestRoleEdit -> RequestRoleEdit -> Ordering
RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit
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 :: RequestRoleEdit -> RequestRoleEdit -> Ordering
compare :: RequestRoleEdit -> RequestRoleEdit -> Ordering
$c< :: RequestRoleEdit -> RequestRoleEdit -> Bool
< :: RequestRoleEdit -> RequestRoleEdit -> Bool
$c<= :: RequestRoleEdit -> RequestRoleEdit -> Bool
<= :: RequestRoleEdit -> RequestRoleEdit -> Bool
$c> :: RequestRoleEdit -> RequestRoleEdit -> Bool
> :: RequestRoleEdit -> RequestRoleEdit -> Bool
$c>= :: RequestRoleEdit -> RequestRoleEdit -> Bool
>= :: RequestRoleEdit -> RequestRoleEdit -> Bool
$cmax :: RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit
max :: RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit
$cmin :: RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit
min :: RequestRoleEdit -> RequestRoleEdit -> RequestRoleEdit
Ord, ReadPrec [RequestRoleEdit]
ReadPrec RequestRoleEdit
Int -> ReadS RequestRoleEdit
ReadS [RequestRoleEdit]
(Int -> ReadS RequestRoleEdit)
-> ReadS [RequestRoleEdit]
-> ReadPrec RequestRoleEdit
-> ReadPrec [RequestRoleEdit]
-> Read RequestRoleEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestRoleEdit
readsPrec :: Int -> ReadS RequestRoleEdit
$creadList :: ReadS [RequestRoleEdit]
readList :: ReadS [RequestRoleEdit]
$creadPrec :: ReadPrec RequestRoleEdit
readPrec :: ReadPrec RequestRoleEdit
$creadListPrec :: ReadPrec [RequestRoleEdit]
readListPrec :: ReadPrec [RequestRoleEdit]
Read, Int -> RequestRoleEdit -> ShowS
[RequestRoleEdit] -> ShowS
RequestRoleEdit -> String
(Int -> RequestRoleEdit -> ShowS)
-> (RequestRoleEdit -> String)
-> ([RequestRoleEdit] -> ShowS)
-> Show RequestRoleEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestRoleEdit -> ShowS
showsPrec :: Int -> RequestRoleEdit -> ShowS
$cshow :: RequestRoleEdit -> String
show :: RequestRoleEdit -> String
$cshowList :: [RequestRoleEdit] -> ShowS
showList :: [RequestRoleEdit] -> ShowS
Show)
deriving
(Value -> Parser [RequestRoleEdit]
Value -> Parser RequestRoleEdit
(Value -> Parser RequestRoleEdit)
-> (Value -> Parser [RequestRoleEdit]) -> FromJSON RequestRoleEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestRoleEdit
parseJSON :: Value -> Parser RequestRoleEdit
$cparseJSONList :: Value -> Parser [RequestRoleEdit]
parseJSONList :: Value -> Parser [RequestRoleEdit]
A.FromJSON, [RequestRoleEdit] -> Value
[RequestRoleEdit] -> Encoding
RequestRoleEdit -> Value
RequestRoleEdit -> Encoding
(RequestRoleEdit -> Value)
-> (RequestRoleEdit -> Encoding)
-> ([RequestRoleEdit] -> Value)
-> ([RequestRoleEdit] -> Encoding)
-> ToJSON RequestRoleEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestRoleEdit -> Value
toJSON :: RequestRoleEdit -> Value
$ctoEncoding :: RequestRoleEdit -> Encoding
toEncoding :: RequestRoleEdit -> Encoding
$ctoJSONList :: [RequestRoleEdit] -> Value
toJSONList :: [RequestRoleEdit] -> Value
$ctoEncodingList :: [RequestRoleEdit] -> Encoding
toEncodingList :: [RequestRoleEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestRoleEdit") RequestRoleEdit
type RoleEditAccessibilityAndPassword :: Type
data RoleEditAccessibilityAndPassword = MkRoleEditAccessibilityAndPassword
{ RoleEditAccessibilityAndPassword -> AccessibilityRole
roleEditAccessibilityAndPasswordAccessibility :: AccessibilityRole
, RoleEditAccessibilityAndPassword -> Maybe Text
roleEditAccessibilityAndPasswordPassword :: Maybe T.Text
}
deriving stock (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
(RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> Eq RoleEditAccessibilityAndPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
== :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
$c/= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
/= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
Eq, (forall x.
RoleEditAccessibilityAndPassword
-> Rep RoleEditAccessibilityAndPassword x)
-> (forall x.
Rep RoleEditAccessibilityAndPassword x
-> RoleEditAccessibilityAndPassword)
-> Generic RoleEditAccessibilityAndPassword
forall x.
Rep RoleEditAccessibilityAndPassword x
-> RoleEditAccessibilityAndPassword
forall x.
RoleEditAccessibilityAndPassword
-> Rep RoleEditAccessibilityAndPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
RoleEditAccessibilityAndPassword
-> Rep RoleEditAccessibilityAndPassword x
from :: forall x.
RoleEditAccessibilityAndPassword
-> Rep RoleEditAccessibilityAndPassword x
$cto :: forall x.
Rep RoleEditAccessibilityAndPassword x
-> RoleEditAccessibilityAndPassword
to :: forall x.
Rep RoleEditAccessibilityAndPassword x
-> RoleEditAccessibilityAndPassword
Generic, Eq RoleEditAccessibilityAndPassword
Eq RoleEditAccessibilityAndPassword =>
(RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Ordering)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword)
-> (RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword)
-> Ord RoleEditAccessibilityAndPassword
RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Ordering
RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
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 :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Ordering
compare :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Ordering
$c< :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
< :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
$c<= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
<= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
$c> :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
> :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
$c>= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
>= :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword -> Bool
$cmax :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
max :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
$cmin :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
min :: RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
-> RoleEditAccessibilityAndPassword
Ord, ReadPrec [RoleEditAccessibilityAndPassword]
ReadPrec RoleEditAccessibilityAndPassword
Int -> ReadS RoleEditAccessibilityAndPassword
ReadS [RoleEditAccessibilityAndPassword]
(Int -> ReadS RoleEditAccessibilityAndPassword)
-> ReadS [RoleEditAccessibilityAndPassword]
-> ReadPrec RoleEditAccessibilityAndPassword
-> ReadPrec [RoleEditAccessibilityAndPassword]
-> Read RoleEditAccessibilityAndPassword
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RoleEditAccessibilityAndPassword
readsPrec :: Int -> ReadS RoleEditAccessibilityAndPassword
$creadList :: ReadS [RoleEditAccessibilityAndPassword]
readList :: ReadS [RoleEditAccessibilityAndPassword]
$creadPrec :: ReadPrec RoleEditAccessibilityAndPassword
readPrec :: ReadPrec RoleEditAccessibilityAndPassword
$creadListPrec :: ReadPrec [RoleEditAccessibilityAndPassword]
readListPrec :: ReadPrec [RoleEditAccessibilityAndPassword]
Read, Int -> RoleEditAccessibilityAndPassword -> ShowS
[RoleEditAccessibilityAndPassword] -> ShowS
RoleEditAccessibilityAndPassword -> String
(Int -> RoleEditAccessibilityAndPassword -> ShowS)
-> (RoleEditAccessibilityAndPassword -> String)
-> ([RoleEditAccessibilityAndPassword] -> ShowS)
-> Show RoleEditAccessibilityAndPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RoleEditAccessibilityAndPassword -> ShowS
showsPrec :: Int -> RoleEditAccessibilityAndPassword -> ShowS
$cshow :: RoleEditAccessibilityAndPassword -> String
show :: RoleEditAccessibilityAndPassword -> String
$cshowList :: [RoleEditAccessibilityAndPassword] -> ShowS
showList :: [RoleEditAccessibilityAndPassword] -> ShowS
Show)
deriving
(Value -> Parser [RoleEditAccessibilityAndPassword]
Value -> Parser RoleEditAccessibilityAndPassword
(Value -> Parser RoleEditAccessibilityAndPassword)
-> (Value -> Parser [RoleEditAccessibilityAndPassword])
-> FromJSON RoleEditAccessibilityAndPassword
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RoleEditAccessibilityAndPassword
parseJSON :: Value -> Parser RoleEditAccessibilityAndPassword
$cparseJSONList :: Value -> Parser [RoleEditAccessibilityAndPassword]
parseJSONList :: Value -> Parser [RoleEditAccessibilityAndPassword]
A.FromJSON, [RoleEditAccessibilityAndPassword] -> Value
[RoleEditAccessibilityAndPassword] -> Encoding
RoleEditAccessibilityAndPassword -> Value
RoleEditAccessibilityAndPassword -> Encoding
(RoleEditAccessibilityAndPassword -> Value)
-> (RoleEditAccessibilityAndPassword -> Encoding)
-> ([RoleEditAccessibilityAndPassword] -> Value)
-> ([RoleEditAccessibilityAndPassword] -> Encoding)
-> ToJSON RoleEditAccessibilityAndPassword
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RoleEditAccessibilityAndPassword -> Value
toJSON :: RoleEditAccessibilityAndPassword -> Value
$ctoEncoding :: RoleEditAccessibilityAndPassword -> Encoding
toEncoding :: RoleEditAccessibilityAndPassword -> Encoding
$ctoJSONList :: [RoleEditAccessibilityAndPassword] -> Value
toJSONList :: [RoleEditAccessibilityAndPassword] -> Value
$ctoEncodingList :: [RoleEditAccessibilityAndPassword] -> Encoding
toEncodingList :: [RoleEditAccessibilityAndPassword] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "RoleEdit" "roleEditAccessibilityAndPassword") RoleEditAccessibilityAndPassword
type ResponseRoleEdit :: Type
newtype ResponseRoleEdit = MkResponseRoleEdit
{ ResponseRoleEdit -> ()
responseRoleEditUnit :: ()
}
deriving stock (ResponseRoleEdit -> ResponseRoleEdit -> Bool
(ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> (ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> Eq ResponseRoleEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
== :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
$c/= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
/= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
Eq, (forall x. ResponseRoleEdit -> Rep ResponseRoleEdit x)
-> (forall x. Rep ResponseRoleEdit x -> ResponseRoleEdit)
-> Generic ResponseRoleEdit
forall x. Rep ResponseRoleEdit x -> ResponseRoleEdit
forall x. ResponseRoleEdit -> Rep ResponseRoleEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseRoleEdit -> Rep ResponseRoleEdit x
from :: forall x. ResponseRoleEdit -> Rep ResponseRoleEdit x
$cto :: forall x. Rep ResponseRoleEdit x -> ResponseRoleEdit
to :: forall x. Rep ResponseRoleEdit x -> ResponseRoleEdit
Generic, Eq ResponseRoleEdit
Eq ResponseRoleEdit =>
(ResponseRoleEdit -> ResponseRoleEdit -> Ordering)
-> (ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> (ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> (ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> (ResponseRoleEdit -> ResponseRoleEdit -> Bool)
-> (ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit)
-> (ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit)
-> Ord ResponseRoleEdit
ResponseRoleEdit -> ResponseRoleEdit -> Bool
ResponseRoleEdit -> ResponseRoleEdit -> Ordering
ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit
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 :: ResponseRoleEdit -> ResponseRoleEdit -> Ordering
compare :: ResponseRoleEdit -> ResponseRoleEdit -> Ordering
$c< :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
< :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
$c<= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
<= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
$c> :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
> :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
$c>= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
>= :: ResponseRoleEdit -> ResponseRoleEdit -> Bool
$cmax :: ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit
max :: ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit
$cmin :: ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit
min :: ResponseRoleEdit -> ResponseRoleEdit -> ResponseRoleEdit
Ord, ReadPrec [ResponseRoleEdit]
ReadPrec ResponseRoleEdit
Int -> ReadS ResponseRoleEdit
ReadS [ResponseRoleEdit]
(Int -> ReadS ResponseRoleEdit)
-> ReadS [ResponseRoleEdit]
-> ReadPrec ResponseRoleEdit
-> ReadPrec [ResponseRoleEdit]
-> Read ResponseRoleEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseRoleEdit
readsPrec :: Int -> ReadS ResponseRoleEdit
$creadList :: ReadS [ResponseRoleEdit]
readList :: ReadS [ResponseRoleEdit]
$creadPrec :: ReadPrec ResponseRoleEdit
readPrec :: ReadPrec ResponseRoleEdit
$creadListPrec :: ReadPrec [ResponseRoleEdit]
readListPrec :: ReadPrec [ResponseRoleEdit]
Read, Int -> ResponseRoleEdit -> ShowS
[ResponseRoleEdit] -> ShowS
ResponseRoleEdit -> String
(Int -> ResponseRoleEdit -> ShowS)
-> (ResponseRoleEdit -> String)
-> ([ResponseRoleEdit] -> ShowS)
-> Show ResponseRoleEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseRoleEdit -> ShowS
showsPrec :: Int -> ResponseRoleEdit -> ShowS
$cshow :: ResponseRoleEdit -> String
show :: ResponseRoleEdit -> String
$cshowList :: [ResponseRoleEdit] -> ShowS
showList :: [ResponseRoleEdit] -> ShowS
Show)
deriving
(Value -> Parser [ResponseRoleEdit]
Value -> Parser ResponseRoleEdit
(Value -> Parser ResponseRoleEdit)
-> (Value -> Parser [ResponseRoleEdit])
-> FromJSON ResponseRoleEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseRoleEdit
parseJSON :: Value -> Parser ResponseRoleEdit
$cparseJSONList :: Value -> Parser [ResponseRoleEdit]
parseJSONList :: Value -> Parser [ResponseRoleEdit]
A.FromJSON, [ResponseRoleEdit] -> Value
[ResponseRoleEdit] -> Encoding
ResponseRoleEdit -> Value
ResponseRoleEdit -> Encoding
(ResponseRoleEdit -> Value)
-> (ResponseRoleEdit -> Encoding)
-> ([ResponseRoleEdit] -> Value)
-> ([ResponseRoleEdit] -> Encoding)
-> ToJSON ResponseRoleEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseRoleEdit -> Value
toJSON :: ResponseRoleEdit -> Value
$ctoEncoding :: ResponseRoleEdit -> Encoding
toEncoding :: ResponseRoleEdit -> Encoding
$ctoJSONList :: [ResponseRoleEdit] -> Value
toJSONList :: [ResponseRoleEdit] -> Value
$ctoEncodingList :: [ResponseRoleEdit] -> Encoding
toEncodingList :: [ResponseRoleEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseRoleEdit") ResponseRoleEdit
type RequestRoleDelete :: Type
data RequestRoleDelete = MkRequestRoleDelete
{ RequestRoleDelete -> IdentifierRole
requestRoleDeleteId :: IdentifierRole
, RequestRoleDelete -> IdentifierRole
requestRoleDeleteFallbackId :: IdentifierRole
}
deriving stock (RequestRoleDelete -> RequestRoleDelete -> Bool
(RequestRoleDelete -> RequestRoleDelete -> Bool)
-> (RequestRoleDelete -> RequestRoleDelete -> Bool)
-> Eq RequestRoleDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestRoleDelete -> RequestRoleDelete -> Bool
== :: RequestRoleDelete -> RequestRoleDelete -> Bool
$c/= :: RequestRoleDelete -> RequestRoleDelete -> Bool
/= :: RequestRoleDelete -> RequestRoleDelete -> Bool
Eq, (forall x. RequestRoleDelete -> Rep RequestRoleDelete x)
-> (forall x. Rep RequestRoleDelete x -> RequestRoleDelete)
-> Generic RequestRoleDelete
forall x. Rep RequestRoleDelete x -> RequestRoleDelete
forall x. RequestRoleDelete -> Rep RequestRoleDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestRoleDelete -> Rep RequestRoleDelete x
from :: forall x. RequestRoleDelete -> Rep RequestRoleDelete x
$cto :: forall x. Rep RequestRoleDelete x -> RequestRoleDelete
to :: forall x. Rep RequestRoleDelete x -> RequestRoleDelete
Generic, Eq RequestRoleDelete
Eq RequestRoleDelete =>
(RequestRoleDelete -> RequestRoleDelete -> Ordering)
-> (RequestRoleDelete -> RequestRoleDelete -> Bool)
-> (RequestRoleDelete -> RequestRoleDelete -> Bool)
-> (RequestRoleDelete -> RequestRoleDelete -> Bool)
-> (RequestRoleDelete -> RequestRoleDelete -> Bool)
-> (RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete)
-> (RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete)
-> Ord RequestRoleDelete
RequestRoleDelete -> RequestRoleDelete -> Bool
RequestRoleDelete -> RequestRoleDelete -> Ordering
RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete
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 :: RequestRoleDelete -> RequestRoleDelete -> Ordering
compare :: RequestRoleDelete -> RequestRoleDelete -> Ordering
$c< :: RequestRoleDelete -> RequestRoleDelete -> Bool
< :: RequestRoleDelete -> RequestRoleDelete -> Bool
$c<= :: RequestRoleDelete -> RequestRoleDelete -> Bool
<= :: RequestRoleDelete -> RequestRoleDelete -> Bool
$c> :: RequestRoleDelete -> RequestRoleDelete -> Bool
> :: RequestRoleDelete -> RequestRoleDelete -> Bool
$c>= :: RequestRoleDelete -> RequestRoleDelete -> Bool
>= :: RequestRoleDelete -> RequestRoleDelete -> Bool
$cmax :: RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete
max :: RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete
$cmin :: RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete
min :: RequestRoleDelete -> RequestRoleDelete -> RequestRoleDelete
Ord, ReadPrec [RequestRoleDelete]
ReadPrec RequestRoleDelete
Int -> ReadS RequestRoleDelete
ReadS [RequestRoleDelete]
(Int -> ReadS RequestRoleDelete)
-> ReadS [RequestRoleDelete]
-> ReadPrec RequestRoleDelete
-> ReadPrec [RequestRoleDelete]
-> Read RequestRoleDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestRoleDelete
readsPrec :: Int -> ReadS RequestRoleDelete
$creadList :: ReadS [RequestRoleDelete]
readList :: ReadS [RequestRoleDelete]
$creadPrec :: ReadPrec RequestRoleDelete
readPrec :: ReadPrec RequestRoleDelete
$creadListPrec :: ReadPrec [RequestRoleDelete]
readListPrec :: ReadPrec [RequestRoleDelete]
Read, Int -> RequestRoleDelete -> ShowS
[RequestRoleDelete] -> ShowS
RequestRoleDelete -> String
(Int -> RequestRoleDelete -> ShowS)
-> (RequestRoleDelete -> String)
-> ([RequestRoleDelete] -> ShowS)
-> Show RequestRoleDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestRoleDelete -> ShowS
showsPrec :: Int -> RequestRoleDelete -> ShowS
$cshow :: RequestRoleDelete -> String
show :: RequestRoleDelete -> String
$cshowList :: [RequestRoleDelete] -> ShowS
showList :: [RequestRoleDelete] -> ShowS
Show)
deriving
(Value -> Parser [RequestRoleDelete]
Value -> Parser RequestRoleDelete
(Value -> Parser RequestRoleDelete)
-> (Value -> Parser [RequestRoleDelete])
-> FromJSON RequestRoleDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestRoleDelete
parseJSON :: Value -> Parser RequestRoleDelete
$cparseJSONList :: Value -> Parser [RequestRoleDelete]
parseJSONList :: Value -> Parser [RequestRoleDelete]
A.FromJSON, [RequestRoleDelete] -> Value
[RequestRoleDelete] -> Encoding
RequestRoleDelete -> Value
RequestRoleDelete -> Encoding
(RequestRoleDelete -> Value)
-> (RequestRoleDelete -> Encoding)
-> ([RequestRoleDelete] -> Value)
-> ([RequestRoleDelete] -> Encoding)
-> ToJSON RequestRoleDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestRoleDelete -> Value
toJSON :: RequestRoleDelete -> Value
$ctoEncoding :: RequestRoleDelete -> Encoding
toEncoding :: RequestRoleDelete -> Encoding
$ctoJSONList :: [RequestRoleDelete] -> Value
toJSONList :: [RequestRoleDelete] -> Value
$ctoEncodingList :: [RequestRoleDelete] -> Encoding
toEncodingList :: [RequestRoleDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestRoleDelete") RequestRoleDelete
type ResponseRoleDelete :: Type
newtype ResponseRoleDelete = MkResponseRoleDelete
{ ResponseRoleDelete -> ()
responseRoleDeleteUnit :: ()
}
deriving stock (ResponseRoleDelete -> ResponseRoleDelete -> Bool
(ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> (ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> Eq ResponseRoleDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
== :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
$c/= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
/= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
Eq, (forall x. ResponseRoleDelete -> Rep ResponseRoleDelete x)
-> (forall x. Rep ResponseRoleDelete x -> ResponseRoleDelete)
-> Generic ResponseRoleDelete
forall x. Rep ResponseRoleDelete x -> ResponseRoleDelete
forall x. ResponseRoleDelete -> Rep ResponseRoleDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseRoleDelete -> Rep ResponseRoleDelete x
from :: forall x. ResponseRoleDelete -> Rep ResponseRoleDelete x
$cto :: forall x. Rep ResponseRoleDelete x -> ResponseRoleDelete
to :: forall x. Rep ResponseRoleDelete x -> ResponseRoleDelete
Generic, Eq ResponseRoleDelete
Eq ResponseRoleDelete =>
(ResponseRoleDelete -> ResponseRoleDelete -> Ordering)
-> (ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> (ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> (ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> (ResponseRoleDelete -> ResponseRoleDelete -> Bool)
-> (ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete)
-> (ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete)
-> Ord ResponseRoleDelete
ResponseRoleDelete -> ResponseRoleDelete -> Bool
ResponseRoleDelete -> ResponseRoleDelete -> Ordering
ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete
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 :: ResponseRoleDelete -> ResponseRoleDelete -> Ordering
compare :: ResponseRoleDelete -> ResponseRoleDelete -> Ordering
$c< :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
< :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
$c<= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
<= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
$c> :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
> :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
$c>= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
>= :: ResponseRoleDelete -> ResponseRoleDelete -> Bool
$cmax :: ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete
max :: ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete
$cmin :: ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete
min :: ResponseRoleDelete -> ResponseRoleDelete -> ResponseRoleDelete
Ord, ReadPrec [ResponseRoleDelete]
ReadPrec ResponseRoleDelete
Int -> ReadS ResponseRoleDelete
ReadS [ResponseRoleDelete]
(Int -> ReadS ResponseRoleDelete)
-> ReadS [ResponseRoleDelete]
-> ReadPrec ResponseRoleDelete
-> ReadPrec [ResponseRoleDelete]
-> Read ResponseRoleDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseRoleDelete
readsPrec :: Int -> ReadS ResponseRoleDelete
$creadList :: ReadS [ResponseRoleDelete]
readList :: ReadS [ResponseRoleDelete]
$creadPrec :: ReadPrec ResponseRoleDelete
readPrec :: ReadPrec ResponseRoleDelete
$creadListPrec :: ReadPrec [ResponseRoleDelete]
readListPrec :: ReadPrec [ResponseRoleDelete]
Read, Int -> ResponseRoleDelete -> ShowS
[ResponseRoleDelete] -> ShowS
ResponseRoleDelete -> String
(Int -> ResponseRoleDelete -> ShowS)
-> (ResponseRoleDelete -> String)
-> ([ResponseRoleDelete] -> ShowS)
-> Show ResponseRoleDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseRoleDelete -> ShowS
showsPrec :: Int -> ResponseRoleDelete -> ShowS
$cshow :: ResponseRoleDelete -> String
show :: ResponseRoleDelete -> String
$cshowList :: [ResponseRoleDelete] -> ShowS
showList :: [ResponseRoleDelete] -> ShowS
Show)
deriving
(Value -> Parser [ResponseRoleDelete]
Value -> Parser ResponseRoleDelete
(Value -> Parser ResponseRoleDelete)
-> (Value -> Parser [ResponseRoleDelete])
-> FromJSON ResponseRoleDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseRoleDelete
parseJSON :: Value -> Parser ResponseRoleDelete
$cparseJSONList :: Value -> Parser [ResponseRoleDelete]
parseJSONList :: Value -> Parser [ResponseRoleDelete]
A.FromJSON, [ResponseRoleDelete] -> Value
[ResponseRoleDelete] -> Encoding
ResponseRoleDelete -> Value
ResponseRoleDelete -> Encoding
(ResponseRoleDelete -> Value)
-> (ResponseRoleDelete -> Encoding)
-> ([ResponseRoleDelete] -> Value)
-> ([ResponseRoleDelete] -> Encoding)
-> ToJSON ResponseRoleDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseRoleDelete -> Value
toJSON :: ResponseRoleDelete -> Value
$ctoEncoding :: ResponseRoleDelete -> Encoding
toEncoding :: ResponseRoleDelete -> Encoding
$ctoJSONList :: [ResponseRoleDelete] -> Value
toJSONList :: [ResponseRoleDelete] -> Value
$ctoEncodingList :: [ResponseRoleDelete] -> Encoding
toEncodingList :: [ResponseRoleDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseRoleDelete") ResponseRoleDelete
type RequestDeskCreate :: Type
data RequestDeskCreate = MkRequestDeskCreate
{ RequestDeskCreate -> NameDesk
requestDeskCreateName :: NameDesk
, RequestDeskCreate -> NameOrIdentifier NameSpace IdentifierSpace
requestDeskCreateSpace :: NameOrIdentifier NameSpace IdentifierSpace
, RequestDeskCreate -> Maybe LocationDesk
requestDeskCreateLocation :: Maybe LocationDesk
}
deriving stock (RequestDeskCreate -> RequestDeskCreate -> Bool
(RequestDeskCreate -> RequestDeskCreate -> Bool)
-> (RequestDeskCreate -> RequestDeskCreate -> Bool)
-> Eq RequestDeskCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestDeskCreate -> RequestDeskCreate -> Bool
== :: RequestDeskCreate -> RequestDeskCreate -> Bool
$c/= :: RequestDeskCreate -> RequestDeskCreate -> Bool
/= :: RequestDeskCreate -> RequestDeskCreate -> Bool
Eq, (forall x. RequestDeskCreate -> Rep RequestDeskCreate x)
-> (forall x. Rep RequestDeskCreate x -> RequestDeskCreate)
-> Generic RequestDeskCreate
forall x. Rep RequestDeskCreate x -> RequestDeskCreate
forall x. RequestDeskCreate -> Rep RequestDeskCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestDeskCreate -> Rep RequestDeskCreate x
from :: forall x. RequestDeskCreate -> Rep RequestDeskCreate x
$cto :: forall x. Rep RequestDeskCreate x -> RequestDeskCreate
to :: forall x. Rep RequestDeskCreate x -> RequestDeskCreate
Generic, Eq RequestDeskCreate
Eq RequestDeskCreate =>
(RequestDeskCreate -> RequestDeskCreate -> Ordering)
-> (RequestDeskCreate -> RequestDeskCreate -> Bool)
-> (RequestDeskCreate -> RequestDeskCreate -> Bool)
-> (RequestDeskCreate -> RequestDeskCreate -> Bool)
-> (RequestDeskCreate -> RequestDeskCreate -> Bool)
-> (RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate)
-> (RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate)
-> Ord RequestDeskCreate
RequestDeskCreate -> RequestDeskCreate -> Bool
RequestDeskCreate -> RequestDeskCreate -> Ordering
RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate
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 :: RequestDeskCreate -> RequestDeskCreate -> Ordering
compare :: RequestDeskCreate -> RequestDeskCreate -> Ordering
$c< :: RequestDeskCreate -> RequestDeskCreate -> Bool
< :: RequestDeskCreate -> RequestDeskCreate -> Bool
$c<= :: RequestDeskCreate -> RequestDeskCreate -> Bool
<= :: RequestDeskCreate -> RequestDeskCreate -> Bool
$c> :: RequestDeskCreate -> RequestDeskCreate -> Bool
> :: RequestDeskCreate -> RequestDeskCreate -> Bool
$c>= :: RequestDeskCreate -> RequestDeskCreate -> Bool
>= :: RequestDeskCreate -> RequestDeskCreate -> Bool
$cmax :: RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate
max :: RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate
$cmin :: RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate
min :: RequestDeskCreate -> RequestDeskCreate -> RequestDeskCreate
Ord, ReadPrec [RequestDeskCreate]
ReadPrec RequestDeskCreate
Int -> ReadS RequestDeskCreate
ReadS [RequestDeskCreate]
(Int -> ReadS RequestDeskCreate)
-> ReadS [RequestDeskCreate]
-> ReadPrec RequestDeskCreate
-> ReadPrec [RequestDeskCreate]
-> Read RequestDeskCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestDeskCreate
readsPrec :: Int -> ReadS RequestDeskCreate
$creadList :: ReadS [RequestDeskCreate]
readList :: ReadS [RequestDeskCreate]
$creadPrec :: ReadPrec RequestDeskCreate
readPrec :: ReadPrec RequestDeskCreate
$creadListPrec :: ReadPrec [RequestDeskCreate]
readListPrec :: ReadPrec [RequestDeskCreate]
Read, Int -> RequestDeskCreate -> ShowS
[RequestDeskCreate] -> ShowS
RequestDeskCreate -> String
(Int -> RequestDeskCreate -> ShowS)
-> (RequestDeskCreate -> String)
-> ([RequestDeskCreate] -> ShowS)
-> Show RequestDeskCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestDeskCreate -> ShowS
showsPrec :: Int -> RequestDeskCreate -> ShowS
$cshow :: RequestDeskCreate -> String
show :: RequestDeskCreate -> String
$cshowList :: [RequestDeskCreate] -> ShowS
showList :: [RequestDeskCreate] -> ShowS
Show)
deriving
(Value -> Parser [RequestDeskCreate]
Value -> Parser RequestDeskCreate
(Value -> Parser RequestDeskCreate)
-> (Value -> Parser [RequestDeskCreate])
-> FromJSON RequestDeskCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestDeskCreate
parseJSON :: Value -> Parser RequestDeskCreate
$cparseJSONList :: Value -> Parser [RequestDeskCreate]
parseJSONList :: Value -> Parser [RequestDeskCreate]
A.FromJSON, [RequestDeskCreate] -> Value
[RequestDeskCreate] -> Encoding
RequestDeskCreate -> Value
RequestDeskCreate -> Encoding
(RequestDeskCreate -> Value)
-> (RequestDeskCreate -> Encoding)
-> ([RequestDeskCreate] -> Value)
-> ([RequestDeskCreate] -> Encoding)
-> ToJSON RequestDeskCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestDeskCreate -> Value
toJSON :: RequestDeskCreate -> Value
$ctoEncoding :: RequestDeskCreate -> Encoding
toEncoding :: RequestDeskCreate -> Encoding
$ctoJSONList :: [RequestDeskCreate] -> Value
toJSONList :: [RequestDeskCreate] -> Value
$ctoEncodingList :: [RequestDeskCreate] -> Encoding
toEncodingList :: [RequestDeskCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestDeskCreate") RequestDeskCreate
type ResponseDeskCreate :: Type
newtype ResponseDeskCreate = MkResponseDeskCreate
{ ResponseDeskCreate -> IdentifierDesk
responseDeskCreateId :: IdentifierDesk
}
deriving stock (ResponseDeskCreate -> ResponseDeskCreate -> Bool
(ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> (ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> Eq ResponseDeskCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
== :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
$c/= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
/= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
Eq, (forall x. ResponseDeskCreate -> Rep ResponseDeskCreate x)
-> (forall x. Rep ResponseDeskCreate x -> ResponseDeskCreate)
-> Generic ResponseDeskCreate
forall x. Rep ResponseDeskCreate x -> ResponseDeskCreate
forall x. ResponseDeskCreate -> Rep ResponseDeskCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseDeskCreate -> Rep ResponseDeskCreate x
from :: forall x. ResponseDeskCreate -> Rep ResponseDeskCreate x
$cto :: forall x. Rep ResponseDeskCreate x -> ResponseDeskCreate
to :: forall x. Rep ResponseDeskCreate x -> ResponseDeskCreate
Generic, Eq ResponseDeskCreate
Eq ResponseDeskCreate =>
(ResponseDeskCreate -> ResponseDeskCreate -> Ordering)
-> (ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> (ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> (ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> (ResponseDeskCreate -> ResponseDeskCreate -> Bool)
-> (ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate)
-> (ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate)
-> Ord ResponseDeskCreate
ResponseDeskCreate -> ResponseDeskCreate -> Bool
ResponseDeskCreate -> ResponseDeskCreate -> Ordering
ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate
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 :: ResponseDeskCreate -> ResponseDeskCreate -> Ordering
compare :: ResponseDeskCreate -> ResponseDeskCreate -> Ordering
$c< :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
< :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
$c<= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
<= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
$c> :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
> :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
$c>= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
>= :: ResponseDeskCreate -> ResponseDeskCreate -> Bool
$cmax :: ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate
max :: ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate
$cmin :: ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate
min :: ResponseDeskCreate -> ResponseDeskCreate -> ResponseDeskCreate
Ord, ReadPrec [ResponseDeskCreate]
ReadPrec ResponseDeskCreate
Int -> ReadS ResponseDeskCreate
ReadS [ResponseDeskCreate]
(Int -> ReadS ResponseDeskCreate)
-> ReadS [ResponseDeskCreate]
-> ReadPrec ResponseDeskCreate
-> ReadPrec [ResponseDeskCreate]
-> Read ResponseDeskCreate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseDeskCreate
readsPrec :: Int -> ReadS ResponseDeskCreate
$creadList :: ReadS [ResponseDeskCreate]
readList :: ReadS [ResponseDeskCreate]
$creadPrec :: ReadPrec ResponseDeskCreate
readPrec :: ReadPrec ResponseDeskCreate
$creadListPrec :: ReadPrec [ResponseDeskCreate]
readListPrec :: ReadPrec [ResponseDeskCreate]
Read, Int -> ResponseDeskCreate -> ShowS
[ResponseDeskCreate] -> ShowS
ResponseDeskCreate -> String
(Int -> ResponseDeskCreate -> ShowS)
-> (ResponseDeskCreate -> String)
-> ([ResponseDeskCreate] -> ShowS)
-> Show ResponseDeskCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseDeskCreate -> ShowS
showsPrec :: Int -> ResponseDeskCreate -> ShowS
$cshow :: ResponseDeskCreate -> String
show :: ResponseDeskCreate -> String
$cshowList :: [ResponseDeskCreate] -> ShowS
showList :: [ResponseDeskCreate] -> ShowS
Show)
deriving
(Value -> Parser [ResponseDeskCreate]
Value -> Parser ResponseDeskCreate
(Value -> Parser ResponseDeskCreate)
-> (Value -> Parser [ResponseDeskCreate])
-> FromJSON ResponseDeskCreate
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseDeskCreate
parseJSON :: Value -> Parser ResponseDeskCreate
$cparseJSONList :: Value -> Parser [ResponseDeskCreate]
parseJSONList :: Value -> Parser [ResponseDeskCreate]
A.FromJSON, [ResponseDeskCreate] -> Value
[ResponseDeskCreate] -> Encoding
ResponseDeskCreate -> Value
ResponseDeskCreate -> Encoding
(ResponseDeskCreate -> Value)
-> (ResponseDeskCreate -> Encoding)
-> ([ResponseDeskCreate] -> Value)
-> ([ResponseDeskCreate] -> Encoding)
-> ToJSON ResponseDeskCreate
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseDeskCreate -> Value
toJSON :: ResponseDeskCreate -> Value
$ctoEncoding :: ResponseDeskCreate -> Encoding
toEncoding :: ResponseDeskCreate -> Encoding
$ctoJSONList :: [ResponseDeskCreate] -> Value
toJSONList :: [ResponseDeskCreate] -> Value
$ctoEncodingList :: [ResponseDeskCreate] -> Encoding
toEncodingList :: [ResponseDeskCreate] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseDeskCreate") ResponseDeskCreate
type RequestDeskDelete :: Type
newtype RequestDeskDelete = MkRequestDeskDelete
{ RequestDeskDelete -> IdentifierDesk
requestDeskDeleteId :: IdentifierDesk
}
deriving stock (RequestDeskDelete -> RequestDeskDelete -> Bool
(RequestDeskDelete -> RequestDeskDelete -> Bool)
-> (RequestDeskDelete -> RequestDeskDelete -> Bool)
-> Eq RequestDeskDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestDeskDelete -> RequestDeskDelete -> Bool
== :: RequestDeskDelete -> RequestDeskDelete -> Bool
$c/= :: RequestDeskDelete -> RequestDeskDelete -> Bool
/= :: RequestDeskDelete -> RequestDeskDelete -> Bool
Eq, (forall x. RequestDeskDelete -> Rep RequestDeskDelete x)
-> (forall x. Rep RequestDeskDelete x -> RequestDeskDelete)
-> Generic RequestDeskDelete
forall x. Rep RequestDeskDelete x -> RequestDeskDelete
forall x. RequestDeskDelete -> Rep RequestDeskDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestDeskDelete -> Rep RequestDeskDelete x
from :: forall x. RequestDeskDelete -> Rep RequestDeskDelete x
$cto :: forall x. Rep RequestDeskDelete x -> RequestDeskDelete
to :: forall x. Rep RequestDeskDelete x -> RequestDeskDelete
Generic, Eq RequestDeskDelete
Eq RequestDeskDelete =>
(RequestDeskDelete -> RequestDeskDelete -> Ordering)
-> (RequestDeskDelete -> RequestDeskDelete -> Bool)
-> (RequestDeskDelete -> RequestDeskDelete -> Bool)
-> (RequestDeskDelete -> RequestDeskDelete -> Bool)
-> (RequestDeskDelete -> RequestDeskDelete -> Bool)
-> (RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete)
-> (RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete)
-> Ord RequestDeskDelete
RequestDeskDelete -> RequestDeskDelete -> Bool
RequestDeskDelete -> RequestDeskDelete -> Ordering
RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete
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 :: RequestDeskDelete -> RequestDeskDelete -> Ordering
compare :: RequestDeskDelete -> RequestDeskDelete -> Ordering
$c< :: RequestDeskDelete -> RequestDeskDelete -> Bool
< :: RequestDeskDelete -> RequestDeskDelete -> Bool
$c<= :: RequestDeskDelete -> RequestDeskDelete -> Bool
<= :: RequestDeskDelete -> RequestDeskDelete -> Bool
$c> :: RequestDeskDelete -> RequestDeskDelete -> Bool
> :: RequestDeskDelete -> RequestDeskDelete -> Bool
$c>= :: RequestDeskDelete -> RequestDeskDelete -> Bool
>= :: RequestDeskDelete -> RequestDeskDelete -> Bool
$cmax :: RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete
max :: RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete
$cmin :: RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete
min :: RequestDeskDelete -> RequestDeskDelete -> RequestDeskDelete
Ord, ReadPrec [RequestDeskDelete]
ReadPrec RequestDeskDelete
Int -> ReadS RequestDeskDelete
ReadS [RequestDeskDelete]
(Int -> ReadS RequestDeskDelete)
-> ReadS [RequestDeskDelete]
-> ReadPrec RequestDeskDelete
-> ReadPrec [RequestDeskDelete]
-> Read RequestDeskDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestDeskDelete
readsPrec :: Int -> ReadS RequestDeskDelete
$creadList :: ReadS [RequestDeskDelete]
readList :: ReadS [RequestDeskDelete]
$creadPrec :: ReadPrec RequestDeskDelete
readPrec :: ReadPrec RequestDeskDelete
$creadListPrec :: ReadPrec [RequestDeskDelete]
readListPrec :: ReadPrec [RequestDeskDelete]
Read, Int -> RequestDeskDelete -> ShowS
[RequestDeskDelete] -> ShowS
RequestDeskDelete -> String
(Int -> RequestDeskDelete -> ShowS)
-> (RequestDeskDelete -> String)
-> ([RequestDeskDelete] -> ShowS)
-> Show RequestDeskDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestDeskDelete -> ShowS
showsPrec :: Int -> RequestDeskDelete -> ShowS
$cshow :: RequestDeskDelete -> String
show :: RequestDeskDelete -> String
$cshowList :: [RequestDeskDelete] -> ShowS
showList :: [RequestDeskDelete] -> ShowS
Show)
deriving
(Value -> Parser [RequestDeskDelete]
Value -> Parser RequestDeskDelete
(Value -> Parser RequestDeskDelete)
-> (Value -> Parser [RequestDeskDelete])
-> FromJSON RequestDeskDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestDeskDelete
parseJSON :: Value -> Parser RequestDeskDelete
$cparseJSONList :: Value -> Parser [RequestDeskDelete]
parseJSONList :: Value -> Parser [RequestDeskDelete]
A.FromJSON, [RequestDeskDelete] -> Value
[RequestDeskDelete] -> Encoding
RequestDeskDelete -> Value
RequestDeskDelete -> Encoding
(RequestDeskDelete -> Value)
-> (RequestDeskDelete -> Encoding)
-> ([RequestDeskDelete] -> Value)
-> ([RequestDeskDelete] -> Encoding)
-> ToJSON RequestDeskDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestDeskDelete -> Value
toJSON :: RequestDeskDelete -> Value
$ctoEncoding :: RequestDeskDelete -> Encoding
toEncoding :: RequestDeskDelete -> Encoding
$ctoJSONList :: [RequestDeskDelete] -> Value
toJSONList :: [RequestDeskDelete] -> Value
$ctoEncodingList :: [RequestDeskDelete] -> Encoding
toEncodingList :: [RequestDeskDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestDeskDelete") RequestDeskDelete
type ResponseDeskDelete :: Type
newtype ResponseDeskDelete = MkResponseDeskDelete
{ ResponseDeskDelete -> ()
responseDeskDeleteUnit :: ()
}
deriving stock (ResponseDeskDelete -> ResponseDeskDelete -> Bool
(ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> (ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> Eq ResponseDeskDelete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
== :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
$c/= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
/= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
Eq, (forall x. ResponseDeskDelete -> Rep ResponseDeskDelete x)
-> (forall x. Rep ResponseDeskDelete x -> ResponseDeskDelete)
-> Generic ResponseDeskDelete
forall x. Rep ResponseDeskDelete x -> ResponseDeskDelete
forall x. ResponseDeskDelete -> Rep ResponseDeskDelete x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseDeskDelete -> Rep ResponseDeskDelete x
from :: forall x. ResponseDeskDelete -> Rep ResponseDeskDelete x
$cto :: forall x. Rep ResponseDeskDelete x -> ResponseDeskDelete
to :: forall x. Rep ResponseDeskDelete x -> ResponseDeskDelete
Generic, Eq ResponseDeskDelete
Eq ResponseDeskDelete =>
(ResponseDeskDelete -> ResponseDeskDelete -> Ordering)
-> (ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> (ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> (ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> (ResponseDeskDelete -> ResponseDeskDelete -> Bool)
-> (ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete)
-> (ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete)
-> Ord ResponseDeskDelete
ResponseDeskDelete -> ResponseDeskDelete -> Bool
ResponseDeskDelete -> ResponseDeskDelete -> Ordering
ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete
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 :: ResponseDeskDelete -> ResponseDeskDelete -> Ordering
compare :: ResponseDeskDelete -> ResponseDeskDelete -> Ordering
$c< :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
< :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
$c<= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
<= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
$c> :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
> :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
$c>= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
>= :: ResponseDeskDelete -> ResponseDeskDelete -> Bool
$cmax :: ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete
max :: ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete
$cmin :: ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete
min :: ResponseDeskDelete -> ResponseDeskDelete -> ResponseDeskDelete
Ord, ReadPrec [ResponseDeskDelete]
ReadPrec ResponseDeskDelete
Int -> ReadS ResponseDeskDelete
ReadS [ResponseDeskDelete]
(Int -> ReadS ResponseDeskDelete)
-> ReadS [ResponseDeskDelete]
-> ReadPrec ResponseDeskDelete
-> ReadPrec [ResponseDeskDelete]
-> Read ResponseDeskDelete
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseDeskDelete
readsPrec :: Int -> ReadS ResponseDeskDelete
$creadList :: ReadS [ResponseDeskDelete]
readList :: ReadS [ResponseDeskDelete]
$creadPrec :: ReadPrec ResponseDeskDelete
readPrec :: ReadPrec ResponseDeskDelete
$creadListPrec :: ReadPrec [ResponseDeskDelete]
readListPrec :: ReadPrec [ResponseDeskDelete]
Read, Int -> ResponseDeskDelete -> ShowS
[ResponseDeskDelete] -> ShowS
ResponseDeskDelete -> String
(Int -> ResponseDeskDelete -> ShowS)
-> (ResponseDeskDelete -> String)
-> ([ResponseDeskDelete] -> ShowS)
-> Show ResponseDeskDelete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseDeskDelete -> ShowS
showsPrec :: Int -> ResponseDeskDelete -> ShowS
$cshow :: ResponseDeskDelete -> String
show :: ResponseDeskDelete -> String
$cshowList :: [ResponseDeskDelete] -> ShowS
showList :: [ResponseDeskDelete] -> ShowS
Show)
deriving
(Value -> Parser [ResponseDeskDelete]
Value -> Parser ResponseDeskDelete
(Value -> Parser ResponseDeskDelete)
-> (Value -> Parser [ResponseDeskDelete])
-> FromJSON ResponseDeskDelete
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseDeskDelete
parseJSON :: Value -> Parser ResponseDeskDelete
$cparseJSONList :: Value -> Parser [ResponseDeskDelete]
parseJSONList :: Value -> Parser [ResponseDeskDelete]
A.FromJSON, [ResponseDeskDelete] -> Value
[ResponseDeskDelete] -> Encoding
ResponseDeskDelete -> Value
ResponseDeskDelete -> Encoding
(ResponseDeskDelete -> Value)
-> (ResponseDeskDelete -> Encoding)
-> ([ResponseDeskDelete] -> Value)
-> ([ResponseDeskDelete] -> Encoding)
-> ToJSON ResponseDeskDelete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseDeskDelete -> Value
toJSON :: ResponseDeskDelete -> Value
$ctoEncoding :: ResponseDeskDelete -> Encoding
toEncoding :: ResponseDeskDelete -> Encoding
$ctoJSONList :: [ResponseDeskDelete] -> Value
toJSONList :: [ResponseDeskDelete] -> Value
$ctoEncodingList :: [ResponseDeskDelete] -> Encoding
toEncodingList :: [ResponseDeskDelete] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseDeskDelete") ResponseDeskDelete
type RequestDeskEdit :: Type
data RequestDeskEdit = MkRequestDeskEdit
{ RequestDeskEdit -> IdentifierDesk
requestDeskEditId :: IdentifierDesk
, RequestDeskEdit -> Updatable NameDesk
requestDeskEditName :: Updatable NameDesk
, RequestDeskEdit -> Updatable (Maybe LocationDesk)
requestDeskEditLocation :: Updatable (Maybe LocationDesk)
}
deriving stock (RequestDeskEdit -> RequestDeskEdit -> Bool
(RequestDeskEdit -> RequestDeskEdit -> Bool)
-> (RequestDeskEdit -> RequestDeskEdit -> Bool)
-> Eq RequestDeskEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestDeskEdit -> RequestDeskEdit -> Bool
== :: RequestDeskEdit -> RequestDeskEdit -> Bool
$c/= :: RequestDeskEdit -> RequestDeskEdit -> Bool
/= :: RequestDeskEdit -> RequestDeskEdit -> Bool
Eq, (forall x. RequestDeskEdit -> Rep RequestDeskEdit x)
-> (forall x. Rep RequestDeskEdit x -> RequestDeskEdit)
-> Generic RequestDeskEdit
forall x. Rep RequestDeskEdit x -> RequestDeskEdit
forall x. RequestDeskEdit -> Rep RequestDeskEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestDeskEdit -> Rep RequestDeskEdit x
from :: forall x. RequestDeskEdit -> Rep RequestDeskEdit x
$cto :: forall x. Rep RequestDeskEdit x -> RequestDeskEdit
to :: forall x. Rep RequestDeskEdit x -> RequestDeskEdit
Generic, Eq RequestDeskEdit
Eq RequestDeskEdit =>
(RequestDeskEdit -> RequestDeskEdit -> Ordering)
-> (RequestDeskEdit -> RequestDeskEdit -> Bool)
-> (RequestDeskEdit -> RequestDeskEdit -> Bool)
-> (RequestDeskEdit -> RequestDeskEdit -> Bool)
-> (RequestDeskEdit -> RequestDeskEdit -> Bool)
-> (RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit)
-> (RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit)
-> Ord RequestDeskEdit
RequestDeskEdit -> RequestDeskEdit -> Bool
RequestDeskEdit -> RequestDeskEdit -> Ordering
RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit
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 :: RequestDeskEdit -> RequestDeskEdit -> Ordering
compare :: RequestDeskEdit -> RequestDeskEdit -> Ordering
$c< :: RequestDeskEdit -> RequestDeskEdit -> Bool
< :: RequestDeskEdit -> RequestDeskEdit -> Bool
$c<= :: RequestDeskEdit -> RequestDeskEdit -> Bool
<= :: RequestDeskEdit -> RequestDeskEdit -> Bool
$c> :: RequestDeskEdit -> RequestDeskEdit -> Bool
> :: RequestDeskEdit -> RequestDeskEdit -> Bool
$c>= :: RequestDeskEdit -> RequestDeskEdit -> Bool
>= :: RequestDeskEdit -> RequestDeskEdit -> Bool
$cmax :: RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit
max :: RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit
$cmin :: RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit
min :: RequestDeskEdit -> RequestDeskEdit -> RequestDeskEdit
Ord, ReadPrec [RequestDeskEdit]
ReadPrec RequestDeskEdit
Int -> ReadS RequestDeskEdit
ReadS [RequestDeskEdit]
(Int -> ReadS RequestDeskEdit)
-> ReadS [RequestDeskEdit]
-> ReadPrec RequestDeskEdit
-> ReadPrec [RequestDeskEdit]
-> Read RequestDeskEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestDeskEdit
readsPrec :: Int -> ReadS RequestDeskEdit
$creadList :: ReadS [RequestDeskEdit]
readList :: ReadS [RequestDeskEdit]
$creadPrec :: ReadPrec RequestDeskEdit
readPrec :: ReadPrec RequestDeskEdit
$creadListPrec :: ReadPrec [RequestDeskEdit]
readListPrec :: ReadPrec [RequestDeskEdit]
Read, Int -> RequestDeskEdit -> ShowS
[RequestDeskEdit] -> ShowS
RequestDeskEdit -> String
(Int -> RequestDeskEdit -> ShowS)
-> (RequestDeskEdit -> String)
-> ([RequestDeskEdit] -> ShowS)
-> Show RequestDeskEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestDeskEdit -> ShowS
showsPrec :: Int -> RequestDeskEdit -> ShowS
$cshow :: RequestDeskEdit -> String
show :: RequestDeskEdit -> String
$cshowList :: [RequestDeskEdit] -> ShowS
showList :: [RequestDeskEdit] -> ShowS
Show)
deriving
(Value -> Parser [RequestDeskEdit]
Value -> Parser RequestDeskEdit
(Value -> Parser RequestDeskEdit)
-> (Value -> Parser [RequestDeskEdit]) -> FromJSON RequestDeskEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestDeskEdit
parseJSON :: Value -> Parser RequestDeskEdit
$cparseJSONList :: Value -> Parser [RequestDeskEdit]
parseJSONList :: Value -> Parser [RequestDeskEdit]
A.FromJSON, [RequestDeskEdit] -> Value
[RequestDeskEdit] -> Encoding
RequestDeskEdit -> Value
RequestDeskEdit -> Encoding
(RequestDeskEdit -> Value)
-> (RequestDeskEdit -> Encoding)
-> ([RequestDeskEdit] -> Value)
-> ([RequestDeskEdit] -> Encoding)
-> ToJSON RequestDeskEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestDeskEdit -> Value
toJSON :: RequestDeskEdit -> Value
$ctoEncoding :: RequestDeskEdit -> Encoding
toEncoding :: RequestDeskEdit -> Encoding
$ctoJSONList :: [RequestDeskEdit] -> Value
toJSONList :: [RequestDeskEdit] -> Value
$ctoEncodingList :: [RequestDeskEdit] -> Encoding
toEncodingList :: [RequestDeskEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestDeskEdit") RequestDeskEdit
type ResponseDeskEdit :: Type
newtype ResponseDeskEdit = MkResponseDeskEdit
{ ResponseDeskEdit -> ()
responseDeskEditUnit :: ()
}
deriving stock (ResponseDeskEdit -> ResponseDeskEdit -> Bool
(ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> (ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> Eq ResponseDeskEdit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
== :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
$c/= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
/= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
Eq, (forall x. ResponseDeskEdit -> Rep ResponseDeskEdit x)
-> (forall x. Rep ResponseDeskEdit x -> ResponseDeskEdit)
-> Generic ResponseDeskEdit
forall x. Rep ResponseDeskEdit x -> ResponseDeskEdit
forall x. ResponseDeskEdit -> Rep ResponseDeskEdit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseDeskEdit -> Rep ResponseDeskEdit x
from :: forall x. ResponseDeskEdit -> Rep ResponseDeskEdit x
$cto :: forall x. Rep ResponseDeskEdit x -> ResponseDeskEdit
to :: forall x. Rep ResponseDeskEdit x -> ResponseDeskEdit
Generic, Eq ResponseDeskEdit
Eq ResponseDeskEdit =>
(ResponseDeskEdit -> ResponseDeskEdit -> Ordering)
-> (ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> (ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> (ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> (ResponseDeskEdit -> ResponseDeskEdit -> Bool)
-> (ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit)
-> (ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit)
-> Ord ResponseDeskEdit
ResponseDeskEdit -> ResponseDeskEdit -> Bool
ResponseDeskEdit -> ResponseDeskEdit -> Ordering
ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit
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 :: ResponseDeskEdit -> ResponseDeskEdit -> Ordering
compare :: ResponseDeskEdit -> ResponseDeskEdit -> Ordering
$c< :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
< :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
$c<= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
<= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
$c> :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
> :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
$c>= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
>= :: ResponseDeskEdit -> ResponseDeskEdit -> Bool
$cmax :: ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit
max :: ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit
$cmin :: ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit
min :: ResponseDeskEdit -> ResponseDeskEdit -> ResponseDeskEdit
Ord, ReadPrec [ResponseDeskEdit]
ReadPrec ResponseDeskEdit
Int -> ReadS ResponseDeskEdit
ReadS [ResponseDeskEdit]
(Int -> ReadS ResponseDeskEdit)
-> ReadS [ResponseDeskEdit]
-> ReadPrec ResponseDeskEdit
-> ReadPrec [ResponseDeskEdit]
-> Read ResponseDeskEdit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseDeskEdit
readsPrec :: Int -> ReadS ResponseDeskEdit
$creadList :: ReadS [ResponseDeskEdit]
readList :: ReadS [ResponseDeskEdit]
$creadPrec :: ReadPrec ResponseDeskEdit
readPrec :: ReadPrec ResponseDeskEdit
$creadListPrec :: ReadPrec [ResponseDeskEdit]
readListPrec :: ReadPrec [ResponseDeskEdit]
Read, Int -> ResponseDeskEdit -> ShowS
[ResponseDeskEdit] -> ShowS
ResponseDeskEdit -> String
(Int -> ResponseDeskEdit -> ShowS)
-> (ResponseDeskEdit -> String)
-> ([ResponseDeskEdit] -> ShowS)
-> Show ResponseDeskEdit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseDeskEdit -> ShowS
showsPrec :: Int -> ResponseDeskEdit -> ShowS
$cshow :: ResponseDeskEdit -> String
show :: ResponseDeskEdit -> String
$cshowList :: [ResponseDeskEdit] -> ShowS
showList :: [ResponseDeskEdit] -> ShowS
Show)
deriving
(Value -> Parser [ResponseDeskEdit]
Value -> Parser ResponseDeskEdit
(Value -> Parser ResponseDeskEdit)
-> (Value -> Parser [ResponseDeskEdit])
-> FromJSON ResponseDeskEdit
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseDeskEdit
parseJSON :: Value -> Parser ResponseDeskEdit
$cparseJSONList :: Value -> Parser [ResponseDeskEdit]
parseJSONList :: Value -> Parser [ResponseDeskEdit]
A.FromJSON, [ResponseDeskEdit] -> Value
[ResponseDeskEdit] -> Encoding
ResponseDeskEdit -> Value
ResponseDeskEdit -> Encoding
(ResponseDeskEdit -> Value)
-> (ResponseDeskEdit -> Encoding)
-> ([ResponseDeskEdit] -> Value)
-> ([ResponseDeskEdit] -> Encoding)
-> ToJSON ResponseDeskEdit
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseDeskEdit -> Value
toJSON :: ResponseDeskEdit -> Value
$ctoEncoding :: ResponseDeskEdit -> Encoding
toEncoding :: ResponseDeskEdit -> Encoding
$ctoJSONList :: [ResponseDeskEdit] -> Value
toJSONList :: [ResponseDeskEdit] -> Value
$ctoEncodingList :: [ResponseDeskEdit] -> Encoding
toEncodingList :: [ResponseDeskEdit] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseDeskEdit") ResponseDeskEdit
type RequestDeskList :: Type
data RequestDeskList = MkRequestDeskList
{ RequestDeskList -> NameOrIdentifier NameSpace IdentifierSpace
requestDeskListSpace :: NameOrIdentifier NameSpace IdentifierSpace
, RequestDeskList -> IntervalUnbounded UTCTime
requestDeskListTimeWindow :: IntervalUnbounded T.UTCTime
}
deriving stock (RequestDeskList -> RequestDeskList -> Bool
(RequestDeskList -> RequestDeskList -> Bool)
-> (RequestDeskList -> RequestDeskList -> Bool)
-> Eq RequestDeskList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestDeskList -> RequestDeskList -> Bool
== :: RequestDeskList -> RequestDeskList -> Bool
$c/= :: RequestDeskList -> RequestDeskList -> Bool
/= :: RequestDeskList -> RequestDeskList -> Bool
Eq, (forall x. RequestDeskList -> Rep RequestDeskList x)
-> (forall x. Rep RequestDeskList x -> RequestDeskList)
-> Generic RequestDeskList
forall x. Rep RequestDeskList x -> RequestDeskList
forall x. RequestDeskList -> Rep RequestDeskList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RequestDeskList -> Rep RequestDeskList x
from :: forall x. RequestDeskList -> Rep RequestDeskList x
$cto :: forall x. Rep RequestDeskList x -> RequestDeskList
to :: forall x. Rep RequestDeskList x -> RequestDeskList
Generic, Eq RequestDeskList
Eq RequestDeskList =>
(RequestDeskList -> RequestDeskList -> Ordering)
-> (RequestDeskList -> RequestDeskList -> Bool)
-> (RequestDeskList -> RequestDeskList -> Bool)
-> (RequestDeskList -> RequestDeskList -> Bool)
-> (RequestDeskList -> RequestDeskList -> Bool)
-> (RequestDeskList -> RequestDeskList -> RequestDeskList)
-> (RequestDeskList -> RequestDeskList -> RequestDeskList)
-> Ord RequestDeskList
RequestDeskList -> RequestDeskList -> Bool
RequestDeskList -> RequestDeskList -> Ordering
RequestDeskList -> RequestDeskList -> RequestDeskList
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 :: RequestDeskList -> RequestDeskList -> Ordering
compare :: RequestDeskList -> RequestDeskList -> Ordering
$c< :: RequestDeskList -> RequestDeskList -> Bool
< :: RequestDeskList -> RequestDeskList -> Bool
$c<= :: RequestDeskList -> RequestDeskList -> Bool
<= :: RequestDeskList -> RequestDeskList -> Bool
$c> :: RequestDeskList -> RequestDeskList -> Bool
> :: RequestDeskList -> RequestDeskList -> Bool
$c>= :: RequestDeskList -> RequestDeskList -> Bool
>= :: RequestDeskList -> RequestDeskList -> Bool
$cmax :: RequestDeskList -> RequestDeskList -> RequestDeskList
max :: RequestDeskList -> RequestDeskList -> RequestDeskList
$cmin :: RequestDeskList -> RequestDeskList -> RequestDeskList
min :: RequestDeskList -> RequestDeskList -> RequestDeskList
Ord, ReadPrec [RequestDeskList]
ReadPrec RequestDeskList
Int -> ReadS RequestDeskList
ReadS [RequestDeskList]
(Int -> ReadS RequestDeskList)
-> ReadS [RequestDeskList]
-> ReadPrec RequestDeskList
-> ReadPrec [RequestDeskList]
-> Read RequestDeskList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RequestDeskList
readsPrec :: Int -> ReadS RequestDeskList
$creadList :: ReadS [RequestDeskList]
readList :: ReadS [RequestDeskList]
$creadPrec :: ReadPrec RequestDeskList
readPrec :: ReadPrec RequestDeskList
$creadListPrec :: ReadPrec [RequestDeskList]
readListPrec :: ReadPrec [RequestDeskList]
Read, Int -> RequestDeskList -> ShowS
[RequestDeskList] -> ShowS
RequestDeskList -> String
(Int -> RequestDeskList -> ShowS)
-> (RequestDeskList -> String)
-> ([RequestDeskList] -> ShowS)
-> Show RequestDeskList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestDeskList -> ShowS
showsPrec :: Int -> RequestDeskList -> ShowS
$cshow :: RequestDeskList -> String
show :: RequestDeskList -> String
$cshowList :: [RequestDeskList] -> ShowS
showList :: [RequestDeskList] -> ShowS
Show)
deriving
(Value -> Parser [RequestDeskList]
Value -> Parser RequestDeskList
(Value -> Parser RequestDeskList)
-> (Value -> Parser [RequestDeskList]) -> FromJSON RequestDeskList
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser RequestDeskList
parseJSON :: Value -> Parser RequestDeskList
$cparseJSONList :: Value -> Parser [RequestDeskList]
parseJSONList :: Value -> Parser [RequestDeskList]
A.FromJSON, [RequestDeskList] -> Value
[RequestDeskList] -> Encoding
RequestDeskList -> Value
RequestDeskList -> Encoding
(RequestDeskList -> Value)
-> (RequestDeskList -> Encoding)
-> ([RequestDeskList] -> Value)
-> ([RequestDeskList] -> Encoding)
-> ToJSON RequestDeskList
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: RequestDeskList -> Value
toJSON :: RequestDeskList -> Value
$ctoEncoding :: RequestDeskList -> Encoding
toEncoding :: RequestDeskList -> Encoding
$ctoJSONList :: [RequestDeskList] -> Value
toJSONList :: [RequestDeskList] -> Value
$ctoEncodingList :: [RequestDeskList] -> Encoding
toEncodingList :: [RequestDeskList] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkRequest" "requestDeskList") RequestDeskList
type DeskWithInfo :: Type
data DeskWithInfo = MkDeskWithInfo
{ DeskWithInfo -> Desk
deskWithInfoDesk :: Desk
, DeskWithInfo -> [Reservation]
deskWithInfoReservations :: [Reservation]
}
deriving stock (DeskWithInfo -> DeskWithInfo -> Bool
(DeskWithInfo -> DeskWithInfo -> Bool)
-> (DeskWithInfo -> DeskWithInfo -> Bool) -> Eq DeskWithInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeskWithInfo -> DeskWithInfo -> Bool
== :: DeskWithInfo -> DeskWithInfo -> Bool
$c/= :: DeskWithInfo -> DeskWithInfo -> Bool
/= :: DeskWithInfo -> DeskWithInfo -> Bool
Eq, (forall x. DeskWithInfo -> Rep DeskWithInfo x)
-> (forall x. Rep DeskWithInfo x -> DeskWithInfo)
-> Generic DeskWithInfo
forall x. Rep DeskWithInfo x -> DeskWithInfo
forall x. DeskWithInfo -> Rep DeskWithInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DeskWithInfo -> Rep DeskWithInfo x
from :: forall x. DeskWithInfo -> Rep DeskWithInfo x
$cto :: forall x. Rep DeskWithInfo x -> DeskWithInfo
to :: forall x. Rep DeskWithInfo x -> DeskWithInfo
Generic, Eq DeskWithInfo
Eq DeskWithInfo =>
(DeskWithInfo -> DeskWithInfo -> Ordering)
-> (DeskWithInfo -> DeskWithInfo -> Bool)
-> (DeskWithInfo -> DeskWithInfo -> Bool)
-> (DeskWithInfo -> DeskWithInfo -> Bool)
-> (DeskWithInfo -> DeskWithInfo -> Bool)
-> (DeskWithInfo -> DeskWithInfo -> DeskWithInfo)
-> (DeskWithInfo -> DeskWithInfo -> DeskWithInfo)
-> Ord DeskWithInfo
DeskWithInfo -> DeskWithInfo -> Bool
DeskWithInfo -> DeskWithInfo -> Ordering
DeskWithInfo -> DeskWithInfo -> DeskWithInfo
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 :: DeskWithInfo -> DeskWithInfo -> Ordering
compare :: DeskWithInfo -> DeskWithInfo -> Ordering
$c< :: DeskWithInfo -> DeskWithInfo -> Bool
< :: DeskWithInfo -> DeskWithInfo -> Bool
$c<= :: DeskWithInfo -> DeskWithInfo -> Bool
<= :: DeskWithInfo -> DeskWithInfo -> Bool
$c> :: DeskWithInfo -> DeskWithInfo -> Bool
> :: DeskWithInfo -> DeskWithInfo -> Bool
$c>= :: DeskWithInfo -> DeskWithInfo -> Bool
>= :: DeskWithInfo -> DeskWithInfo -> Bool
$cmax :: DeskWithInfo -> DeskWithInfo -> DeskWithInfo
max :: DeskWithInfo -> DeskWithInfo -> DeskWithInfo
$cmin :: DeskWithInfo -> DeskWithInfo -> DeskWithInfo
min :: DeskWithInfo -> DeskWithInfo -> DeskWithInfo
Ord, ReadPrec [DeskWithInfo]
ReadPrec DeskWithInfo
Int -> ReadS DeskWithInfo
ReadS [DeskWithInfo]
(Int -> ReadS DeskWithInfo)
-> ReadS [DeskWithInfo]
-> ReadPrec DeskWithInfo
-> ReadPrec [DeskWithInfo]
-> Read DeskWithInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DeskWithInfo
readsPrec :: Int -> ReadS DeskWithInfo
$creadList :: ReadS [DeskWithInfo]
readList :: ReadS [DeskWithInfo]
$creadPrec :: ReadPrec DeskWithInfo
readPrec :: ReadPrec DeskWithInfo
$creadListPrec :: ReadPrec [DeskWithInfo]
readListPrec :: ReadPrec [DeskWithInfo]
Read, Int -> DeskWithInfo -> ShowS
[DeskWithInfo] -> ShowS
DeskWithInfo -> String
(Int -> DeskWithInfo -> ShowS)
-> (DeskWithInfo -> String)
-> ([DeskWithInfo] -> ShowS)
-> Show DeskWithInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeskWithInfo -> ShowS
showsPrec :: Int -> DeskWithInfo -> ShowS
$cshow :: DeskWithInfo -> String
show :: DeskWithInfo -> String
$cshowList :: [DeskWithInfo] -> ShowS
showList :: [DeskWithInfo] -> ShowS
Show)
deriving
(Value -> Parser [DeskWithInfo]
Value -> Parser DeskWithInfo
(Value -> Parser DeskWithInfo)
-> (Value -> Parser [DeskWithInfo]) -> FromJSON DeskWithInfo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser DeskWithInfo
parseJSON :: Value -> Parser DeskWithInfo
$cparseJSONList :: Value -> Parser [DeskWithInfo]
parseJSONList :: Value -> Parser [DeskWithInfo]
A.FromJSON, [DeskWithInfo] -> Value
[DeskWithInfo] -> Encoding
DeskWithInfo -> Value
DeskWithInfo -> Encoding
(DeskWithInfo -> Value)
-> (DeskWithInfo -> Encoding)
-> ([DeskWithInfo] -> Value)
-> ([DeskWithInfo] -> Encoding)
-> ToJSON DeskWithInfo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: DeskWithInfo -> Value
toJSON :: DeskWithInfo -> Value
$ctoEncoding :: DeskWithInfo -> Encoding
toEncoding :: DeskWithInfo -> Encoding
$ctoJSONList :: [DeskWithInfo] -> Value
toJSONList :: [DeskWithInfo] -> Value
$ctoEncodingList :: [DeskWithInfo] -> Encoding
toEncodingList :: [DeskWithInfo] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "Mk" "deskWithInfo") DeskWithInfo
type ResponseDeskList :: Type
newtype ResponseDeskList = MkResponseDeskList
{ ResponseDeskList -> [DeskWithInfo]
responseDeskListDesks :: [DeskWithInfo]
}
deriving stock (ResponseDeskList -> ResponseDeskList -> Bool
(ResponseDeskList -> ResponseDeskList -> Bool)
-> (ResponseDeskList -> ResponseDeskList -> Bool)
-> Eq ResponseDeskList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseDeskList -> ResponseDeskList -> Bool
== :: ResponseDeskList -> ResponseDeskList -> Bool
$c/= :: ResponseDeskList -> ResponseDeskList -> Bool
/= :: ResponseDeskList -> ResponseDeskList -> Bool
Eq, (forall x. ResponseDeskList -> Rep ResponseDeskList x)
-> (forall x. Rep ResponseDeskList x -> ResponseDeskList)
-> Generic ResponseDeskList
forall x. Rep ResponseDeskList x -> ResponseDeskList
forall x. ResponseDeskList -> Rep ResponseDeskList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseDeskList -> Rep ResponseDeskList x
from :: forall x. ResponseDeskList -> Rep ResponseDeskList x
$cto :: forall x. Rep ResponseDeskList x -> ResponseDeskList
to :: forall x. Rep ResponseDeskList x -> ResponseDeskList
Generic, Eq ResponseDeskList
Eq ResponseDeskList =>
(ResponseDeskList -> ResponseDeskList -> Ordering)
-> (ResponseDeskList -> ResponseDeskList -> Bool)
-> (ResponseDeskList -> ResponseDeskList -> Bool)
-> (ResponseDeskList -> ResponseDeskList -> Bool)
-> (ResponseDeskList -> ResponseDeskList -> Bool)
-> (ResponseDeskList -> ResponseDeskList -> ResponseDeskList)
-> (ResponseDeskList -> ResponseDeskList -> ResponseDeskList)
-> Ord ResponseDeskList
ResponseDeskList -> ResponseDeskList -> Bool
ResponseDeskList -> ResponseDeskList -> Ordering
ResponseDeskList -> ResponseDeskList -> ResponseDeskList
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 :: ResponseDeskList -> ResponseDeskList -> Ordering
compare :: ResponseDeskList -> ResponseDeskList -> Ordering
$c< :: ResponseDeskList -> ResponseDeskList -> Bool
< :: ResponseDeskList -> ResponseDeskList -> Bool
$c<= :: ResponseDeskList -> ResponseDeskList -> Bool
<= :: ResponseDeskList -> ResponseDeskList -> Bool
$c> :: ResponseDeskList -> ResponseDeskList -> Bool
> :: ResponseDeskList -> ResponseDeskList -> Bool
$c>= :: ResponseDeskList -> ResponseDeskList -> Bool
>= :: ResponseDeskList -> ResponseDeskList -> Bool
$cmax :: ResponseDeskList -> ResponseDeskList -> ResponseDeskList
max :: ResponseDeskList -> ResponseDeskList -> ResponseDeskList
$cmin :: ResponseDeskList -> ResponseDeskList -> ResponseDeskList
min :: ResponseDeskList -> ResponseDeskList -> ResponseDeskList
Ord, ReadPrec [ResponseDeskList]
ReadPrec ResponseDeskList
Int -> ReadS ResponseDeskList
ReadS [ResponseDeskList]
(Int -> ReadS ResponseDeskList)
-> ReadS [ResponseDeskList]
-> ReadPrec ResponseDeskList
-> ReadPrec [ResponseDeskList]
-> Read ResponseDeskList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ResponseDeskList
readsPrec :: Int -> ReadS ResponseDeskList
$creadList :: ReadS [ResponseDeskList]
readList :: ReadS [ResponseDeskList]
$creadPrec :: ReadPrec ResponseDeskList
readPrec :: ReadPrec ResponseDeskList
$creadListPrec :: ReadPrec [ResponseDeskList]
readListPrec :: ReadPrec [ResponseDeskList]
Read, Int -> ResponseDeskList -> ShowS
[ResponseDeskList] -> ShowS
ResponseDeskList -> String
(Int -> ResponseDeskList -> ShowS)
-> (ResponseDeskList -> String)
-> ([ResponseDeskList] -> ShowS)
-> Show ResponseDeskList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseDeskList -> ShowS
showsPrec :: Int -> ResponseDeskList -> ShowS
$cshow :: ResponseDeskList -> String
show :: ResponseDeskList -> String
$cshowList :: [ResponseDeskList] -> ShowS
showList :: [ResponseDeskList] -> ShowS
Show)
deriving
(Value -> Parser [ResponseDeskList]
Value -> Parser ResponseDeskList
(Value -> Parser ResponseDeskList)
-> (Value -> Parser [ResponseDeskList])
-> FromJSON ResponseDeskList
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ResponseDeskList
parseJSON :: Value -> Parser ResponseDeskList
$cparseJSONList :: Value -> Parser [ResponseDeskList]
parseJSONList :: Value -> Parser [ResponseDeskList]
A.FromJSON, [ResponseDeskList] -> Value
[ResponseDeskList] -> Encoding
ResponseDeskList -> Value
ResponseDeskList -> Encoding
(ResponseDeskList -> Value)
-> (ResponseDeskList -> Encoding)
-> ([ResponseDeskList] -> Value)
-> ([ResponseDeskList] -> Encoding)
-> ToJSON ResponseDeskList
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ResponseDeskList -> Value
toJSON :: ResponseDeskList -> Value
$ctoEncoding :: ResponseDeskList -> Encoding
toEncoding :: ResponseDeskList -> Encoding
$ctoJSONList :: [ResponseDeskList] -> Value
toJSONList :: [ResponseDeskList] -> Value
$ctoEncodingList :: [ResponseDeskList] -> Encoding
toEncodingList :: [ResponseDeskList] -> Encoding
A.ToJSON)
via A.CustomJSON (JSONSettings "MkResponse" "responseDeskList") ResponseDeskList