{-# 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.AppRunner.DeleteService
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete an App Runner service.
--
-- This is an asynchronous operation. On a successful call, you can use the
-- returned @OperationId@ and the ListOperations call to track the
-- operation\'s progress.
--
-- Make sure that you don\'t have any active VPCIngressConnections
-- associated with the service you want to delete.
module Amazonka.AppRunner.DeleteService
  ( -- * Creating a Request
    DeleteService (..),
    newDeleteService,

    -- * Request Lenses
    deleteService_serviceArn,

    -- * Destructuring the Response
    DeleteServiceResponse (..),
    newDeleteServiceResponse,

    -- * Response Lenses
    deleteServiceResponse_httpStatus,
    deleteServiceResponse_service,
    deleteServiceResponse_operationId,
  )
where

import Amazonka.AppRunner.Types
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

-- | /See:/ 'newDeleteService' smart constructor.
data DeleteService = DeleteService'
  { -- | The Amazon Resource Name (ARN) of the App Runner service that you want
    -- to delete.
    DeleteService -> Text
serviceArn :: Prelude.Text
  }
  deriving (DeleteService -> DeleteService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteService -> DeleteService -> Bool
$c/= :: DeleteService -> DeleteService -> Bool
== :: DeleteService -> DeleteService -> Bool
$c== :: DeleteService -> DeleteService -> Bool
Prelude.Eq, ReadPrec [DeleteService]
ReadPrec DeleteService
Int -> ReadS DeleteService
ReadS [DeleteService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteService]
$creadListPrec :: ReadPrec [DeleteService]
readPrec :: ReadPrec DeleteService
$creadPrec :: ReadPrec DeleteService
readList :: ReadS [DeleteService]
$creadList :: ReadS [DeleteService]
readsPrec :: Int -> ReadS DeleteService
$creadsPrec :: Int -> ReadS DeleteService
Prelude.Read, Int -> DeleteService -> ShowS
[DeleteService] -> ShowS
DeleteService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteService] -> ShowS
$cshowList :: [DeleteService] -> ShowS
show :: DeleteService -> String
$cshow :: DeleteService -> String
showsPrec :: Int -> DeleteService -> ShowS
$cshowsPrec :: Int -> DeleteService -> ShowS
Prelude.Show, forall x. Rep DeleteService x -> DeleteService
forall x. DeleteService -> Rep DeleteService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteService x -> DeleteService
$cfrom :: forall x. DeleteService -> Rep DeleteService x
Prelude.Generic)

-- |
-- Create a value of 'DeleteService' 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:
--
-- 'serviceArn', 'deleteService_serviceArn' - The Amazon Resource Name (ARN) of the App Runner service that you want
-- to delete.
newDeleteService ::
  -- | 'serviceArn'
  Prelude.Text ->
  DeleteService
newDeleteService :: Text -> DeleteService
newDeleteService Text
pServiceArn_ =
  DeleteService' {$sel:serviceArn:DeleteService' :: Text
serviceArn = Text
pServiceArn_}

-- | The Amazon Resource Name (ARN) of the App Runner service that you want
-- to delete.
deleteService_serviceArn :: Lens.Lens' DeleteService Prelude.Text
deleteService_serviceArn :: Lens' DeleteService Text
deleteService_serviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteService' {Text
serviceArn :: Text
$sel:serviceArn:DeleteService' :: DeleteService -> Text
serviceArn} -> Text
serviceArn) (\s :: DeleteService
s@DeleteService' {} Text
a -> DeleteService
s {$sel:serviceArn:DeleteService' :: Text
serviceArn = Text
a} :: DeleteService)

instance Core.AWSRequest DeleteService where
  type
    AWSResponse DeleteService =
      DeleteServiceResponse
  request :: (Service -> Service) -> DeleteService -> Request DeleteService
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 DeleteService
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteService)))
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 ->
          Int -> Service -> Text -> DeleteServiceResponse
DeleteServiceResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Service")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"OperationId")
      )

instance Prelude.Hashable DeleteService where
  hashWithSalt :: Int -> DeleteService -> Int
hashWithSalt Int
_salt DeleteService' {Text
serviceArn :: Text
$sel:serviceArn:DeleteService' :: DeleteService -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceArn

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

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

instance Data.ToJSON DeleteService where
  toJSON :: DeleteService -> Value
toJSON DeleteService' {Text
serviceArn :: Text
$sel:serviceArn:DeleteService' :: DeleteService -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ServiceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceArn)]
      )

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

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

