{-# 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.SageMaker.CreatePresignedNotebookInstanceUrl
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a URL that you can use to connect to the Jupyter server from a
-- notebook instance. In the SageMaker console, when you choose @Open@ next
-- to a notebook instance, SageMaker opens a new tab showing the Jupyter
-- server home page from the notebook instance. The console uses this API
-- to get the URL and show the page.
--
-- The IAM role or user used to call this API defines the permissions to
-- access the notebook instance. Once the presigned URL is created, no
-- additional permission is required to access this URL. IAM authorization
-- policies for this API are also enforced for every HTTP request and
-- WebSocket frame that attempts to connect to the notebook instance.
--
-- You can restrict access to this API and to the URL that it returns to a
-- list of IP addresses that you specify. Use the @NotIpAddress@ condition
-- operator and the @aws:SourceIP@ condition context key to specify the
-- list of IP addresses that you want to have access to the notebook
-- instance. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/security_iam_id-based-policy-examples.html#nbi-ip-filter Limit Access to a Notebook Instance by IP Address>.
--
-- The URL that you get from a call to CreatePresignedNotebookInstanceUrl
-- is valid only for 5 minutes. If you try to use the URL after the
-- 5-minute limit expires, you are directed to the Amazon Web Services
-- console sign-in page.
module Amazonka.SageMaker.CreatePresignedNotebookInstanceUrl
  ( -- * Creating a Request
    CreatePresignedNotebookInstanceUrl (..),
    newCreatePresignedNotebookInstanceUrl,

    -- * Request Lenses
    createPresignedNotebookInstanceUrl_sessionExpirationDurationInSeconds,
    createPresignedNotebookInstanceUrl_notebookInstanceName,

    -- * Destructuring the Response
    CreatePresignedNotebookInstanceUrlResponse (..),
    newCreatePresignedNotebookInstanceUrlResponse,

    -- * Response Lenses
    createPresignedNotebookInstanceUrlResponse_authorizedUrl,
    createPresignedNotebookInstanceUrlResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreatePresignedNotebookInstanceUrl' smart constructor.
data CreatePresignedNotebookInstanceUrl = CreatePresignedNotebookInstanceUrl'
  { -- | The duration of the session, in seconds. The default is 12 hours.
    CreatePresignedNotebookInstanceUrl -> Maybe Natural
sessionExpirationDurationInSeconds :: Prelude.Maybe Prelude.Natural,
    -- | The name of the notebook instance.
    CreatePresignedNotebookInstanceUrl -> Text
notebookInstanceName :: Prelude.Text
  }
  deriving (CreatePresignedNotebookInstanceUrl
-> CreatePresignedNotebookInstanceUrl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePresignedNotebookInstanceUrl
-> CreatePresignedNotebookInstanceUrl -> Bool
$c/= :: CreatePresignedNotebookInstanceUrl
-> CreatePresignedNotebookInstanceUrl -> Bool
== :: CreatePresignedNotebookInstanceUrl
-> CreatePresignedNotebookInstanceUrl -> Bool
$c== :: CreatePresignedNotebookInstanceUrl
-> CreatePresignedNotebookInstanceUrl -> Bool
Prelude.Eq, ReadPrec [CreatePresignedNotebookInstanceUrl]
ReadPrec CreatePresignedNotebookInstanceUrl
Int -> ReadS CreatePresignedNotebookInstanceUrl
ReadS [CreatePresignedNotebookInstanceUrl]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePresignedNotebookInstanceUrl]
$creadListPrec :: ReadPrec [CreatePresignedNotebookInstanceUrl]
readPrec :: ReadPrec CreatePresignedNotebookInstanceUrl
$creadPrec :: ReadPrec CreatePresignedNotebookInstanceUrl
readList :: ReadS [CreatePresignedNotebookInstanceUrl]
$creadList :: ReadS [CreatePresignedNotebookInstanceUrl]
readsPrec :: Int -> ReadS CreatePresignedNotebookInstanceUrl
$creadsPrec :: Int -> ReadS CreatePresignedNotebookInstanceUrl
Prelude.Read, Int -> CreatePresignedNotebookInstanceUrl -> ShowS
[CreatePresignedNotebookInstanceUrl] -> ShowS
CreatePresignedNotebookInstanceUrl -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePresignedNotebookInstanceUrl] -> ShowS
$cshowList :: [CreatePresignedNotebookInstanceUrl] -> ShowS
show :: CreatePresignedNotebookInstanceUrl -> String
$cshow :: CreatePresignedNotebookInstanceUrl -> String
showsPrec :: Int -> CreatePresignedNotebookInstanceUrl -> ShowS
$cshowsPrec :: Int -> CreatePresignedNotebookInstanceUrl -> ShowS
Prelude.Show, forall x.
Rep CreatePresignedNotebookInstanceUrl x
-> CreatePresignedNotebookInstanceUrl
forall x.
CreatePresignedNotebookInstanceUrl
-> Rep CreatePresignedNotebookInstanceUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreatePresignedNotebookInstanceUrl x
-> CreatePresignedNotebookInstanceUrl
$cfrom :: forall x.
CreatePresignedNotebookInstanceUrl
-> Rep CreatePresignedNotebookInstanceUrl x
Prelude.Generic)

