{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EMR.UpdateStudioSessionMapping
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the session policy attached to the user or group for the
-- specified Amazon EMR Studio.
module Amazonka.EMR.UpdateStudioSessionMapping
  ( -- * Creating a Request
    UpdateStudioSessionMapping (..),
    newUpdateStudioSessionMapping,

    -- * Request Lenses
    updateStudioSessionMapping_identityId,
    updateStudioSessionMapping_identityName,
    updateStudioSessionMapping_studioId,
    updateStudioSessionMapping_identityType,
    updateStudioSessionMapping_sessionPolicyArn,

    -- * Destructuring the Response
    UpdateStudioSessionMappingResponse (..),
    newUpdateStudioSessionMappingResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMR.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateStudioSessionMapping' smart constructor.
data UpdateStudioSessionMapping = UpdateStudioSessionMapping'
  { -- | The globally unique identifier (GUID) of the user or group. For more
    -- information, see
    -- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserId UserId>
    -- and
    -- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-GroupId GroupId>
    -- in the /IAM Identity Center Identity Store API Reference/. Either
    -- @IdentityName@ or @IdentityId@ must be specified.
    UpdateStudioSessionMapping -> Maybe Text
identityId :: Prelude.Maybe Prelude.Text,
    -- | The name of the user or group to update. For more information, see
    -- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserName UserName>
    -- and
    -- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-DisplayName DisplayName>
    -- in the /IAM Identity Center Identity Store API Reference/. Either
    -- @IdentityName@ or @IdentityId@ must be specified.
    UpdateStudioSessionMapping -> Maybe Text
identityName :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon EMR Studio.
    UpdateStudioSessionMapping -> Text
studioId :: Prelude.Text,
    -- | Specifies whether the identity to update is a user or a group.
    UpdateStudioSessionMapping -> IdentityType
identityType :: IdentityType,
    -- | The Amazon Resource Name (ARN) of the session policy to associate with
    -- the specified user or group.
    UpdateStudioSessionMapping -> Text
sessionPolicyArn :: Prelude.Text
  }
  deriving (UpdateStudioSessionMapping -> UpdateStudioSessionMapping -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateStudioSessionMapping -> UpdateStudioSessionMapping -> Bool
$c/= :: UpdateStudioSessionMapping -> UpdateStudioSessionMapping -> Bool
== :: UpdateStudioSessionMapping -> UpdateStudioSessionMapping -> Bool
$c== :: UpdateStudioSessionMapping -> UpdateStudioSessionMapping -> Bool
Prelude.Eq, ReadPrec [UpdateStudioSessionMapping]
ReadPrec UpdateStudioSessionMapping
Int -> ReadS UpdateStudioSessionMapping
ReadS [UpdateStudioSessionMapping]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateStudioSessionMapping]
$creadListPrec :: ReadPrec [UpdateStudioSessionMapping]
readPrec :: ReadPrec UpdateStudioSessionMapping
$creadPrec :: ReadPrec UpdateStudioSessionMapping
readList :: ReadS [UpdateStudioSessionMapping]
$creadList :: ReadS [UpdateStudioSessionMapping]
readsPrec :: Int -> ReadS UpdateStudioSessionMapping
$creadsPrec :: Int -> ReadS UpdateStudioSessionMapping
Prelude.Read, Int -> UpdateStudioSessionMapping -> ShowS
[UpdateStudioSessionMapping] -> ShowS
UpdateStudioSessionMapping -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateStudioSessionMapping] -> ShowS
$cshowList :: [UpdateStudioSessionMapping] -> ShowS
show :: UpdateStudioSessionMapping -> String
$cshow :: UpdateStudioSessionMapping -> String
showsPrec :: Int -> UpdateStudioSessionMapping -> ShowS
$cshowsPrec :: Int -> UpdateStudioSessionMapping -> ShowS
Prelude.Show, forall x.
Rep UpdateStudioSessionMapping x -> UpdateStudioSessionMapping
forall x.
UpdateStudioSessionMapping -> Rep UpdateStudioSessionMapping x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateStudioSessionMapping x -> UpdateStudioSessionMapping
$cfrom :: forall x.
UpdateStudioSessionMapping -> Rep UpdateStudioSessionMapping x
Prelude.Generic)

