module Temporal.Operator where
import Control.Monad
import Control.Monad.IO.Class
import Data.Map.Strict (Map)
import Data.ProtoLens (Message (defMessage))
import Data.Text (Text)
import Lens.Family2
import qualified Proto.Temporal.Api.Enums.V1.Common as Proto
import qualified Proto.Temporal.Api.Operatorservice.V1.RequestResponse_Fields as Proto
import Temporal.Core.Client
import qualified Temporal.Core.Client.OperatorService as Core
import Temporal.SearchAttributes (SearchAttributeKey (..))
import Temporal.SearchAttributes.Internal
import Temporal.Workflow (Namespace (..))
data IndexedValueType
= Text
| Keyword
| Int
| Double
| Bool
| Datetime
| KeywordList
| UnrecognizedIndexedValueType
deriving stock (IndexedValueType -> IndexedValueType -> Bool
(IndexedValueType -> IndexedValueType -> Bool)
-> (IndexedValueType -> IndexedValueType -> Bool)
-> Eq IndexedValueType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexedValueType -> IndexedValueType -> Bool
== :: IndexedValueType -> IndexedValueType -> Bool
$c/= :: IndexedValueType -> IndexedValueType -> Bool
/= :: IndexedValueType -> IndexedValueType -> Bool
Eq, Int -> IndexedValueType -> ShowS
[IndexedValueType] -> ShowS
IndexedValueType -> String
(Int -> IndexedValueType -> ShowS)
-> (IndexedValueType -> String)
-> ([IndexedValueType] -> ShowS)
-> Show IndexedValueType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexedValueType -> ShowS
showsPrec :: Int -> IndexedValueType -> ShowS
$cshow :: IndexedValueType -> String
show :: IndexedValueType -> String
$cshowList :: [IndexedValueType] -> ShowS
showList :: [IndexedValueType] -> ShowS
Show)
data SearchAttributes = SearchAttributes
{ SearchAttributes -> Map SearchAttributeKey IndexedValueType
customAttributes :: Map SearchAttributeKey IndexedValueType
, SearchAttributes -> Map SearchAttributeKey IndexedValueType
systemAttributes :: Map SearchAttributeKey IndexedValueType
, SearchAttributes -> Map Text Text
storageSchema :: Map Text Text
}
searchAttributeTypeFromProto :: Proto.IndexedValueType -> IndexedValueType
searchAttributeTypeFromProto :: IndexedValueType -> IndexedValueType
searchAttributeTypeFromProto = \case
IndexedValueType
Proto.INDEXED_VALUE_TYPE_UNSPECIFIED -> IndexedValueType
UnrecognizedIndexedValueType
IndexedValueType
Proto.INDEXED_VALUE_TYPE_TEXT -> IndexedValueType
Text
IndexedValueType
Proto.INDEXED_VALUE_TYPE_KEYWORD -> IndexedValueType
Keyword
IndexedValueType
Proto.INDEXED_VALUE_TYPE_INT -> IndexedValueType
Int
IndexedValueType
Proto.INDEXED_VALUE_TYPE_DOUBLE -> IndexedValueType
Double
IndexedValueType
Proto.INDEXED_VALUE_TYPE_BOOL -> IndexedValueType
Bool
IndexedValueType
Proto.INDEXED_VALUE_TYPE_DATETIME -> IndexedValueType
Datetime
IndexedValueType
Proto.INDEXED_VALUE_TYPE_KEYWORD_LIST -> IndexedValueType
KeywordList
(Proto.IndexedValueType'Unrecognized IndexedValueType'UnrecognizedValue
_) -> IndexedValueType
UnrecognizedIndexedValueType
searchAttributeTypeToProto :: IndexedValueType -> Proto.IndexedValueType
searchAttributeTypeToProto :: IndexedValueType -> IndexedValueType
searchAttributeTypeToProto = \case
IndexedValueType
UnrecognizedIndexedValueType -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_UNSPECIFIED
IndexedValueType
Text -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_TEXT
IndexedValueType
Keyword -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_KEYWORD
IndexedValueType
Int -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_INT
IndexedValueType
Double -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_DOUBLE
IndexedValueType
Bool -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_BOOL
IndexedValueType
Datetime -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_DATETIME
IndexedValueType
KeywordList -> IndexedValueType
Proto.INDEXED_VALUE_TYPE_KEYWORD_LIST
listSearchAttributes :: MonadIO m => Client -> Namespace -> m (Either RpcError SearchAttributes)
listSearchAttributes :: forall (m :: * -> *).
MonadIO m =>
Client -> Namespace -> m (Either RpcError SearchAttributes)
listSearchAttributes Client
c (Namespace Text
n) = do
res <- IO (Either RpcError ListSearchAttributesResponse)
-> m (Either RpcError ListSearchAttributesResponse)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either RpcError ListSearchAttributesResponse)
-> m (Either RpcError ListSearchAttributesResponse))
-> IO (Either RpcError ListSearchAttributesResponse)
-> m (Either RpcError ListSearchAttributesResponse)
forall a b. (a -> b) -> a -> b
$ Client
-> ListSearchAttributesRequest
-> IO (Either RpcError ListSearchAttributesResponse)
Core.listSearchAttributes Client
c (ListSearchAttributesRequest
forall msg. Message msg => msg
defMessage ListSearchAttributesRequest
-> (ListSearchAttributesRequest -> ListSearchAttributesRequest)
-> ListSearchAttributesRequest
forall s t. s -> (s -> t) -> t
& LensLike' f ListSearchAttributesRequest Text
forall {f :: * -> *}.
Identical f =>
LensLike' f ListSearchAttributesRequest Text
forall (f :: * -> *) s a.
(Functor f, HasField s "namespace" a) =>
LensLike' f s a
Proto.namespace (forall {f :: * -> *}.
Identical f =>
LensLike' f ListSearchAttributesRequest Text)
-> Text
-> ListSearchAttributesRequest
-> ListSearchAttributesRequest
forall s t a b. Setter s t a b -> b -> s -> t
.~ Text
n)
pure $ fmap convert res
where
convert :: t -> SearchAttributes
convert t
res =
SearchAttributes
{ customAttributes :: Map SearchAttributeKey IndexedValueType
customAttributes = Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType
forall a. Map Text a -> Map SearchAttributeKey a
wrappedKeys (Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType)
-> Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType
forall a b. (a -> b) -> a -> b
$ (IndexedValueType -> IndexedValueType)
-> Map Text IndexedValueType -> Map Text IndexedValueType
forall a b. (a -> b) -> Map Text a -> Map Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IndexedValueType -> IndexedValueType
searchAttributeTypeFromProto (Map Text IndexedValueType -> Map Text IndexedValueType)
-> Map Text IndexedValueType -> Map Text IndexedValueType
forall a b. (a -> b) -> a -> b
$ t
res t
-> FoldLike
(Map Text IndexedValueType)
t
t
(Map Text IndexedValueType)
(Map Text IndexedValueType)
-> Map Text IndexedValueType
forall s a t b. s -> FoldLike a s t a b -> a
^. FoldLike
(Map Text IndexedValueType)
t
t
(Map Text IndexedValueType)
(Map Text IndexedValueType)
forall (f :: * -> *) s a.
(Functor f, HasField s "customAttributes" a) =>
LensLike' f s a
Proto.customAttributes
, systemAttributes :: Map SearchAttributeKey IndexedValueType
systemAttributes = Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType
forall a. Map Text a -> Map SearchAttributeKey a
wrappedKeys (Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType)
-> Map Text IndexedValueType
-> Map SearchAttributeKey IndexedValueType
forall a b. (a -> b) -> a -> b
$ (IndexedValueType -> IndexedValueType)
-> Map Text IndexedValueType -> Map Text IndexedValueType
forall a b. (a -> b) -> Map Text a -> Map Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IndexedValueType -> IndexedValueType
searchAttributeTypeFromProto (Map Text IndexedValueType -> Map Text IndexedValueType)
-> Map Text IndexedValueType -> Map Text IndexedValueType
forall a b. (a -> b) -> a -> b
$ t
res t
-> FoldLike
(Map Text IndexedValueType)
t
t
(Map Text IndexedValueType)
(Map Text IndexedValueType)
-> Map Text IndexedValueType
forall s a t b. s -> FoldLike a s t a b -> a
^. FoldLike
(Map Text IndexedValueType)
t
t
(Map Text IndexedValueType)
(Map Text IndexedValueType)
forall (f :: * -> *) s a.
(Functor f, HasField s "systemAttributes" a) =>
LensLike' f s a
Proto.systemAttributes
, storageSchema :: Map Text Text
storageSchema = t
res t
-> FoldLike (Map Text Text) t t (Map Text Text) (Map Text Text)
-> Map Text Text
forall s a t b. s -> FoldLike a s t a b -> a
^. FoldLike (Map Text Text) t t (Map Text Text) (Map Text Text)
forall (f :: * -> *) s a.
(Functor f, HasField s "storageSchema" a) =>
LensLike' f s a
Proto.storageSchema
}
addSearchAttributes :: MonadIO m => Client -> Namespace -> Map SearchAttributeKey IndexedValueType -> m (Either RpcError ())
addSearchAttributes :: forall (m :: * -> *).
MonadIO m =>
Client
-> Namespace
-> Map SearchAttributeKey IndexedValueType
-> m (Either RpcError ())
addSearchAttributes Client
c (Namespace Text
n) Map SearchAttributeKey IndexedValueType
newAttrs = do
if Map SearchAttributeKey IndexedValueType -> Bool
forall a. Map SearchAttributeKey a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map SearchAttributeKey IndexedValueType
newAttrs
then Either RpcError () -> m (Either RpcError ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either RpcError () -> m (Either RpcError ()))
-> Either RpcError () -> m (Either RpcError ())
forall a b. (a -> b) -> a -> b
$ () -> Either RpcError ()
forall a b. b -> Either a b
Right ()
else do
res <-
IO (Either RpcError AddSearchAttributesResponse)
-> m (Either RpcError AddSearchAttributesResponse)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either RpcError AddSearchAttributesResponse)
-> m (Either RpcError AddSearchAttributesResponse))
-> IO (Either RpcError AddSearchAttributesResponse)
-> m (Either RpcError AddSearchAttributesResponse)
forall a b. (a -> b) -> a -> b
$
Client
-> AddSearchAttributesRequest
-> IO (Either RpcError AddSearchAttributesResponse)
Core.addSearchAttributes
Client
c
( AddSearchAttributesRequest
forall msg. Message msg => msg
defMessage
AddSearchAttributesRequest
-> (AddSearchAttributesRequest -> AddSearchAttributesRequest)
-> AddSearchAttributesRequest
forall s t. s -> (s -> t) -> t
& LensLike' f AddSearchAttributesRequest Text
forall {f :: * -> *}.
Identical f =>
LensLike' f AddSearchAttributesRequest Text
forall (f :: * -> *) s a.
(Functor f, HasField s "namespace" a) =>
LensLike' f s a
Proto.namespace (forall {f :: * -> *}.
Identical f =>
LensLike' f AddSearchAttributesRequest Text)
-> Text -> AddSearchAttributesRequest -> AddSearchAttributesRequest
forall s t a b. Setter s t a b -> b -> s -> t
.~ Text
n
AddSearchAttributesRequest
-> (AddSearchAttributesRequest -> AddSearchAttributesRequest)
-> AddSearchAttributesRequest
forall s t. s -> (s -> t) -> t
& LensLike' f AddSearchAttributesRequest (Map Text IndexedValueType)
forall {f :: * -> *}.
Identical f =>
LensLike' f AddSearchAttributesRequest (Map Text IndexedValueType)
forall (f :: * -> *) s a.
(Functor f, HasField s "searchAttributes" a) =>
LensLike' f s a
Proto.searchAttributes (forall {f :: * -> *}.
Identical f =>
LensLike' f AddSearchAttributesRequest (Map Text IndexedValueType))
-> Map Text IndexedValueType
-> AddSearchAttributesRequest
-> AddSearchAttributesRequest
forall s t a b. Setter s t a b -> b -> s -> t
.~ Map Text IndexedValueType
converted
)
pure $ void res
where
converted :: Map Text IndexedValueType
converted = Map SearchAttributeKey IndexedValueType
-> Map Text IndexedValueType
forall a. Map SearchAttributeKey a -> Map Text a
rawKeys (Map SearchAttributeKey IndexedValueType
-> Map Text IndexedValueType)
-> Map SearchAttributeKey IndexedValueType
-> Map Text IndexedValueType
forall a b. (a -> b) -> a -> b
$ (IndexedValueType -> IndexedValueType)
-> Map SearchAttributeKey IndexedValueType
-> Map SearchAttributeKey IndexedValueType
forall a b.
(a -> b) -> Map SearchAttributeKey a -> Map SearchAttributeKey b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IndexedValueType -> IndexedValueType
searchAttributeTypeToProto Map SearchAttributeKey IndexedValueType
newAttrs