{-# 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.DescribeNotebookInstance
-- 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 information about a notebook instance.
module Amazonka.SageMaker.DescribeNotebookInstance
  ( -- * Creating a Request
    DescribeNotebookInstance (..),
    newDescribeNotebookInstance,

    -- * Request Lenses
    describeNotebookInstance_notebookInstanceName,

    -- * Destructuring the Response
    DescribeNotebookInstanceResponse (..),
    newDescribeNotebookInstanceResponse,

    -- * Response Lenses
    describeNotebookInstanceResponse_acceleratorTypes,
    describeNotebookInstanceResponse_additionalCodeRepositories,
    describeNotebookInstanceResponse_creationTime,
    describeNotebookInstanceResponse_defaultCodeRepository,
    describeNotebookInstanceResponse_directInternetAccess,
    describeNotebookInstanceResponse_failureReason,
    describeNotebookInstanceResponse_instanceMetadataServiceConfiguration,
    describeNotebookInstanceResponse_instanceType,
    describeNotebookInstanceResponse_kmsKeyId,
    describeNotebookInstanceResponse_lastModifiedTime,
    describeNotebookInstanceResponse_networkInterfaceId,
    describeNotebookInstanceResponse_notebookInstanceArn,
    describeNotebookInstanceResponse_notebookInstanceLifecycleConfigName,
    describeNotebookInstanceResponse_notebookInstanceName,
    describeNotebookInstanceResponse_notebookInstanceStatus,
    describeNotebookInstanceResponse_platformIdentifier,
    describeNotebookInstanceResponse_roleArn,
    describeNotebookInstanceResponse_rootAccess,
    describeNotebookInstanceResponse_securityGroups,
    describeNotebookInstanceResponse_subnetId,
    describeNotebookInstanceResponse_url,
    describeNotebookInstanceResponse_volumeSizeInGB,
    describeNotebookInstanceResponse_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:/ 'newDescribeNotebookInstance' smart constructor.
data DescribeNotebookInstance = DescribeNotebookInstance'
  { -- | The name of the notebook instance that you want information about.
    DescribeNotebookInstance -> Text
notebookInstanceName :: Prelude.Text
  }
  deriving (DescribeNotebookInstance -> DescribeNotebookInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotebookInstance -> DescribeNotebookInstance -> Bool
$c/= :: DescribeNotebookInstance -> DescribeNotebookInstance -> Bool
== :: DescribeNotebookInstance -> DescribeNotebookInstance -> Bool
$c== :: DescribeNotebookInstance -> DescribeNotebookInstance -> Bool
Prelude.Eq, ReadPrec [DescribeNotebookInstance]
ReadPrec DescribeNotebookInstance
Int -> ReadS DescribeNotebookInstance
ReadS [DescribeNotebookInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotebookInstance]
$creadListPrec :: ReadPrec [DescribeNotebookInstance]
readPrec :: ReadPrec DescribeNotebookInstance
$creadPrec :: ReadPrec DescribeNotebookInstance
readList :: ReadS [DescribeNotebookInstance]
$creadList :: ReadS [DescribeNotebookInstance]
readsPrec :: Int -> ReadS DescribeNotebookInstance
$creadsPrec :: Int -> ReadS DescribeNotebookInstance
Prelude.Read, Int -> DescribeNotebookInstance -> ShowS
[DescribeNotebookInstance] -> ShowS
DescribeNotebookInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotebookInstance] -> ShowS
$cshowList :: [DescribeNotebookInstance] -> ShowS
show :: DescribeNotebookInstance -> String
$cshow :: DescribeNotebookInstance -> String
showsPrec :: Int -> DescribeNotebookInstance -> ShowS
$cshowsPrec :: Int -> DescribeNotebookInstance -> ShowS
Prelude.Show, forall x.
Rep DescribeNotebookInstance x -> DescribeNotebookInstance
forall x.
DescribeNotebookInstance -> Rep DescribeNotebookInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotebookInstance x -> DescribeNotebookInstance
$cfrom :: forall x.
DescribeNotebookInstance -> Rep DescribeNotebookInstance x
Prelude.Generic)

-- |
-- Create a value of 'DescribeNotebookInstance' 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:
--
-- 'notebookInstanceName', 'describeNotebookInstance_notebookInstanceName' - The name of the notebook instance that you want information about.
newDescribeNotebookInstance ::
  -- | 'notebookInstanceName'
  Prelude.Text ->
  DescribeNotebookInstance
newDescribeNotebookInstance :: Text -> DescribeNotebookInstance
newDescribeNotebookInstance Text
pNotebookInstanceName_ =
  DescribeNotebookInstance'
    { $sel:notebookInstanceName:DescribeNotebookInstance' :: Text
notebookInstanceName =
        Text
pNotebookInstanceName_
    }

-- | The name of the notebook instance that you want information about.
describeNotebookInstance_notebookInstanceName :: Lens.Lens' DescribeNotebookInstance Prelude.Text
describeNotebookInstance_notebookInstanceName :: Lens' DescribeNotebookInstance Text
describeNotebookInstance_notebookInstanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstance' {Text
notebookInstanceName :: Text
$sel:notebookInstanceName:DescribeNotebookInstance' :: DescribeNotebookInstance -> Text
notebookInstanceName} -> Text
notebookInstanceName) (\s :: DescribeNotebookInstance
s@DescribeNotebookInstance' {} Text
a -> DescribeNotebookInstance
s {$sel:notebookInstanceName:DescribeNotebookInstance' :: Text
notebookInstanceName = Text
a} :: DescribeNotebookInstance)

