{-# 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.CreateStudioSessionMapping
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Maps a user or group to the Amazon EMR Studio specified by @StudioId@,
-- and applies a session policy to refine Studio permissions for that user
-- or group. Use @CreateStudioSessionMapping@ to assign users to a Studio
-- when you use IAM Identity Center authentication. For instructions on how
-- to assign users to a Studio when you use IAM authentication, see
-- <https://docs.aws.amazon.com/emr/latest/ManagementGuide/emr-studio-manage-users.html#emr-studio-assign-users-groups Assign a user or group to your EMR Studio>.
module Amazonka.EMR.CreateStudioSessionMapping
  ( -- * Creating a Request
    CreateStudioSessionMapping (..),
    newCreateStudioSessionMapping,

    -- * Request Lenses
    createStudioSessionMapping_identityId,
    createStudioSessionMapping_identityName,
    createStudioSessionMapping_studioId,
    createStudioSessionMapping_identityType,
    createStudioSessionMapping_sessionPolicyArn,

    -- * Destructuring the Response
    CreateStudioSessionMappingResponse (..),
    newCreateStudioSessionMappingResponse,
  )
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:/ 'newCreateStudioSessionMapping' smart constructor.
data CreateStudioSessionMapping = CreateStudioSessionMapping'
  { -- | The globally unique identifier (GUID) of the user or group from the IAM
    -- Identity Center Identity Store. 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, but not both.
    CreateStudioSessionMapping -> Maybe Text
identityId :: Prelude.Maybe Prelude.Text,
    -- | The name of the user or group. 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, but not both.
    CreateStudioSessionMapping -> Maybe Text
identityName :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon EMR Studio to which the user or group will be
    -- mapped.
    CreateStudioSessionMapping -> Text
studioId :: Prelude.Text,
    -- | Specifies whether the identity to map to the Amazon EMR Studio is a user
    -- or a group.
    CreateStudioSessionMapping -> IdentityType
identityType :: IdentityType,
    -- | The Amazon Resource Name (ARN) for the session policy that will be
    -- applied to the user or group. You should specify the ARN for the session
    -- policy that you want to apply, not the ARN of your user role. For more
    -- information, see
    -- <https://docs.aws.amazon.com/emr/latest/ManagementGuide/emr-studio-user-role.html Create an EMR Studio User Role with Session Policies>.
    CreateStudioSessionMapping -> Text
sessionPolicyArn :: Prelude.Text
  }
  deriving (CreateStudioSessionMapping -> CreateStudioSessionMapping -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateStudioSessionMapping -> CreateStudioSessionMapping -> Bool
$c/= :: CreateStudioSessionMapping -> CreateStudioSessionMapping -> Bool
== :: CreateStudioSessionMapping -> CreateStudioSessionMapping -> Bool
$c== :: CreateStudioSessionMapping -> CreateStudioSessionMapping -> Bool
Prelude.Eq, ReadPrec [CreateStudioSessionMapping]
ReadPrec CreateStudioSessionMapping
Int -> ReadS CreateStudioSessionMapping
ReadS [CreateStudioSessionMapping]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateStudioSessionMapping]
$creadListPrec :: ReadPrec [CreateStudioSessionMapping]
readPrec :: ReadPrec CreateStudioSessionMapping
$creadPrec :: ReadPrec CreateStudioSessionMapping
readList :: ReadS [CreateStudioSessionMapping]
$creadList :: ReadS [CreateStudioSessionMapping]
readsPrec :: Int -> ReadS CreateStudioSessionMapping
$creadsPrec :: Int -> ReadS CreateStudioSessionMapping
Prelude.Read, Int -> CreateStudioSessionMapping -> ShowS
[CreateStudioSessionMapping] -> ShowS
CreateStudioSessionMapping -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateStudioSessionMapping] -> ShowS
$cshowList :: [CreateStudioSessionMapping] -> ShowS
show :: CreateStudioSessionMapping -> String
$cshow :: CreateStudioSessionMapping -> String
showsPrec :: Int -> CreateStudioSessionMapping -> ShowS
$cshowsPrec :: Int -> CreateStudioSessionMapping -> ShowS
Prelude.Show, forall x.
Rep CreateStudioSessionMapping x -> CreateStudioSessionMapping
forall x.
CreateStudioSessionMapping -> Rep CreateStudioSessionMapping x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateStudioSessionMapping x -> CreateStudioSessionMapping
$cfrom :: forall x.
CreateStudioSessionMapping -> Rep CreateStudioSessionMapping x
Prelude.Generic)

