{-# 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.DeleteApp
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Used to stop and delete an app.
module Amazonka.SageMaker.DeleteApp
  ( -- * Creating a Request
    DeleteApp (..),
    newDeleteApp,

    -- * Request Lenses
    deleteApp_spaceName,
    deleteApp_userProfileName,
    deleteApp_domainId,
    deleteApp_appType,
    deleteApp_appName,

    -- * Destructuring the Response
    DeleteAppResponse (..),
    newDeleteAppResponse,
  )
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:/ 'newDeleteApp' smart constructor.
data DeleteApp = DeleteApp'
  { -- | The name of the space. If this value is not set, then @UserProfileName@
    -- must be set.
    DeleteApp -> Maybe Text
spaceName :: Prelude.Maybe Prelude.Text,
    -- | The user profile name. If this value is not set, then @SpaceName@ must
    -- be set.
    DeleteApp -> Maybe Text
userProfileName :: Prelude.Maybe Prelude.Text,
    -- | The domain ID.
    DeleteApp -> Text
domainId :: Prelude.Text,
    -- | The type of app.
    DeleteApp -> AppType
appType :: AppType,
    -- | The name of the app.
    DeleteApp -> Text
appName :: Prelude.Text
  }
  deriving (DeleteApp -> DeleteApp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteApp -> DeleteApp -> Bool
$c/= :: DeleteApp -> DeleteApp -> Bool
== :: DeleteApp -> DeleteApp -> Bool
$c== :: DeleteApp -> DeleteApp -> Bool
Prelude.Eq, ReadPrec [DeleteApp]
ReadPrec DeleteApp
Int -> ReadS DeleteApp
ReadS [DeleteApp]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteApp]
$creadListPrec :: ReadPrec [DeleteApp]
readPrec :: ReadPrec DeleteApp
$creadPrec :: ReadPrec DeleteApp
readList :: ReadS [DeleteApp]
$creadList :: ReadS [DeleteApp]
readsPrec :: Int -> ReadS DeleteApp
$creadsPrec :: Int -> ReadS DeleteApp
Prelude.Read, Int -> DeleteApp -> ShowS
[DeleteApp] -> ShowS
DeleteApp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteApp] -> ShowS
$cshowList :: [DeleteApp] -> ShowS
show :: DeleteApp -> String
$cshow :: DeleteApp -> String
showsPrec :: Int -> DeleteApp -> ShowS
$cshowsPrec :: Int -> DeleteApp -> ShowS
Prelude.Show, forall x. Rep DeleteApp x -> DeleteApp
forall x. DeleteApp -> Rep DeleteApp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteApp x -> DeleteApp
$cfrom :: forall x. DeleteApp -> Rep DeleteApp x
Prelude.Generic)

-- |
-- Create a value of 'DeleteApp' 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:
--
-- 'spaceName', 'deleteApp_spaceName' - The name of the space. If this value is not set, then @UserProfileName@
-- must be set.
--
-- 'userProfileName', 'deleteApp_userProfileName' - The user profile name. If this value is not set, then @SpaceName@ must
-- be set.
--
-- 'domainId', 'deleteApp_domainId' - The domain ID.
--
-- 'appType', 'deleteApp_appType' - The type of app.
--
-- 'appName', 'deleteApp_appName' - The name of the app.
newDeleteApp ::
  -- | 'domainId'
  Prelude.Text ->
  -- | 'appType'
  AppType ->
  -- | 'appName'
  Prelude.Text ->
  DeleteApp
newDeleteApp :: Text -> AppType -> Text -> DeleteApp
newDeleteApp Text
pDomainId_ AppType
pAppType_ Text
pAppName_ =
  DeleteApp'
    { $sel:spaceName:DeleteApp' :: Maybe Text
spaceName = forall a. Maybe a
Prelude.Nothing,
      $sel:userProfileName:DeleteApp' :: Maybe Text
userProfileName = forall a. Maybe a
Prelude.Nothing,
      $sel:domainId:DeleteApp' :: Text
domainId = Text
pDomainId_,
      $sel:appType:DeleteApp' :: AppType
appType = AppType
pAppType_,
      $sel:appName:DeleteApp' :: Text
appName = Text
pAppName_
    }

-- | The name of the space. If this value is not set, then @UserProfileName@
-- must be set.
deleteApp_spaceName :: Lens.Lens' DeleteApp (Prelude.Maybe Prelude.Text)
deleteApp_spaceName :: Lens' DeleteApp (Maybe Text)
deleteApp_spaceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Maybe Text
spaceName :: Maybe Text
$sel:spaceName:DeleteApp' :: DeleteApp -> Maybe Text
spaceName} -> Maybe Text
spaceName) (\s :: DeleteApp
s@DeleteApp' {} Maybe Text
a -> DeleteApp
s {$sel:spaceName:DeleteApp' :: Maybe Text
spaceName = Maybe Text
a} :: DeleteApp)