instance Core.AWSRequest DescribeNotebookInstance where
  type
    AWSResponse DescribeNotebookInstance =
      DescribeNotebookInstanceResponse
  request :: (Service -> Service)
-> DescribeNotebookInstance -> Request DescribeNotebookInstance
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 DescribeNotebookInstance
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeNotebookInstance)))
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 [NotebookInstanceAcceleratorType]
-> Maybe [Text]
-> Maybe POSIX
-> Maybe Text
-> Maybe DirectInternetAccess
-> Maybe Text
-> Maybe InstanceMetadataServiceConfiguration
-> Maybe InstanceType
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe NotebookInstanceStatus
-> Maybe Text
-> Maybe Text
-> Maybe RootAccess
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Int
-> DescribeNotebookInstanceResponse
DescribeNotebookInstanceResponse'
            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
"AcceleratorTypes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AdditionalCodeRepositories"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DefaultCodeRepository")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DirectInternetAccess")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"InstanceMetadataServiceConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"InstanceType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"KmsKeyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NetworkInterfaceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotebookInstanceArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotebookInstanceLifecycleConfigName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotebookInstanceName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotebookInstanceStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PlatformIdentifier")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RootAccess")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SecurityGroups" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SubnetId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Url")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VolumeSizeInGB")
            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 DescribeNotebookInstance where
  hashWithSalt :: Int -> DescribeNotebookInstance -> Int
hashWithSalt Int
_salt DescribeNotebookInstance' {Text
notebookInstanceName :: Text
$sel:notebookInstanceName:DescribeNotebookInstance' :: DescribeNotebookInstance -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
notebookInstanceName

instance Prelude.NFData DescribeNotebookInstance where
  rnf :: DescribeNotebookInstance -> ()
rnf DescribeNotebookInstance' {Text
notebookInstanceName :: Text
$sel:notebookInstanceName:DescribeNotebookInstance' :: DescribeNotebookInstance -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
notebookInstanceName

instance Data.ToHeaders DescribeNotebookInstance where
  toHeaders :: DescribeNotebookInstance -> 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.DescribeNotebookInstance" ::
                          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 DescribeNotebookInstance where
  toJSON :: DescribeNotebookInstance -> Value
toJSON DescribeNotebookInstance' {Text
notebookInstanceName :: Text
$sel:notebookInstanceName:DescribeNotebookInstance' :: DescribeNotebookInstance -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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 DescribeNotebookInstance where
  toPath :: DescribeNotebookInstance -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeNotebookInstanceResponse' smart constructor.