-- |
-- Create a value of 'UpdateStudioSessionMapping' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'identityId', 'updateStudioSessionMapping_identityId' - The globally unique identifier (GUID) of the user or group. For more
-- information, see
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserId UserId>
-- and
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-GroupId GroupId>
-- in the /IAM Identity Center Identity Store API Reference/. Either
-- @IdentityName@ or @IdentityId@ must be specified.
--
-- 'identityName', 'updateStudioSessionMapping_identityName' - The name of the user or group to update. For more information, see
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserName UserName>
-- and
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-DisplayName DisplayName>
-- in the /IAM Identity Center Identity Store API Reference/. Either
-- @IdentityName@ or @IdentityId@ must be specified.
--
-- 'studioId', 'updateStudioSessionMapping_studioId' - The ID of the Amazon EMR Studio.
--
-- 'identityType', 'updateStudioSessionMapping_identityType' - Specifies whether the identity to update is a user or a group.
--
-- 'sessionPolicyArn', 'updateStudioSessionMapping_sessionPolicyArn' - The Amazon Resource Name (ARN) of the session policy to associate with
-- the specified user or group.
newUpdateStudioSessionMapping ::
  -- | 'studioId'
  Prelude.Text ->
  -- | 'identityType'
  IdentityType ->
  -- | 'sessionPolicyArn'
  Prelude.Text ->
  UpdateStudioSessionMapping
newUpdateStudioSessionMapping :: Text -> IdentityType -> Text -> UpdateStudioSessionMapping
newUpdateStudioSessionMapping
  Text
pStudioId_
  IdentityType
pIdentityType_
  Text
pSessionPolicyArn_ =
    UpdateStudioSessionMapping'
      { $sel:identityId:UpdateStudioSessionMapping' :: Maybe Text
identityId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:identityName:UpdateStudioSessionMapping' :: Maybe Text
identityName = forall a. Maybe a
Prelude.Nothing,
        $sel:studioId:UpdateStudioSessionMapping' :: Text
studioId = Text
pStudioId_,
        $sel:identityType:UpdateStudioSessionMapping' :: IdentityType
identityType = IdentityType
pIdentityType_,
        $sel:sessionPolicyArn:UpdateStudioSessionMapping' :: Text
sessionPolicyArn = Text
pSessionPolicyArn_
      }

-- | The globally unique identifier (GUID) of the user or group. For more
-- information, see
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserId UserId>
-- and
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-GroupId GroupId>
-- in the /IAM Identity Center Identity Store API Reference/. Either
-- @IdentityName@ or @IdentityId@ must be specified.
updateStudioSessionMapping_identityId :: Lens.Lens' UpdateStudioSessionMapping (Prelude.Maybe Prelude.Text)
updateStudioSessionMapping_identityId :: Lens' UpdateStudioSessionMapping (Maybe Text)
updateStudioSessionMapping_identityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateStudioSessionMapping' {Maybe Text
identityId :: Maybe Text
$sel:identityId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
identityId} -> Maybe Text
identityId) (\s :: UpdateStudioSessionMapping
s@UpdateStudioSessionMapping' {} Maybe Text
a -> UpdateStudioSessionMapping
s {$sel:identityId:UpdateStudioSessionMapping' :: Maybe Text
identityId = Maybe Text
a} :: UpdateStudioSessionMapping)

-- | The name of the user or group to update. For more information, see
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_User.html#singlesignon-Type-User-UserName UserName>
-- and
-- <https://docs.aws.amazon.com/singlesignon/latest/IdentityStoreAPIReference/API_Group.html#singlesignon-Type-Group-DisplayName DisplayName>
-- in the /IAM Identity Center Identity Store API Reference/. Either
-- @IdentityName@ or @IdentityId@ must be specified.
updateStudioSessionMapping_identityName :: Lens.Lens' UpdateStudioSessionMapping (Prelude.Maybe Prelude.Text)
updateStudioSessionMapping_identityName :: Lens' UpdateStudioSessionMapping (Maybe Text)
updateStudioSessionMapping_identityName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateStudioSessionMapping' {Maybe Text
identityName :: Maybe Text
$sel:identityName:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
identityName} -> Maybe Text
identityName) (\s :: UpdateStudioSessionMapping
s@UpdateStudioSessionMapping' {} Maybe Text
a -> UpdateStudioSessionMapping
s {$sel:identityName:UpdateStudioSessionMapping' :: Maybe Text
identityName = Maybe Text
a} :: UpdateStudioSessionMapping)