-- | The user profile name. If this value is not set, then @SpaceName@ must
-- be set.
deleteApp_userProfileName :: Lens.Lens' DeleteApp (Prelude.Maybe Prelude.Text)
deleteApp_userProfileName :: Lens' DeleteApp (Maybe Text)
deleteApp_userProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Maybe Text
userProfileName :: Maybe Text
$sel:userProfileName:DeleteApp' :: DeleteApp -> Maybe Text
userProfileName} -> Maybe Text
userProfileName) (\s :: DeleteApp
s@DeleteApp' {} Maybe Text
a -> DeleteApp
s {$sel:userProfileName:DeleteApp' :: Maybe Text
userProfileName = Maybe Text
a} :: DeleteApp)

-- | The domain ID.
deleteApp_domainId :: Lens.Lens' DeleteApp Prelude.Text
deleteApp_domainId :: Lens' DeleteApp Text
deleteApp_domainId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Text
domainId :: Text
$sel:domainId:DeleteApp' :: DeleteApp -> Text
domainId} -> Text
domainId) (\s :: DeleteApp
s@DeleteApp' {} Text
a -> DeleteApp
s {$sel:domainId:DeleteApp' :: Text
domainId = Text
a} :: DeleteApp)

-- | The type of app.
deleteApp_appType :: Lens.Lens' DeleteApp AppType
deleteApp_appType :: Lens' DeleteApp AppType
deleteApp_appType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {AppType
appType :: AppType
$sel:appType:DeleteApp' :: DeleteApp -> AppType
appType} -> AppType
appType) (\s :: DeleteApp
s@DeleteApp' {} AppType
a -> DeleteApp
s {$sel:appType:DeleteApp' :: AppType
appType = AppType
a} :: DeleteApp)

-- | The name of the app.
deleteApp_appName :: Lens.Lens' DeleteApp Prelude.Text
deleteApp_appName :: Lens' DeleteApp Text
deleteApp_appName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApp' {Text
appName :: Text
$sel:appName:DeleteApp' :: DeleteApp -> Text
appName} -> Text
appName) (\s :: DeleteApp
s@DeleteApp' {} Text
a -> DeleteApp
s {$sel:appName:DeleteApp' :: Text
appName = Text
a} :: DeleteApp)

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

instance Prelude.Hashable DeleteApp where
  hashWithSalt :: Int -> DeleteApp -> Int
hashWithSalt Int
_salt DeleteApp' {Maybe Text
Text
AppType
appName :: Text
appType :: AppType
domainId :: Text
userProfileName :: Maybe Text
spaceName :: Maybe Text
$sel:appName:DeleteApp' :: DeleteApp -> Text
$sel:appType:DeleteApp' :: DeleteApp -> AppType
$sel:domainId:DeleteApp' :: DeleteApp -> Text
$sel:userProfileName:DeleteApp' :: DeleteApp -> Maybe Text
$sel:spaceName:DeleteApp' :: DeleteApp -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
spaceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userProfileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AppType
appType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appName

instance Prelude.NFData DeleteApp where
  rnf :: DeleteApp -> ()
rnf DeleteApp' {Maybe Text
Text
AppType
appName :: Text
appType :: AppType
domainId :: Text
userProfileName :: Maybe Text
spaceName :: Maybe Text
$sel:appName:DeleteApp' :: DeleteApp -> Text
$sel:appType:DeleteApp' :: DeleteApp -> AppType
$sel:domainId:DeleteApp' :: DeleteApp -> Text
$sel:userProfileName:DeleteApp' :: DeleteApp -> Maybe Text
$sel:spaceName:DeleteApp' :: DeleteApp -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
spaceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AppType
appType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appName

instance Data.ToHeaders DeleteApp where
  toHeaders :: DeleteApp -> [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
"SageMaker.DeleteApp" :: 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 DeleteApp where
  toJSON :: DeleteApp -> Value
toJSON DeleteApp' {Maybe Text
Text
AppType
appName :: Text
appType :: AppType
domainId :: Text
userProfileName :: Maybe Text
spaceName :: Maybe Text
$sel:appName:DeleteApp' :: DeleteApp -> Text
$sel:appType:DeleteApp' :: DeleteApp -> AppType
$sel:domainId:DeleteApp' :: DeleteApp -> Text
$sel:userProfileName:DeleteApp' :: DeleteApp -> Maybe Text
$sel:spaceName:DeleteApp' :: DeleteApp -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SpaceName" 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
spaceName,
            (Key
"UserProfileName" 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
userProfileName,
            forall a. a -> Maybe a
Prelude.Just (Key
"DomainId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainId),
            forall a. a -> Maybe a
Prelude.Just (Key
"AppType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AppType
appType),
            forall a. a -> Maybe a
Prelude.Just (Key
"AppName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
appName)
          ]
      )

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

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

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

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

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