data DescribeNotebookInstanceResponse = DescribeNotebookInstanceResponse'
  { -- | A list of the Elastic Inference (EI) instance types associated with this
    -- notebook instance. Currently only one EI instance type can be associated
    -- with a notebook instance. For more information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/ei.html Using Elastic Inference in Amazon SageMaker>.
    DescribeNotebookInstanceResponse
-> Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes :: Prelude.Maybe [NotebookInstanceAcceleratorType],
    -- | An array of up to three Git repositories associated with the notebook
    -- instance. These can be either the names of Git repositories stored as
    -- resources in your account, or the URL of Git repositories in
    -- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
    -- or in any other Git repository. These repositories are cloned at the
    -- same level as the default repository of your notebook instance. For more
    -- information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
    DescribeNotebookInstanceResponse -> Maybe [Text]
additionalCodeRepositories :: Prelude.Maybe [Prelude.Text],
    -- | A timestamp. Use this parameter to return the time when the notebook
    -- instance was created
    DescribeNotebookInstanceResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The Git repository associated with the notebook instance as its default
    -- code repository. This can be either the name of a Git repository stored
    -- as a resource in your account, or the URL of a Git repository in
    -- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
    -- or in any other Git repository. When you open a notebook instance, it
    -- opens in the directory that contains this repository. For more
    -- information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
    DescribeNotebookInstanceResponse -> Maybe Text
defaultCodeRepository :: Prelude.Maybe Prelude.Text,
    -- | Describes whether SageMaker provides internet access to the notebook
    -- instance. If this value is set to /Disabled/, the notebook instance does
    -- not have internet access, and cannot connect to SageMaker training and
    -- endpoint services.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/appendix-additional-considerations.html#appendix-notebook-and-internet-access Notebook Instances Are Internet-Enabled by Default>.
    DescribeNotebookInstanceResponse -> Maybe DirectInternetAccess
directInternetAccess :: Prelude.Maybe DirectInternetAccess,
    -- | If status is @Failed@, the reason it failed.
    DescribeNotebookInstanceResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | Information on the IMDS configuration of the notebook instance
    DescribeNotebookInstanceResponse
-> Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration :: Prelude.Maybe InstanceMetadataServiceConfiguration,
    -- | The type of ML compute instance running on the notebook instance.
    DescribeNotebookInstanceResponse -> Maybe InstanceType
instanceType :: Prelude.Maybe InstanceType,
    -- | The Amazon Web Services KMS key ID SageMaker uses to encrypt data when
    -- storing it on the ML storage volume attached to the instance.
    DescribeNotebookInstanceResponse -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | A timestamp. Use this parameter to retrieve the time when the notebook
    -- instance was last modified.
    DescribeNotebookInstanceResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The network interface IDs that SageMaker created at the time of creating
    -- the instance.
    DescribeNotebookInstanceResponse -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the notebook instance.
    DescribeNotebookInstanceResponse -> Maybe Text
notebookInstanceArn :: Prelude.Maybe Prelude.Text,
    -- | Returns the name of a notebook instance lifecycle configuration.
    --
    -- For information about notebook instance lifestyle configurations, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/notebook-lifecycle-config.html Step 2.1: (Optional) Customize a Notebook Instance>
    DescribeNotebookInstanceResponse -> Maybe Text
notebookInstanceLifecycleConfigName :: Prelude.Maybe Prelude.Text,
    -- | The name of the SageMaker notebook instance.
    DescribeNotebookInstanceResponse -> Maybe Text
notebookInstanceName :: Prelude.Maybe Prelude.Text,
    -- | The status of the notebook instance.
    DescribeNotebookInstanceResponse -> Maybe NotebookInstanceStatus
notebookInstanceStatus :: Prelude.Maybe NotebookInstanceStatus,
    -- | The platform identifier of the notebook instance runtime environment.
    DescribeNotebookInstanceResponse -> Maybe Text
platformIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM role associated with the
    -- instance.
    DescribeNotebookInstanceResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Whether root access is enabled or disabled for users of the notebook
    -- instance.
    --
    -- Lifecycle configurations need root access to be able to set up a
    -- notebook instance. Because of this, lifecycle configurations associated
    -- with a notebook instance always run with root access even if you disable
    -- root access for users.
    DescribeNotebookInstanceResponse -> Maybe RootAccess
rootAccess :: Prelude.Maybe RootAccess,
    -- | The IDs of the VPC security groups.
    DescribeNotebookInstanceResponse -> Maybe [Text]
securityGroups :: Prelude.Maybe [Prelude.Text],
    -- | The ID of the VPC subnet.
    DescribeNotebookInstanceResponse -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The URL that you use to connect to the Jupyter notebook that is running
    -- in your notebook instance.
    DescribeNotebookInstanceResponse -> Maybe Text
url :: Prelude.Maybe Prelude.Text,
    -- | The size, in GB, of the ML storage volume attached to the notebook
    -- instance.
    DescribeNotebookInstanceResponse -> Maybe Natural
volumeSizeInGB :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    DescribeNotebookInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeNotebookInstanceResponse
-> DescribeNotebookInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotebookInstanceResponse
-> DescribeNotebookInstanceResponse -> Bool
$c/= :: DescribeNotebookInstanceResponse
-> DescribeNotebookInstanceResponse -> Bool
== :: DescribeNotebookInstanceResponse
-> DescribeNotebookInstanceResponse -> Bool
$c== :: DescribeNotebookInstanceResponse
-> DescribeNotebookInstanceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeNotebookInstanceResponse]
ReadPrec DescribeNotebookInstanceResponse
Int -> ReadS DescribeNotebookInstanceResponse
ReadS [DescribeNotebookInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotebookInstanceResponse]
$creadListPrec :: ReadPrec [DescribeNotebookInstanceResponse]
readPrec :: ReadPrec DescribeNotebookInstanceResponse
$creadPrec :: ReadPrec DescribeNotebookInstanceResponse
readList :: ReadS [DescribeNotebookInstanceResponse]
$creadList :: ReadS [DescribeNotebookInstanceResponse]
readsPrec :: Int -> ReadS DescribeNotebookInstanceResponse
$creadsPrec :: Int -> ReadS DescribeNotebookInstanceResponse
Prelude.Read, Int -> DescribeNotebookInstanceResponse -> ShowS
[DescribeNotebookInstanceResponse] -> ShowS
DescribeNotebookInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotebookInstanceResponse] -> ShowS
$cshowList :: [DescribeNotebookInstanceResponse] -> ShowS
show :: DescribeNotebookInstanceResponse -> String
$cshow :: DescribeNotebookInstanceResponse -> String
showsPrec :: Int -> DescribeNotebookInstanceResponse -> ShowS
$cshowsPrec :: Int -> DescribeNotebookInstanceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeNotebookInstanceResponse x
-> DescribeNotebookInstanceResponse
forall x.
DescribeNotebookInstanceResponse
-> Rep DescribeNotebookInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotebookInstanceResponse x
-> DescribeNotebookInstanceResponse
$cfrom :: forall x.
DescribeNotebookInstanceResponse
-> Rep DescribeNotebookInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeNotebookInstanceResponse' 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:
--
-- 'acceleratorTypes', 'describeNotebookInstanceResponse_acceleratorTypes' - A list of the Elastic Inference (EI) instance types associated with this
-- notebook instance. Currently only one EI instance type can be associated
-- with a notebook instance. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/ei.html Using Elastic Inference in Amazon SageMaker>.
--
-- 'additionalCodeRepositories', 'describeNotebookInstanceResponse_additionalCodeRepositories' - An array of up to three Git repositories associated with the notebook
-- instance. These can be either the names of Git repositories stored as
-- resources in your account, or the URL of Git repositories in
-- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
-- or in any other Git repository. These repositories are cloned at the
-- same level as the default repository of your notebook instance. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
--
-- 'creationTime', 'describeNotebookInstanceResponse_creationTime' - A timestamp. Use this parameter to return the time when the notebook
-- instance was created
--
-- 'defaultCodeRepository', 'describeNotebookInstanceResponse_defaultCodeRepository' - The Git repository associated with the notebook instance as its default
-- code repository. This can be either the name of a Git repository stored
-- as a resource in your account, or the URL of a Git repository in
-- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
-- or in any other Git repository. When you open a notebook instance, it
-- opens in the directory that contains this repository. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
--
-- 'directInternetAccess', 'describeNotebookInstanceResponse_directInternetAccess' - Describes whether SageMaker provides internet access to the notebook
-- instance. If this value is set to /Disabled/, the notebook instance does
-- not have internet access, and cannot connect to SageMaker training and
-- endpoint services.
--
-- For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/appendix-additional-considerations.html#appendix-notebook-and-internet-access Notebook Instances Are Internet-Enabled by Default>.
--
-- 'failureReason', 'describeNotebookInstanceResponse_failureReason' - If status is @Failed@, the reason it failed.
--
-- 'instanceMetadataServiceConfiguration', 'describeNotebookInstanceResponse_instanceMetadataServiceConfiguration' - Information on the IMDS configuration of the notebook instance
--
-- 'instanceType', 'describeNotebookInstanceResponse_instanceType' - The type of ML compute instance running on the notebook instance.
--
-- 'kmsKeyId', 'describeNotebookInstanceResponse_kmsKeyId' - The Amazon Web Services KMS key ID SageMaker uses to encrypt data when
-- storing it on the ML storage volume attached to the instance.
--
-- 'lastModifiedTime', 'describeNotebookInstanceResponse_lastModifiedTime' - A timestamp. Use this parameter to retrieve the time when the notebook
-- instance was last modified.
--
-- 'networkInterfaceId', 'describeNotebookInstanceResponse_networkInterfaceId' - The network interface IDs that SageMaker created at the time of creating
-- the instance.
--
-- 'notebookInstanceArn', 'describeNotebookInstanceResponse_notebookInstanceArn' - The Amazon Resource Name (ARN) of the notebook instance.
--
-- 'notebookInstanceLifecycleConfigName', 'describeNotebookInstanceResponse_notebookInstanceLifecycleConfigName' - Returns the name of a notebook instance lifecycle configuration.
--
-- For information about notebook instance lifestyle configurations, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/notebook-lifecycle-config.html Step 2.1: (Optional) Customize a Notebook Instance>
--
-- 'notebookInstanceName', 'describeNotebookInstanceResponse_notebookInstanceName' - The name of the SageMaker notebook instance.
--
-- 'notebookInstanceStatus', 'describeNotebookInstanceResponse_notebookInstanceStatus' - The status of the notebook instance.
--
-- 'platformIdentifier', 'describeNotebookInstanceResponse_platformIdentifier' - The platform identifier of the notebook instance runtime environment.
--
-- 'roleArn', 'describeNotebookInstanceResponse_roleArn' - The Amazon Resource Name (ARN) of the IAM role associated with the
-- instance.
--
-- 'rootAccess', 'describeNotebookInstanceResponse_rootAccess' - Whether root access is enabled or disabled for users of the notebook
-- instance.
--
-- Lifecycle configurations need root access to be able to set up a
-- notebook instance. Because of this, lifecycle configurations associated
-- with a notebook instance always run with root access even if you disable
-- root access for users.
--
-- 'securityGroups', 'describeNotebookInstanceResponse_securityGroups' - The IDs of the VPC security groups.
--
-- 'subnetId', 'describeNotebookInstanceResponse_subnetId' - The ID of the VPC subnet.
--
-- 'url', 'describeNotebookInstanceResponse_url' - The URL that you use to connect to the Jupyter notebook that is running
-- in your notebook instance.
--
-- 'volumeSizeInGB', 'describeNotebookInstanceResponse_volumeSizeInGB' - The size, in GB, of the ML storage volume attached to the notebook
-- instance.
--
-- 'httpStatus', 'describeNotebookInstanceResponse_httpStatus' - The response's http status code.
newDescribeNotebookInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeNotebookInstanceResponse
newDescribeNotebookInstanceResponse :: Int -> DescribeNotebookInstanceResponse
newDescribeNotebookInstanceResponse Int
pHttpStatus_ =
  DescribeNotebookInstanceResponse'
    { $sel:acceleratorTypes:DescribeNotebookInstanceResponse' :: Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:additionalCodeRepositories:DescribeNotebookInstanceResponse' :: Maybe [Text]
additionalCodeRepositories =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeNotebookInstanceResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultCodeRepository:DescribeNotebookInstanceResponse' :: Maybe Text
defaultCodeRepository = forall a. Maybe a
Prelude.Nothing,
      $sel:directInternetAccess:DescribeNotebookInstanceResponse' :: Maybe DirectInternetAccess
directInternetAccess = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:DescribeNotebookInstanceResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceMetadataServiceConfiguration:DescribeNotebookInstanceResponse' :: Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:DescribeNotebookInstanceResponse' :: Maybe InstanceType
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:DescribeNotebookInstanceResponse' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DescribeNotebookInstanceResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:DescribeNotebookInstanceResponse' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:notebookInstanceArn:DescribeNotebookInstanceResponse' :: Maybe Text
notebookInstanceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:notebookInstanceLifecycleConfigName:DescribeNotebookInstanceResponse' :: Maybe Text
notebookInstanceLifecycleConfigName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:notebookInstanceName:DescribeNotebookInstanceResponse' :: Maybe Text
notebookInstanceName = forall a. Maybe a
Prelude.Nothing,
      $sel:notebookInstanceStatus:DescribeNotebookInstanceResponse' :: Maybe NotebookInstanceStatus
notebookInstanceStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:platformIdentifier:DescribeNotebookInstanceResponse' :: Maybe Text
platformIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:DescribeNotebookInstanceResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:rootAccess:DescribeNotebookInstanceResponse' :: Maybe RootAccess
rootAccess = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroups:DescribeNotebookInstanceResponse' :: Maybe [Text]
securityGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:DescribeNotebookInstanceResponse' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:url:DescribeNotebookInstanceResponse' :: Maybe Text
url = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeSizeInGB:DescribeNotebookInstanceResponse' :: Maybe Natural
volumeSizeInGB = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeNotebookInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of the Elastic Inference (EI) instance types associated with this
-- notebook instance. Currently only one EI instance type can be associated
-- with a notebook instance. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/ei.html Using Elastic Inference in Amazon SageMaker>.
describeNotebookInstanceResponse_acceleratorTypes :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe [NotebookInstanceAcceleratorType])
describeNotebookInstanceResponse_acceleratorTypes :: Lens'
  DescribeNotebookInstanceResponse
  (Maybe [NotebookInstanceAcceleratorType])
