{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}

module Temporal.Core.Client.OperatorService where

import Proto.Temporal.Api.Operatorservice.V1.RequestResponse
import Proto.Temporal.Api.Operatorservice.V1.Service
import Temporal.Core.Client
import Temporal.Internal.FFI


foreign import ccall "hs_add_or_update_remote_cluster" hs_add_or_update_remote_cluster :: PrimRpcCall


addOrUpdateRemoteCluster :: Client -> AddOrUpdateRemoteClusterRequest -> IO (Either RpcError AddOrUpdateRemoteClusterResponse)
addOrUpdateRemoteCluster :: Client
-> AddOrUpdateRemoteClusterRequest
-> IO (Either RpcError AddOrUpdateRemoteClusterResponse)
addOrUpdateRemoteCluster = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"addOrUpdateRemoteCluster" PrimRpcCall
hs_add_or_update_remote_cluster


foreign import ccall "hs_add_search_attributes" hs_add_search_attributes :: PrimRpcCall


addSearchAttributes :: Client -> AddSearchAttributesRequest -> IO (Either RpcError AddSearchAttributesResponse)
addSearchAttributes :: Client
-> AddSearchAttributesRequest
-> IO (Either RpcError AddSearchAttributesResponse)
addSearchAttributes = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"addSearchAttributes" PrimRpcCall
hs_add_search_attributes


foreign import ccall "hs_delete_namespace" hs_delete_namespace :: PrimRpcCall


deleteNamespace :: Client -> DeleteNamespaceRequest -> IO (Either RpcError DeleteNamespaceResponse)
deleteNamespace :: Client
-> DeleteNamespaceRequest
-> IO (Either RpcError DeleteNamespaceResponse)
deleteNamespace = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"deleteNamespace" PrimRpcCall
hs_delete_namespace


foreign import ccall "hs_list_clusters" hs_list_clusters :: PrimRpcCall


listClusters :: Client -> ListClustersRequest -> IO (Either RpcError ListClustersResponse)
listClusters :: Client
-> ListClustersRequest -> IO (Either RpcError ListClustersResponse)
listClusters = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"listClusters" PrimRpcCall
hs_list_clusters


foreign import ccall "hs_list_search_attributes" hs_list_search_attributes :: PrimRpcCall


listSearchAttributes :: Client -> ListSearchAttributesRequest -> IO (Either RpcError ListSearchAttributesResponse)
listSearchAttributes :: Client
-> ListSearchAttributesRequest
-> IO (Either RpcError ListSearchAttributesResponse)
listSearchAttributes = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"listSearchAttributes" PrimRpcCall
hs_list_search_attributes


foreign import ccall "hs_remove_remote_cluster" hs_remove_remote_cluster :: PrimRpcCall


removeRemoteCluster :: Client -> RemoveRemoteClusterRequest -> IO (Either RpcError RemoveRemoteClusterResponse)
removeRemoteCluster :: Client
-> RemoveRemoteClusterRequest
-> IO (Either RpcError RemoveRemoteClusterResponse)
removeRemoteCluster = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"removeRemoteCluster" PrimRpcCall
hs_remove_remote_cluster


foreign import ccall "hs_remove_search_attributes" hs_remove_search_attributes :: PrimRpcCall


removeSearchAttributes :: Client -> RemoveSearchAttributesRequest -> IO (Either RpcError RemoveSearchAttributesResponse)
removeSearchAttributes :: Client
-> RemoveSearchAttributesRequest
-> IO (Either RpcError RemoveSearchAttributesResponse)
removeSearchAttributes = forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call @OperatorService @"removeSearchAttributes" PrimRpcCall
hs_remove_search_attributes