-- |
-- Create a value of 'CreateStudioSessionMapping' 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', 'createStudioSessionMapping_identityId' - The globally unique identifier (GUID) of the user or group from the IAM
-- Identity Center Identity Store. 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, but not both.
--
-- 'identityName', 'createStudioSessionMapping_identityName' - The name of the user or group. 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, but not both.
--
-- 'studioId', 'createStudioSessionMapping_studioId' - The ID of the Amazon EMR Studio to which the user or group will be
-- mapped.
--
-- 'identityType', 'createStudioSessionMapping_identityType' - Specifies whether the identity to map to the Amazon EMR Studio is a user
-- or a group.
--
-- 'sessionPolicyArn', 'createStudioSessionMapping_sessionPolicyArn' - The Amazon Resource Name (ARN) for the session policy that will be
-- applied to the user or group. You should specify the ARN for the session
-- policy that you want to apply, not the ARN of your user role. For more
-- information, see
-- <https://docs.aws.amazon.com/emr/latest/ManagementGuide/emr-studio-user-role.html Create an EMR Studio User Role with Session Policies>.
newCreateStudioSessionMapping ::
  -- | 'studioId'
  Prelude.Text ->
  -- | 'identityType'
  IdentityType ->
  -- | 'sessionPolicyArn'
  Prelude.Text ->
  CreateStudioSessionMapping
newCreateStudioSessionMapping :: Text -> IdentityType -> Text -> CreateStudioSessionMapping
newCreateStudioSessionMapping
  Text
pStudioId_
  IdentityType
pIdentityType_
  Text
pSessionPolicyArn_ =
    CreateStudioSessionMapping'
      { $sel:identityId:CreateStudioSessionMapping' :: Maybe Text
identityId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:identityName:CreateStudioSessionMapping' :: Maybe Text
identityName = forall a. Maybe a
Prelude.Nothing,
        $sel:studioId:CreateStudioSessionMapping' :: Text
studioId = Text
pStudioId_,
        $sel:identityType:CreateStudioSessionMapping' :: IdentityType
identityType = IdentityType
pIdentityType_,
        $sel:sessionPolicyArn:CreateStudioSessionMapping' :: Text
sessionPolicyArn = Text
pSessionPolicyArn_
      }

-- | The globally unique identifier (GUID) of the user or group from the IAM
-- Identity Center Identity Store. 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, but not both.
createStudioSessionMapping_identityId :: Lens.Lens' CreateStudioSessionMapping (Prelude.Maybe Prelude.Text)
createStudioSessionMapping_identityId :: Lens' CreateStudioSessionMapping (Maybe Text)
createStudioSessionMapping_identityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStudioSessionMapping' {Maybe Text
identityId :: Maybe Text
$sel:identityId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Maybe Text
identityId} -> Maybe Text
identityId) (\s :: CreateStudioSessionMapping
s@CreateStudioSessionMapping' {} Maybe Text
a -> CreateStudioSessionMapping
s {$sel:identityId:CreateStudioSessionMapping' :: Maybe Text
identityId = Maybe Text
a} :: CreateStudioSessionMapping)

-- | The name of the user or group. 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, but not both.
createStudioSessionMapping_identityName :: Lens.Lens' CreateStudioSessionMapping (Prelude.Maybe Prelude.Text)
createStudioSessionMapping_identityName :: Lens' CreateStudioSessionMapping (Maybe Text)
createStudioSessionMapping_identityName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStudioSessionMapping' {Maybe Text
identityName :: Maybe Text
$sel:identityName:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Maybe Text
identityName} -> Maybe Text
identityName) (\s :: CreateStudioSessionMapping
s@CreateStudioSessionMapping' {} Maybe Text
a -> CreateStudioSessionMapping
s {$sel:identityName:CreateStudioSessionMapping' :: Maybe Text
identityName = Maybe Text
a} :: CreateStudioSessionMapping)