-- |
-- Create a value of 'CreatePresignedNotebookInstanceUrl' 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:
--
-- 'sessionExpirationDurationInSeconds', 'createPresignedNotebookInstanceUrl_sessionExpirationDurationInSeconds' - The duration of the session, in seconds. The default is 12 hours.
--
-- 'notebookInstanceName', 'createPresignedNotebookInstanceUrl_notebookInstanceName' - The name of the notebook instance.
newCreatePresignedNotebookInstanceUrl ::
  -- | 'notebookInstanceName'
  Prelude.Text ->
  CreatePresignedNotebookInstanceUrl
newCreatePresignedNotebookInstanceUrl :: Text -> CreatePresignedNotebookInstanceUrl
newCreatePresignedNotebookInstanceUrl
  Text
pNotebookInstanceName_ =
    CreatePresignedNotebookInstanceUrl'
      { $sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: Maybe Natural
sessionExpirationDurationInSeconds =
          forall a. Maybe a
Prelude.Nothing,
        $sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: Text
notebookInstanceName =
          Text
pNotebookInstanceName_
      }

-- | The duration of the session, in seconds. The default is 12 hours.
createPresignedNotebookInstanceUrl_sessionExpirationDurationInSeconds :: Lens.Lens' CreatePresignedNotebookInstanceUrl (Prelude.Maybe Prelude.Natural)
createPresignedNotebookInstanceUrl_sessionExpirationDurationInSeconds :: Lens' CreatePresignedNotebookInstanceUrl (Maybe Natural)
createPresignedNotebookInstanceUrl_sessionExpirationDurationInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePresignedNotebookInstanceUrl' {Maybe Natural
sessionExpirationDurationInSeconds :: Maybe Natural
$sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Maybe Natural
sessionExpirationDurationInSeconds} -> Maybe Natural
sessionExpirationDurationInSeconds) (\s :: CreatePresignedNotebookInstanceUrl
s@CreatePresignedNotebookInstanceUrl' {} Maybe Natural
a -> CreatePresignedNotebookInstanceUrl
s {$sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: Maybe Natural
sessionExpirationDurationInSeconds = Maybe Natural
a} :: CreatePresignedNotebookInstanceUrl)

-- | The name of the notebook instance.
createPresignedNotebookInstanceUrl_notebookInstanceName :: Lens.Lens' CreatePresignedNotebookInstanceUrl Prelude.Text
createPresignedNotebookInstanceUrl_notebookInstanceName :: Lens' CreatePresignedNotebookInstanceUrl Text
createPresignedNotebookInstanceUrl_notebookInstanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePresignedNotebookInstanceUrl' {Text
notebookInstanceName :: Text
$sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Text
notebookInstanceName} -> Text
notebookInstanceName) (\s :: CreatePresignedNotebookInstanceUrl
s@CreatePresignedNotebookInstanceUrl' {} Text
a -> CreatePresignedNotebookInstanceUrl
s {$sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: Text
notebookInstanceName = Text
a} :: CreatePresignedNotebookInstanceUrl)

instance
  Core.AWSRequest
    CreatePresignedNotebookInstanceUrl
  where
  type
    AWSResponse CreatePresignedNotebookInstanceUrl =
      CreatePresignedNotebookInstanceUrlResponse
  request :: (Service -> Service)
-> CreatePresignedNotebookInstanceUrl
-> Request CreatePresignedNotebookInstanceUrl
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 CreatePresignedNotebookInstanceUrl
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CreatePresignedNotebookInstanceUrl)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> CreatePresignedNotebookInstanceUrlResponse
CreatePresignedNotebookInstanceUrlResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AuthorizedUrl")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    CreatePresignedNotebookInstanceUrl
  where
  hashWithSalt :: Int -> CreatePresignedNotebookInstanceUrl -> Int