describeNotebookInstanceResponse_acceleratorTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes :: Maybe [NotebookInstanceAcceleratorType]
$sel:acceleratorTypes:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse
-> Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes} -> Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe [NotebookInstanceAcceleratorType]
a -> DescribeNotebookInstanceResponse
s {$sel:acceleratorTypes:DescribeNotebookInstanceResponse' :: Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes = Maybe [NotebookInstanceAcceleratorType]
a} :: DescribeNotebookInstanceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | An array of up to three Git repositories associated with the notebook
-- instance. These can be either the names of Git repositories stored as
-- resources in your account, or the URL of Git repositories in
-- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
-- or in any other Git repository. These repositories are cloned at the
-- same level as the default repository of your notebook instance. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
describeNotebookInstanceResponse_additionalCodeRepositories :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe [Prelude.Text])
describeNotebookInstanceResponse_additionalCodeRepositories :: Lens' DescribeNotebookInstanceResponse (Maybe [Text])
describeNotebookInstanceResponse_additionalCodeRepositories = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe [Text]
additionalCodeRepositories :: Maybe [Text]
$sel:additionalCodeRepositories:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe [Text]
additionalCodeRepositories} -> Maybe [Text]
additionalCodeRepositories) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe [Text]
a -> DescribeNotebookInstanceResponse
s {$sel:additionalCodeRepositories:DescribeNotebookInstanceResponse' :: Maybe [Text]
additionalCodeRepositories = Maybe [Text]
a} :: DescribeNotebookInstanceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A timestamp. Use this parameter to return the time when the notebook
-- instance was created
describeNotebookInstanceResponse_creationTime :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.UTCTime)
describeNotebookInstanceResponse_creationTime :: Lens' DescribeNotebookInstanceResponse (Maybe UTCTime)
describeNotebookInstanceResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe POSIX
a -> DescribeNotebookInstanceResponse
s {$sel:creationTime:DescribeNotebookInstanceResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeNotebookInstanceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Git repository associated with the notebook instance as its default
-- code repository. This can be either the name of a Git repository stored
-- as a resource in your account, or the URL of a Git repository in
-- <https://docs.aws.amazon.com/codecommit/latest/userguide/welcome.html Amazon Web Services CodeCommit>
-- or in any other Git repository. When you open a notebook instance, it
-- opens in the directory that contains this repository. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/nbi-git-repo.html Associating Git Repositories with SageMaker Notebook Instances>.
describeNotebookInstanceResponse_defaultCodeRepository :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_defaultCodeRepository :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_defaultCodeRepository = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
defaultCodeRepository :: Maybe Text
$sel:defaultCodeRepository:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
defaultCodeRepository} -> Maybe Text
defaultCodeRepository) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:defaultCodeRepository:DescribeNotebookInstanceResponse' :: Maybe Text
defaultCodeRepository = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | Describes whether SageMaker provides internet access to the notebook
-- instance. If this value is set to /Disabled/, the notebook instance does
-- not have internet access, and cannot connect to SageMaker training and
-- endpoint services.
--
-- For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/appendix-additional-considerations.html#appendix-notebook-and-internet-access Notebook Instances Are Internet-Enabled by Default>.
describeNotebookInstanceResponse_directInternetAccess :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe DirectInternetAccess)
describeNotebookInstanceResponse_directInternetAccess :: Lens' DescribeNotebookInstanceResponse (Maybe DirectInternetAccess)
describeNotebookInstanceResponse_directInternetAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe DirectInternetAccess
directInternetAccess :: Maybe DirectInternetAccess
$sel:directInternetAccess:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe DirectInternetAccess
directInternetAccess} -> Maybe DirectInternetAccess
directInternetAccess) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe DirectInternetAccess
a -> DescribeNotebookInstanceResponse
s {$sel:directInternetAccess:DescribeNotebookInstanceResponse' :: Maybe DirectInternetAccess
directInternetAccess = Maybe DirectInternetAccess
a} :: DescribeNotebookInstanceResponse)