-- | The ID of the Amazon EMR Studio.
updateStudioSessionMapping_studioId :: Lens.Lens' UpdateStudioSessionMapping Prelude.Text
updateStudioSessionMapping_studioId :: Lens' UpdateStudioSessionMapping Text
updateStudioSessionMapping_studioId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateStudioSessionMapping' {Text
studioId :: Text
$sel:studioId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
studioId} -> Text
studioId) (\s :: UpdateStudioSessionMapping
s@UpdateStudioSessionMapping' {} Text
a -> UpdateStudioSessionMapping
s {$sel:studioId:UpdateStudioSessionMapping' :: Text
studioId = Text
a} :: UpdateStudioSessionMapping)

-- | Specifies whether the identity to update is a user or a group.
updateStudioSessionMapping_identityType :: Lens.Lens' UpdateStudioSessionMapping IdentityType
updateStudioSessionMapping_identityType :: Lens' UpdateStudioSessionMapping IdentityType
updateStudioSessionMapping_identityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateStudioSessionMapping' {IdentityType
identityType :: IdentityType
$sel:identityType:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> IdentityType
identityType} -> IdentityType
identityType) (\s :: UpdateStudioSessionMapping
s@UpdateStudioSessionMapping' {} IdentityType
a -> UpdateStudioSessionMapping
s {$sel:identityType:UpdateStudioSessionMapping' :: IdentityType
identityType = IdentityType
a} :: UpdateStudioSessionMapping)

-- | The Amazon Resource Name (ARN) of the session policy to associate with
-- the specified user or group.
updateStudioSessionMapping_sessionPolicyArn :: Lens.Lens' UpdateStudioSessionMapping Prelude.Text
updateStudioSessionMapping_sessionPolicyArn :: Lens' UpdateStudioSessionMapping Text
updateStudioSessionMapping_sessionPolicyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateStudioSessionMapping' {Text
sessionPolicyArn :: Text
$sel:sessionPolicyArn:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
sessionPolicyArn} -> Text
sessionPolicyArn) (\s :: UpdateStudioSessionMapping
s@UpdateStudioSessionMapping' {} Text
a -> UpdateStudioSessionMapping
s {$sel:sessionPolicyArn:UpdateStudioSessionMapping' :: Text
sessionPolicyArn = Text
a} :: UpdateStudioSessionMapping)

instance Core.AWSRequest UpdateStudioSessionMapping where
  type
    AWSResponse UpdateStudioSessionMapping =
      UpdateStudioSessionMappingResponse
  request :: (Service -> Service)
-> UpdateStudioSessionMapping -> Request UpdateStudioSessionMapping
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateStudioSessionMapping
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateStudioSessionMapping)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      UpdateStudioSessionMappingResponse
UpdateStudioSessionMappingResponse'

instance Prelude.Hashable UpdateStudioSessionMapping where
  hashWithSalt :: Int -> UpdateStudioSessionMapping -> Int
hashWithSalt Int
_salt UpdateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityType:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> IdentityType
$sel:studioId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityName:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
$sel:identityId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
identityId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
identityName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
studioId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IdentityType
identityType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sessionPolicyArn

instance Prelude.NFData UpdateStudioSessionMapping where
  rnf :: UpdateStudioSessionMapping -> ()
rnf UpdateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityType:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> IdentityType
$sel:studioId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityName:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
$sel:identityId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
identityId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
identityName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
studioId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IdentityType
identityType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sessionPolicyArn