hashWithSalt
    Int
_salt
    CreatePresignedNotebookInstanceUrl' {Maybe Natural
Text
notebookInstanceName :: Text
sessionExpirationDurationInSeconds :: Maybe Natural
$sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Text
$sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
sessionExpirationDurationInSeconds
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
notebookInstanceName

instance
  Prelude.NFData
    CreatePresignedNotebookInstanceUrl
  where
  rnf :: CreatePresignedNotebookInstanceUrl -> ()
rnf CreatePresignedNotebookInstanceUrl' {Maybe Natural
Text
notebookInstanceName :: Text
sessionExpirationDurationInSeconds :: Maybe Natural
$sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Text
$sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
sessionExpirationDurationInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
notebookInstanceName

instance
  Data.ToHeaders
    CreatePresignedNotebookInstanceUrl
  where
  toHeaders :: CreatePresignedNotebookInstanceUrl -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"SageMaker.CreatePresignedNotebookInstanceUrl" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    CreatePresignedNotebookInstanceUrl
  where
  toJSON :: CreatePresignedNotebookInstanceUrl -> Value
toJSON CreatePresignedNotebookInstanceUrl' {Maybe Natural
Text
notebookInstanceName :: Text
sessionExpirationDurationInSeconds :: Maybe Natural
$sel:notebookInstanceName:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Text
$sel:sessionExpirationDurationInSeconds:CreatePresignedNotebookInstanceUrl' :: CreatePresignedNotebookInstanceUrl -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SessionExpirationDurationInSeconds" 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 Natural
sessionExpirationDurationInSeconds,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"NotebookInstanceName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
notebookInstanceName
              )
          ]
      )

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

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

-- | /See:/ 'newCreatePresignedNotebookInstanceUrlResponse' smart constructor.
data CreatePresignedNotebookInstanceUrlResponse = CreatePresignedNotebookInstanceUrlResponse'
  { -- | A JSON object that contains the URL string.
    CreatePresignedNotebookInstanceUrlResponse -> Maybe Text
authorizedUrl :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreatePresignedNotebookInstanceUrlResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreatePresignedNotebookInstanceUrlResponse
-> CreatePresignedNotebookInstanceUrlResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePresignedNotebookInstanceUrlResponse
-> CreatePresignedNotebookInstanceUrlResponse -> Bool
$c/= :: CreatePresignedNotebookInstanceUrlResponse
-> CreatePresignedNotebookInstanceUrlResponse -> Bool
== :: CreatePresignedNotebookInstanceUrlResponse
-> CreatePresignedNotebookInstanceUrlResponse -> Bool
$c== :: CreatePresignedNotebookInstanceUrlResponse
-> CreatePresignedNotebookInstanceUrlResponse -> Bool
Prelude.Eq, ReadPrec [CreatePresignedNotebookInstanceUrlResponse]
ReadPrec CreatePresignedNotebookInstanceUrlResponse
Int -> ReadS CreatePresignedNotebookInstanceUrlResponse
ReadS [CreatePresignedNotebookInstanceUrlResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePresignedNotebookInstanceUrlResponse]
$creadListPrec :: ReadPrec [CreatePresignedNotebookInstanceUrlResponse]
readPrec :: ReadPrec CreatePresignedNotebookInstanceUrlResponse
$creadPrec :: ReadPrec CreatePresignedNotebookInstanceUrlResponse
readList :: ReadS [CreatePresignedNotebookInstanceUrlResponse]
$creadList :: ReadS [CreatePresignedNotebookInstanceUrlResponse]
readsPrec :: Int -> ReadS CreatePresignedNotebookInstanceUrlResponse
$creadsPrec :: Int -> ReadS CreatePresignedNotebookInstanceUrlResponse
Prelude.Read, Int -> CreatePresignedNotebookInstanceUrlResponse -> ShowS
[CreatePresignedNotebookInstanceUrlResponse] -> ShowS
CreatePresignedNotebookInstanceUrlResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePresignedNotebookInstanceUrlResponse] -> ShowS
$cshowList :: [CreatePresignedNotebookInstanceUrlResponse] -> ShowS
show :: CreatePresignedNotebookInstanceUrlResponse -> String
$cshow :: CreatePresignedNotebookInstanceUrlResponse -> String
showsPrec :: Int -> CreatePresignedNotebookInstanceUrlResponse -> ShowS
$cshowsPrec :: Int -> CreatePresignedNotebookInstanceUrlResponse -> ShowS
Prelude.Show, forall x.
Rep CreatePresignedNotebookInstanceUrlResponse x
-> CreatePresignedNotebookInstanceUrlResponse
forall x.
CreatePresignedNotebookInstanceUrlResponse
-> Rep CreatePresignedNotebookInstanceUrlResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreatePresignedNotebookInstanceUrlResponse x
-> CreatePresignedNotebookInstanceUrlResponse
$cfrom :: forall x.
CreatePresignedNotebookInstanceUrlResponse
-> Rep CreatePresignedNotebookInstanceUrlResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreatePresignedNotebookInstanceUrlResponse' 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:
--
-- 'authorizedUrl', 'createPresignedNotebookInstanceUrlResponse_authorizedUrl' - A JSON object that contains the URL string.
--
-- 'httpStatus', 'createPresignedNotebookInstanceUrlResponse_httpStatus' - The response's http status code.
newCreatePresignedNotebookInstanceUrlResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreatePresignedNotebookInstanceUrlResponse
newCreatePresignedNotebookInstanceUrlResponse :: Int -> CreatePresignedNotebookInstanceUrlResponse
newCreatePresignedNotebookInstanceUrlResponse
  Int