-- | If status is @Failed@, the reason it failed.
describeNotebookInstanceResponse_failureReason :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_failureReason :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:failureReason:DescribeNotebookInstanceResponse' :: Maybe Text
failureReason = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | Information on the IMDS configuration of the notebook instance
describeNotebookInstanceResponse_instanceMetadataServiceConfiguration :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe InstanceMetadataServiceConfiguration)
describeNotebookInstanceResponse_instanceMetadataServiceConfiguration :: Lens'
  DescribeNotebookInstanceResponse
  (Maybe InstanceMetadataServiceConfiguration)
describeNotebookInstanceResponse_instanceMetadataServiceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration :: Maybe InstanceMetadataServiceConfiguration
$sel:instanceMetadataServiceConfiguration:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse
-> Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration} -> Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe InstanceMetadataServiceConfiguration
a -> DescribeNotebookInstanceResponse
s {$sel:instanceMetadataServiceConfiguration:DescribeNotebookInstanceResponse' :: Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration = Maybe InstanceMetadataServiceConfiguration
a} :: DescribeNotebookInstanceResponse)

-- | The type of ML compute instance running on the notebook instance.
describeNotebookInstanceResponse_instanceType :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe InstanceType)
describeNotebookInstanceResponse_instanceType :: Lens' DescribeNotebookInstanceResponse (Maybe InstanceType)
describeNotebookInstanceResponse_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe InstanceType
instanceType :: Maybe InstanceType
$sel:instanceType:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe InstanceType
instanceType} -> Maybe InstanceType
instanceType) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe InstanceType
a -> DescribeNotebookInstanceResponse
s {$sel:instanceType:DescribeNotebookInstanceResponse' :: Maybe InstanceType
instanceType = Maybe InstanceType
a} :: DescribeNotebookInstanceResponse)

-- | The Amazon Web Services KMS key ID SageMaker uses to encrypt data when
-- storing it on the ML storage volume attached to the instance.
describeNotebookInstanceResponse_kmsKeyId :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_kmsKeyId :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:kmsKeyId:DescribeNotebookInstanceResponse' :: Maybe Text
kmsKeyId = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | A timestamp. Use this parameter to retrieve the time when the notebook
-- instance was last modified.
describeNotebookInstanceResponse_lastModifiedTime :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.UTCTime)
describeNotebookInstanceResponse_lastModifiedTime :: Lens' DescribeNotebookInstanceResponse (Maybe UTCTime)
describeNotebookInstanceResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe POSIX
a -> DescribeNotebookInstanceResponse
s {$sel:lastModifiedTime:DescribeNotebookInstanceResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeNotebookInstanceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The network interface IDs that SageMaker created at the time of creating
-- the instance.
describeNotebookInstanceResponse_networkInterfaceId :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_networkInterfaceId :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
networkInterfaceId :: Maybe Text
$sel:networkInterfaceId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
networkInterfaceId} -> Maybe Text
networkInterfaceId) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:networkInterfaceId:DescribeNotebookInstanceResponse' :: Maybe Text
networkInterfaceId = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | The Amazon Resource Name (ARN) of the notebook instance.
describeNotebookInstanceResponse_notebookInstanceArn :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_notebookInstanceArn :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_notebookInstanceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
notebookInstanceArn :: Maybe Text
$sel:notebookInstanceArn:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
notebookInstanceArn} -> Maybe Text
notebookInstanceArn) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:notebookInstanceArn:DescribeNotebookInstanceResponse' :: Maybe Text
notebookInstanceArn = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | Returns the name of a notebook instance lifecycle configuration.
--
-- For information about notebook instance lifestyle configurations, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/notebook-lifecycle-config.html Step 2.1: (Optional) Customize a Notebook Instance>
describeNotebookInstanceResponse_notebookInstanceLifecycleConfigName :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_notebookInstanceLifecycleConfigName :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_notebookInstanceLifecycleConfigName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
notebookInstanceLifecycleConfigName :: Maybe Text
$sel:notebookInstanceLifecycleConfigName:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
notebookInstanceLifecycleConfigName} -> Maybe Text
notebookInstanceLifecycleConfigName) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:notebookInstanceLifecycleConfigName:DescribeNotebookInstanceResponse' :: Maybe Text
notebookInstanceLifecycleConfigName = Maybe Text
a} :: DescribeNotebookInstanceResponse)

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