-- | The ID of the Amazon EMR Studio to which the user or group will be
-- mapped.
createStudioSessionMapping_studioId :: Lens.Lens' CreateStudioSessionMapping Prelude.Text
createStudioSessionMapping_studioId :: Lens' CreateStudioSessionMapping Text
createStudioSessionMapping_studioId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStudioSessionMapping' {Text
studioId :: Text
$sel:studioId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
studioId} -> Text
studioId) (\s :: CreateStudioSessionMapping
s@CreateStudioSessionMapping' {} Text
a -> CreateStudioSessionMapping
s {$sel:studioId:CreateStudioSessionMapping' :: Text
studioId = Text
a} :: CreateStudioSessionMapping)

-- | Specifies whether the identity to map to the Amazon EMR Studio is a user
-- or a group.
createStudioSessionMapping_identityType :: Lens.Lens' CreateStudioSessionMapping IdentityType
createStudioSessionMapping_identityType :: Lens' CreateStudioSessionMapping IdentityType
createStudioSessionMapping_identityType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStudioSessionMapping' {IdentityType
identityType :: IdentityType
$sel:identityType:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> IdentityType
identityType} -> IdentityType
identityType) (\s :: CreateStudioSessionMapping
s@CreateStudioSessionMapping' {} IdentityType
a -> CreateStudioSessionMapping
s {$sel:identityType:CreateStudioSessionMapping' :: IdentityType
identityType = IdentityType
a} :: CreateStudioSessionMapping)

-- | The Amazon Resource Name (ARN) for the session policy that will be
-- applied to the user or group. You should specify the ARN for the session
-- policy that you want to apply, not the ARN of your user role. For more
-- information, see
-- <https://docs.aws.amazon.com/emr/latest/ManagementGuide/emr-studio-user-role.html Create an EMR Studio User Role with Session Policies>.
createStudioSessionMapping_sessionPolicyArn :: Lens.Lens' CreateStudioSessionMapping Prelude.Text
createStudioSessionMapping_sessionPolicyArn :: Lens' CreateStudioSessionMapping Text
createStudioSessionMapping_sessionPolicyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStudioSessionMapping' {Text
sessionPolicyArn :: Text
$sel:sessionPolicyArn:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
sessionPolicyArn} -> Text
sessionPolicyArn) (\s :: CreateStudioSessionMapping
s@CreateStudioSessionMapping' {} Text
a -> CreateStudioSessionMapping
s {$sel:sessionPolicyArn:CreateStudioSessionMapping' :: Text
sessionPolicyArn = Text
a} :: CreateStudioSessionMapping)

instance Core.AWSRequest CreateStudioSessionMapping where
  type
    AWSResponse CreateStudioSessionMapping =
      CreateStudioSessionMappingResponse
  request :: (Service -> Service)
-> CreateStudioSessionMapping -> Request CreateStudioSessionMapping
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 CreateStudioSessionMapping
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateStudioSessionMapping)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      CreateStudioSessionMappingResponse
CreateStudioSessionMappingResponse'

instance Prelude.Hashable CreateStudioSessionMapping where
  hashWithSalt :: Int -> CreateStudioSessionMapping -> Int
hashWithSalt Int
_salt CreateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityType:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> IdentityType
$sel:studioId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityName:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Maybe Text
$sel:identityId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> 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 CreateStudioSessionMapping where
  rnf :: CreateStudioSessionMapping -> ()
rnf CreateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityType:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> IdentityType
$sel:studioId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityName:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Maybe Text
$sel:identityId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> 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 CreateStudioSessionMapping where
  toHeaders :: CreateStudioSessionMapping -> [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.CreateStudioSessionMapping" ::
                          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 CreateStudioSessionMapping where
  toJSON :: CreateStudioSessionMapping -> Value
toJSON CreateStudioSessionMapping' {Maybe Text
Text
IdentityType
sessionPolicyArn :: Text
identityType :: IdentityType
studioId :: Text
identityName :: Maybe Text
identityId :: Maybe Text
$sel:sessionPolicyArn:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityType:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> IdentityType
$sel:studioId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Text
$sel:identityName:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> Maybe Text
$sel:identityId:CreateStudioSessionMapping' :: CreateStudioSessionMapping -> 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 CreateStudioSessionMapping where
  toPath :: CreateStudioSessionMapping -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateStudioSessionMappingResponse' 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.
newCreateStudioSessionMappingResponse ::
  CreateStudioSessionMappingResponse
newCreateStudioSessionMappingResponse :: CreateStudioSessionMappingResponse
newCreateStudioSessionMappingResponse =
  CreateStudioSessionMappingResponse
CreateStudioSessionMappingResponse'

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