pHttpStatus_ =
    CreatePresignedNotebookInstanceUrlResponse'
      { $sel:authorizedUrl:CreatePresignedNotebookInstanceUrlResponse' :: Maybe Text
authorizedUrl =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CreatePresignedNotebookInstanceUrlResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A JSON object that contains the URL string.
createPresignedNotebookInstanceUrlResponse_authorizedUrl :: Lens.Lens' CreatePresignedNotebookInstanceUrlResponse (Prelude.Maybe Prelude.Text)
createPresignedNotebookInstanceUrlResponse_authorizedUrl :: Lens' CreatePresignedNotebookInstanceUrlResponse (Maybe Text)
createPresignedNotebookInstanceUrlResponse_authorizedUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePresignedNotebookInstanceUrlResponse' {Maybe Text
authorizedUrl :: Maybe Text
$sel:authorizedUrl:CreatePresignedNotebookInstanceUrlResponse' :: CreatePresignedNotebookInstanceUrlResponse -> Maybe Text
authorizedUrl} -> Maybe Text
authorizedUrl) (\s :: CreatePresignedNotebookInstanceUrlResponse
s@CreatePresignedNotebookInstanceUrlResponse' {} Maybe Text
a -> CreatePresignedNotebookInstanceUrlResponse
s {$sel:authorizedUrl:CreatePresignedNotebookInstanceUrlResponse' :: Maybe Text
authorizedUrl = Maybe Text
a} :: CreatePresignedNotebookInstanceUrlResponse)

-- | The response's http status code.
createPresignedNotebookInstanceUrlResponse_httpStatus :: Lens.Lens' CreatePresignedNotebookInstanceUrlResponse Prelude.Int
createPresignedNotebookInstanceUrlResponse_httpStatus :: Lens' CreatePresignedNotebookInstanceUrlResponse Int
createPresignedNotebookInstanceUrlResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePresignedNotebookInstanceUrlResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreatePresignedNotebookInstanceUrlResponse' :: CreatePresignedNotebookInstanceUrlResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreatePresignedNotebookInstanceUrlResponse
s@CreatePresignedNotebookInstanceUrlResponse' {} Int
a -> CreatePresignedNotebookInstanceUrlResponse
s {$sel:httpStatus:CreatePresignedNotebookInstanceUrlResponse' :: Int
httpStatus = Int
a} :: CreatePresignedNotebookInstanceUrlResponse)

instance
  Prelude.NFData
    CreatePresignedNotebookInstanceUrlResponse
  where
  rnf :: CreatePresignedNotebookInstanceUrlResponse -> ()
rnf CreatePresignedNotebookInstanceUrlResponse' {Int
Maybe Text
httpStatus :: Int
authorizedUrl :: Maybe Text
$sel:httpStatus:CreatePresignedNotebookInstanceUrlResponse' :: CreatePresignedNotebookInstanceUrlResponse -> Int
$sel:authorizedUrl:CreatePresignedNotebookInstanceUrlResponse' :: CreatePresignedNotebookInstanceUrlResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorizedUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus