module Temporal.SearchAttributes.Internal where
import Control.Monad.Except
import Data.Coerce
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import qualified Proto.Temporal.Api.Common.V1.Message as Message
import Temporal.Payload
import Temporal.SearchAttributes
import Unsafe.Coerce (unsafeCoerce)
unsafeCoerceMapKeys :: forall a b c. Coercible a b => Map.Map a c -> Map.Map b c
unsafeCoerceMapKeys :: forall a b c. Coercible a b => Map a c -> Map b c
unsafeCoerceMapKeys = Map a c -> Map b c
forall a b. a -> b
unsafeCoerce
rawKeys :: Map.Map SearchAttributeKey a -> Map.Map Text a
rawKeys :: forall a. Map SearchAttributeKey a -> Map Text a
rawKeys = Map SearchAttributeKey a -> Map Text a
forall a b c. Coercible a b => Map a c -> Map b c
unsafeCoerceMapKeys
wrappedKeys :: Map.Map Text a -> Map.Map SearchAttributeKey a
wrappedKeys :: forall a. Map Text a -> Map SearchAttributeKey a
wrappedKeys = Map Text a -> Map SearchAttributeKey a
forall a b c. Coercible a b => Map a c -> Map b c
unsafeCoerceMapKeys
searchAttributesToProto :: Map.Map SearchAttributeKey SearchAttributeType -> IO (Map.Map Text Message.Payload)
searchAttributesToProto :: Map SearchAttributeKey SearchAttributeType -> IO (Map Text Payload)
searchAttributesToProto = (Map SearchAttributeKey Payload -> Map Text Payload)
-> IO (Map SearchAttributeKey Payload) -> IO (Map Text Payload)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Map SearchAttributeKey Payload -> Map Text Payload
forall a. Map SearchAttributeKey a -> Map Text a
rawKeys (IO (Map SearchAttributeKey Payload) -> IO (Map Text Payload))
-> (Map SearchAttributeKey SearchAttributeType
-> IO (Map SearchAttributeKey Payload))
-> Map SearchAttributeKey SearchAttributeType
-> IO (Map Text Payload)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SearchAttributeType -> IO Payload)
-> Map SearchAttributeKey SearchAttributeType
-> IO (Map SearchAttributeKey Payload)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> Map SearchAttributeKey a -> f (Map SearchAttributeKey b)
traverse ((Payload -> Payload) -> IO Payload -> IO Payload
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Payload -> Payload
convertToProtoPayload (IO Payload -> IO Payload)
-> (SearchAttributeType -> IO Payload)
-> SearchAttributeType
-> IO Payload
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSON -> SearchAttributeType -> IO Payload
forall fmt a. Codec fmt a => fmt -> a -> IO Payload
encode JSON
JSON)
searchAttributesFromProto :: Map.Map Text Message.Payload -> IO (Either String (Map.Map SearchAttributeKey SearchAttributeType))
searchAttributesFromProto :: Map Text Payload
-> IO (Either String (Map SearchAttributeKey SearchAttributeType))
searchAttributesFromProto = (Either String (Map Text SearchAttributeType)
-> Either String (Map SearchAttributeKey SearchAttributeType))
-> IO (Either String (Map Text SearchAttributeType))
-> IO (Either String (Map SearchAttributeKey SearchAttributeType))
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Map Text SearchAttributeType
-> Map SearchAttributeKey SearchAttributeType)
-> Either String (Map Text SearchAttributeType)
-> Either String (Map SearchAttributeKey SearchAttributeType)
forall a b. (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Map Text SearchAttributeType
-> Map SearchAttributeKey SearchAttributeType
forall a. Map Text a -> Map SearchAttributeKey a
wrappedKeys) (IO (Either String (Map Text SearchAttributeType))
-> IO (Either String (Map SearchAttributeKey SearchAttributeType)))
-> (Map Text Payload
-> IO (Either String (Map Text SearchAttributeType)))
-> Map Text Payload
-> IO (Either String (Map SearchAttributeKey SearchAttributeType))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT String IO (Map Text SearchAttributeType)
-> IO (Either String (Map Text SearchAttributeType))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT String IO (Map Text SearchAttributeType)
-> IO (Either String (Map Text SearchAttributeType)))
-> (Map Text Payload
-> ExceptT String IO (Map Text SearchAttributeType))
-> Map Text Payload
-> IO (Either String (Map Text SearchAttributeType))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Payload -> ExceptT String IO SearchAttributeType)
-> Map Text Payload
-> ExceptT String IO (Map Text SearchAttributeType)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Text a -> f (Map Text b)
traverse (IO (Either String SearchAttributeType)
-> ExceptT String IO SearchAttributeType
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either String SearchAttributeType)
-> ExceptT String IO SearchAttributeType)
-> (Payload -> IO (Either String SearchAttributeType))
-> Payload
-> ExceptT String IO SearchAttributeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSON -> Payload -> IO (Either String SearchAttributeType)
forall fmt a. Codec fmt a => fmt -> Payload -> IO (Either String a)
decode JSON
JSON (Payload -> IO (Either String SearchAttributeType))
-> (Payload -> Payload)
-> Payload
-> IO (Either String SearchAttributeType)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Payload -> Payload
convertFromProtoPayload)