instance Data.ToHeaders UpdateStudioSessionMapping where
  toHeaders :: UpdateStudioSessionMapping -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"ElasticMapReduce.UpdateStudioSessionMapping" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateStudioSessionMapping where
  toJSON :: UpdateStudioSessionMapping -> Value
toJSON UpdateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityType:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> IdentityType
$sel:studioId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Text
$sel:identityName:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
$sel:identityId:UpdateStudioSessionMapping' :: UpdateStudioSessionMapping -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"IdentityId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
identityId,
            (Key
"IdentityName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
identityName,
            forall a. a -> Maybe a
Prelude.Just (Key
"StudioId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
studioId),
            forall a. a -> Maybe a
Prelude.Just (Key
"IdentityType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IdentityType
identityType),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SessionPolicyArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sessionPolicyArn)
          ]
      )

instance Data.ToPath UpdateStudioSessionMapping where
  toPath :: UpdateStudioSessionMapping -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateStudioSessionMapping where
  toQuery :: UpdateStudioSessionMapping -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateStudioSessionMappingResponse' smart constructor.
data UpdateStudioSessionMappingResponse = UpdateStudioSessionMappingResponse'
  {
  }
  deriving (UpdateStudioSessionMappingResponse
-> UpdateStudioSessionMappingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateStudioSessionMappingResponse
-> UpdateStudioSessionMappingResponse -> Bool
$c/= :: UpdateStudioSessionMappingResponse
-> UpdateStudioSessionMappingResponse -> Bool
== :: UpdateStudioSessionMappingResponse
-> UpdateStudioSessionMappingResponse -> Bool
$c== :: UpdateStudioSessionMappingResponse
-> UpdateStudioSessionMappingResponse -> Bool
Prelude.Eq, ReadPrec [UpdateStudioSessionMappingResponse]
ReadPrec UpdateStudioSessionMappingResponse
Int -> ReadS UpdateStudioSessionMappingResponse
ReadS [UpdateStudioSessionMappingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateStudioSessionMappingResponse]
$creadListPrec :: ReadPrec [UpdateStudioSessionMappingResponse]
readPrec :: ReadPrec UpdateStudioSessionMappingResponse
$creadPrec :: ReadPrec UpdateStudioSessionMappingResponse
readList :: ReadS [UpdateStudioSessionMappingResponse]
$creadList :: ReadS [UpdateStudioSessionMappingResponse]
readsPrec :: Int -> ReadS UpdateStudioSessionMappingResponse
$creadsPrec :: Int -> ReadS UpdateStudioSessionMappingResponse
Prelude.Read, Int -> UpdateStudioSessionMappingResponse -> ShowS
[UpdateStudioSessionMappingResponse] -> ShowS
UpdateStudioSessionMappingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateStudioSessionMappingResponse] -> ShowS
$cshowList :: [UpdateStudioSessionMappingResponse] -> ShowS
show :: UpdateStudioSessionMappingResponse -> String
$cshow :: UpdateStudioSessionMappingResponse -> String
showsPrec :: Int -> UpdateStudioSessionMappingResponse -> ShowS
$cshowsPrec :: Int -> UpdateStudioSessionMappingResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateStudioSessionMappingResponse x
-> UpdateStudioSessionMappingResponse
forall x.
UpdateStudioSessionMappingResponse
-> Rep UpdateStudioSessionMappingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateStudioSessionMappingResponse x
-> UpdateStudioSessionMappingResponse
$cfrom :: forall x.
UpdateStudioSessionMappingResponse
-> Rep UpdateStudioSessionMappingResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateStudioSessionMappingResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
newUpdateStudioSessionMappingResponse ::
  UpdateStudioSessionMappingResponse
newUpdateStudioSessionMappingResponse :: UpdateStudioSessionMappingResponse
newUpdateStudioSessionMappingResponse =
  UpdateStudioSessionMappingResponse
UpdateStudioSessionMappingResponse'

instance
  Prelude.NFData
    UpdateStudioSessionMappingResponse
  where
  rnf :: UpdateStudioSessionMappingResponse -> ()
rnf UpdateStudioSessionMappingResponse
_ = ()