-- | The status of the notebook instance.
describeNotebookInstanceResponse_notebookInstanceStatus :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe NotebookInstanceStatus)
describeNotebookInstanceResponse_notebookInstanceStatus :: Lens'
  DescribeNotebookInstanceResponse (Maybe NotebookInstanceStatus)
describeNotebookInstanceResponse_notebookInstanceStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe NotebookInstanceStatus
notebookInstanceStatus :: Maybe NotebookInstanceStatus
$sel:notebookInstanceStatus:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe NotebookInstanceStatus
notebookInstanceStatus} -> Maybe NotebookInstanceStatus
notebookInstanceStatus) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe NotebookInstanceStatus
a -> DescribeNotebookInstanceResponse
s {$sel:notebookInstanceStatus:DescribeNotebookInstanceResponse' :: Maybe NotebookInstanceStatus
notebookInstanceStatus = Maybe NotebookInstanceStatus
a} :: DescribeNotebookInstanceResponse)

-- | The platform identifier of the notebook instance runtime environment.
describeNotebookInstanceResponse_platformIdentifier :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_platformIdentifier :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_platformIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
platformIdentifier :: Maybe Text
$sel:platformIdentifier:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
platformIdentifier} -> Maybe Text
platformIdentifier) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:platformIdentifier:DescribeNotebookInstanceResponse' :: Maybe Text
platformIdentifier = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | The Amazon Resource Name (ARN) of the IAM role associated with the
-- instance.
describeNotebookInstanceResponse_roleArn :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_roleArn :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:roleArn:DescribeNotebookInstanceResponse' :: Maybe Text
roleArn = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | Whether root access is enabled or disabled for users of the notebook
-- instance.
--
-- Lifecycle configurations need root access to be able to set up a
-- notebook instance. Because of this, lifecycle configurations associated
-- with a notebook instance always run with root access even if you disable
-- root access for users.
describeNotebookInstanceResponse_rootAccess :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe RootAccess)
describeNotebookInstanceResponse_rootAccess :: Lens' DescribeNotebookInstanceResponse (Maybe RootAccess)
describeNotebookInstanceResponse_rootAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe RootAccess
rootAccess :: Maybe RootAccess
$sel:rootAccess:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe RootAccess
rootAccess} -> Maybe RootAccess
rootAccess) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe RootAccess
a -> DescribeNotebookInstanceResponse
s {$sel:rootAccess:DescribeNotebookInstanceResponse' :: Maybe RootAccess
rootAccess = Maybe RootAccess
a} :: DescribeNotebookInstanceResponse)

-- | The IDs of the VPC security groups.
describeNotebookInstanceResponse_securityGroups :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe [Prelude.Text])
describeNotebookInstanceResponse_securityGroups :: Lens' DescribeNotebookInstanceResponse (Maybe [Text])
describeNotebookInstanceResponse_securityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe [Text]
securityGroups :: Maybe [Text]
$sel:securityGroups:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe [Text]
securityGroups} -> Maybe [Text]
securityGroups) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe [Text]
a -> DescribeNotebookInstanceResponse
s {$sel:securityGroups:DescribeNotebookInstanceResponse' :: Maybe [Text]
securityGroups = Maybe [Text]
a} :: DescribeNotebookInstanceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The ID of the VPC subnet.
describeNotebookInstanceResponse_subnetId :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_subnetId :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:subnetId:DescribeNotebookInstanceResponse' :: Maybe Text
subnetId = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | The URL that you use to connect to the Jupyter notebook that is running
-- in your notebook instance.
describeNotebookInstanceResponse_url :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Text)
describeNotebookInstanceResponse_url :: Lens' DescribeNotebookInstanceResponse (Maybe Text)
describeNotebookInstanceResponse_url = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Text
url :: Maybe Text
$sel:url:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
url} -> Maybe Text
url) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Text
a -> DescribeNotebookInstanceResponse
s {$sel:url:DescribeNotebookInstanceResponse' :: Maybe Text
url = Maybe Text
a} :: DescribeNotebookInstanceResponse)