-- | /See:/ 'newDeleteServiceResponse' smart constructor.
data DeleteServiceResponse = DeleteServiceResponse'
  { -- | The response's http status code.
    DeleteServiceResponse -> Int
httpStatus :: Prelude.Int,
    -- | A description of the App Runner service that this request just deleted.
    DeleteServiceResponse -> Service
service :: Service,
    -- | The unique ID of the asynchronous operation that this request started.
    -- You can use it combined with the ListOperations call to track the
    -- operation\'s progress.
    DeleteServiceResponse -> Text
operationId :: Prelude.Text
  }
  deriving (DeleteServiceResponse -> DeleteServiceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteServiceResponse -> DeleteServiceResponse -> Bool
$c/= :: DeleteServiceResponse -> DeleteServiceResponse -> Bool
== :: DeleteServiceResponse -> DeleteServiceResponse -> Bool
$c== :: DeleteServiceResponse -> DeleteServiceResponse -> Bool
Prelude.Eq, Int -> DeleteServiceResponse -> ShowS
[DeleteServiceResponse] -> ShowS
DeleteServiceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteServiceResponse] -> ShowS
$cshowList :: [DeleteServiceResponse] -> ShowS
show :: DeleteServiceResponse -> String
$cshow :: DeleteServiceResponse -> String
showsPrec :: Int -> DeleteServiceResponse -> ShowS
$cshowsPrec :: Int -> DeleteServiceResponse -> ShowS
Prelude.Show, forall x. Rep DeleteServiceResponse x -> DeleteServiceResponse
forall x. DeleteServiceResponse -> Rep DeleteServiceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteServiceResponse x -> DeleteServiceResponse
$cfrom :: forall x. DeleteServiceResponse -> Rep DeleteServiceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteServiceResponse' 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:
--
-- 'httpStatus', 'deleteServiceResponse_httpStatus' - The response's http status code.
--
-- 'service', 'deleteServiceResponse_service' - A description of the App Runner service that this request just deleted.
--
-- 'operationId', 'deleteServiceResponse_operationId' - The unique ID of the asynchronous operation that this request started.
-- You can use it combined with the ListOperations call to track the
-- operation\'s progress.
newDeleteServiceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'service'
  Service ->
  -- | 'operationId'
  Prelude.Text ->
  DeleteServiceResponse
newDeleteServiceResponse :: Int -> Service -> Text -> DeleteServiceResponse
newDeleteServiceResponse
  Int
pHttpStatus_
  Service
pService_
  Text
pOperationId_ =
    DeleteServiceResponse'
      { $sel:httpStatus:DeleteServiceResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:service:DeleteServiceResponse' :: Service
service = Service
pService_,
        $sel:operationId:DeleteServiceResponse' :: Text
operationId = Text
pOperationId_
      }

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

-- | A description of the App Runner service that this request just deleted.
deleteServiceResponse_service :: Lens.Lens' DeleteServiceResponse Service
deleteServiceResponse_service :: Lens' DeleteServiceResponse Service
deleteServiceResponse_service = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteServiceResponse' {Service
service :: Service
$sel:service:DeleteServiceResponse' :: DeleteServiceResponse -> Service
service} -> Service
service) (\s :: DeleteServiceResponse
s@DeleteServiceResponse' {} Service
a -> DeleteServiceResponse
s {$sel:service:DeleteServiceResponse' :: Service
service = Service
a} :: DeleteServiceResponse)

-- | The unique ID of the asynchronous operation that this request started.
-- You can use it combined with the ListOperations call to track the
-- operation\'s progress.
deleteServiceResponse_operationId :: Lens.Lens' DeleteServiceResponse Prelude.Text
deleteServiceResponse_operationId :: Lens' DeleteServiceResponse Text
deleteServiceResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteServiceResponse' {Text
operationId :: Text
$sel:operationId:DeleteServiceResponse' :: DeleteServiceResponse -> Text
operationId} -> Text
operationId) (\s :: DeleteServiceResponse
s@DeleteServiceResponse' {} Text
a -> DeleteServiceResponse
s {$sel:operationId:DeleteServiceResponse' :: Text
operationId = Text
a} :: DeleteServiceResponse)

instance Prelude.NFData DeleteServiceResponse where
  rnf :: DeleteServiceResponse -> ()
rnf DeleteServiceResponse' {Int
Text
Service
operationId :: Text
service :: Service
httpStatus :: Int
$sel:operationId:DeleteServiceResponse' :: DeleteServiceResponse -> Text
$sel:service:DeleteServiceResponse' :: DeleteServiceResponse -> Service
$sel:httpStatus:DeleteServiceResponse' :: DeleteServiceResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Service
service
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
operationId