-- | The size, in GB, of the ML storage volume attached to the notebook
-- instance.
describeNotebookInstanceResponse_volumeSizeInGB :: Lens.Lens' DescribeNotebookInstanceResponse (Prelude.Maybe Prelude.Natural)
describeNotebookInstanceResponse_volumeSizeInGB :: Lens' DescribeNotebookInstanceResponse (Maybe Natural)
describeNotebookInstanceResponse_volumeSizeInGB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotebookInstanceResponse' {Maybe Natural
volumeSizeInGB :: Maybe Natural
$sel:volumeSizeInGB:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Natural
volumeSizeInGB} -> Maybe Natural
volumeSizeInGB) (\s :: DescribeNotebookInstanceResponse
s@DescribeNotebookInstanceResponse' {} Maybe Natural
a -> DescribeNotebookInstanceResponse
s {$sel:volumeSizeInGB:DescribeNotebookInstanceResponse' :: Maybe Natural
volumeSizeInGB = Maybe Natural
a} :: DescribeNotebookInstanceResponse)

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

instance
  Prelude.NFData
    DescribeNotebookInstanceResponse
  where
  rnf :: DescribeNotebookInstanceResponse -> ()
rnf DescribeNotebookInstanceResponse' {Int
Maybe Natural
Maybe [Text]
Maybe [NotebookInstanceAcceleratorType]
Maybe Text
Maybe POSIX
Maybe DirectInternetAccess
Maybe InstanceMetadataServiceConfiguration
Maybe InstanceType
Maybe NotebookInstanceStatus
Maybe RootAccess
httpStatus :: Int
volumeSizeInGB :: Maybe Natural
url :: Maybe Text
subnetId :: Maybe Text
securityGroups :: Maybe [Text]
rootAccess :: Maybe RootAccess
roleArn :: Maybe Text
platformIdentifier :: Maybe Text
notebookInstanceStatus :: Maybe NotebookInstanceStatus
notebookInstanceName :: Maybe Text
notebookInstanceLifecycleConfigName :: Maybe Text
notebookInstanceArn :: Maybe Text
networkInterfaceId :: Maybe Text
lastModifiedTime :: Maybe POSIX
kmsKeyId :: Maybe Text
instanceType :: Maybe InstanceType
instanceMetadataServiceConfiguration :: Maybe InstanceMetadataServiceConfiguration
failureReason :: Maybe Text
directInternetAccess :: Maybe DirectInternetAccess
defaultCodeRepository :: Maybe Text
creationTime :: Maybe POSIX
additionalCodeRepositories :: Maybe [Text]
acceleratorTypes :: Maybe [NotebookInstanceAcceleratorType]
$sel:httpStatus:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Int
$sel:volumeSizeInGB:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Natural
$sel:url:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:subnetId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:securityGroups:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe [Text]
$sel:rootAccess:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe RootAccess
$sel:roleArn:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:platformIdentifier:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:notebookInstanceStatus:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe NotebookInstanceStatus
$sel:notebookInstanceName:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:notebookInstanceLifecycleConfigName:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:notebookInstanceArn:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:networkInterfaceId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:lastModifiedTime:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe POSIX
$sel:kmsKeyId:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:instanceType:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe InstanceType
$sel:instanceMetadataServiceConfiguration:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse
-> Maybe InstanceMetadataServiceConfiguration
$sel:failureReason:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:directInternetAccess:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe DirectInternetAccess
$sel:defaultCodeRepository:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe Text
$sel:creationTime:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe POSIX
$sel:additionalCodeRepositories:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse -> Maybe [Text]
$sel:acceleratorTypes:DescribeNotebookInstanceResponse' :: DescribeNotebookInstanceResponse
-> Maybe [NotebookInstanceAcceleratorType]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [NotebookInstanceAcceleratorType]
acceleratorTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
additionalCodeRepositories
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultCodeRepository
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DirectInternetAccess
directInternetAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceMetadataServiceConfiguration
instanceMetadataServiceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceType
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkInterfaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
notebookInstanceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
notebookInstanceLifecycleConfigName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
notebookInstanceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NotebookInstanceStatus
notebookInstanceStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RootAccess
rootAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
securityGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
url
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
volumeSizeInGB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus