{-# 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.ResumeService
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resume an active App Runner service. App Runner provisions compute
-- capacity for the 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.
module Amazonka.AppRunner.ResumeService
  ( -- * Creating a Request
    ResumeService (..),
    newResumeService,

    -- * Request Lenses
    resumeService_serviceArn,

    -- * Destructuring the Response
    ResumeServiceResponse (..),
    newResumeServiceResponse,

    -- * Response Lenses
    resumeServiceResponse_operationId,
    resumeServiceResponse_httpStatus,
    resumeServiceResponse_service,
  )
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:/ 'newResumeService' smart constructor.
data ResumeService = ResumeService'
  { -- | The Amazon Resource Name (ARN) of the App Runner service that you want
    -- to resume.
    ResumeService -> Text
serviceArn :: Prelude.Text
  }
  deriving (ResumeService -> ResumeService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResumeService -> ResumeService -> Bool
$c/= :: ResumeService -> ResumeService -> Bool
== :: ResumeService -> ResumeService -> Bool
$c== :: ResumeService -> ResumeService -> Bool
Prelude.Eq, ReadPrec [ResumeService]
ReadPrec ResumeService
Int -> ReadS ResumeService
ReadS [ResumeService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResumeService]
$creadListPrec :: ReadPrec [ResumeService]
readPrec :: ReadPrec ResumeService
$creadPrec :: ReadPrec ResumeService
readList :: ReadS [ResumeService]
$creadList :: ReadS [ResumeService]
readsPrec :: Int -> ReadS ResumeService
$creadsPrec :: Int -> ReadS ResumeService
Prelude.Read, Int -> ResumeService -> ShowS
[ResumeService] -> ShowS
ResumeService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResumeService] -> ShowS
$cshowList :: [ResumeService] -> ShowS
show :: ResumeService -> String
$cshow :: ResumeService -> String
showsPrec :: Int -> ResumeService -> ShowS
$cshowsPrec :: Int -> ResumeService -> ShowS
Prelude.Show, forall x. Rep ResumeService x -> ResumeService
forall x. ResumeService -> Rep ResumeService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResumeService x -> ResumeService
$cfrom :: forall x. ResumeService -> Rep ResumeService x
Prelude.Generic)

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

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

instance Core.AWSRequest ResumeService where
  type
    AWSResponse ResumeService =
      ResumeServiceResponse
  request :: (Service -> Service) -> ResumeService -> Request ResumeService
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 ResumeService
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ResumeService)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> Service -> ResumeServiceResponse
ResumeServiceResponse'
            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
"OperationId")
            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))
            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")
      )

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

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

instance Data.ToHeaders ResumeService where
  toHeaders :: ResumeService -> 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.ResumeService" :: 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 ResumeService where
  toJSON :: ResumeService -> Value
toJSON ResumeService' {Text
serviceArn :: Text
$sel:serviceArn:ResumeService' :: ResumeService -> 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 ResumeService where
  toPath :: ResumeService -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newResumeServiceResponse' smart constructor.
data ResumeServiceResponse = ResumeServiceResponse'
  { -- | 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.
    ResumeServiceResponse -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ResumeServiceResponse -> Int
httpStatus :: Prelude.Int,
    -- | A description of the App Runner service that this request just resumed.
    ResumeServiceResponse -> Service
service :: Service
  }
  deriving (ResumeServiceResponse -> ResumeServiceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResumeServiceResponse -> ResumeServiceResponse -> Bool
$c/= :: ResumeServiceResponse -> ResumeServiceResponse -> Bool
== :: ResumeServiceResponse -> ResumeServiceResponse -> Bool
$c== :: ResumeServiceResponse -> ResumeServiceResponse -> Bool
Prelude.Eq, Int -> ResumeServiceResponse -> ShowS
[ResumeServiceResponse] -> ShowS
ResumeServiceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResumeServiceResponse] -> ShowS
$cshowList :: [ResumeServiceResponse] -> ShowS
show :: ResumeServiceResponse -> String
$cshow :: ResumeServiceResponse -> String
showsPrec :: Int -> ResumeServiceResponse -> ShowS
$cshowsPrec :: Int -> ResumeServiceResponse -> ShowS
Prelude.Show, forall x. Rep ResumeServiceResponse x -> ResumeServiceResponse
forall x. ResumeServiceResponse -> Rep ResumeServiceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResumeServiceResponse x -> ResumeServiceResponse
$cfrom :: forall x. ResumeServiceResponse -> Rep ResumeServiceResponse x
Prelude.Generic)

-- |
-- Create a value of 'ResumeServiceResponse' 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:
--
-- 'operationId', 'resumeServiceResponse_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.
--
-- 'httpStatus', 'resumeServiceResponse_httpStatus' - The response's http status code.
--
-- 'service', 'resumeServiceResponse_service' - A description of the App Runner service that this request just resumed.
newResumeServiceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'service'
  Service ->
  ResumeServiceResponse
newResumeServiceResponse :: Int -> Service -> ResumeServiceResponse
newResumeServiceResponse Int
pHttpStatus_ Service
pService_ =
  ResumeServiceResponse'
    { $sel:operationId:ResumeServiceResponse' :: Maybe Text
operationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ResumeServiceResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:service:ResumeServiceResponse' :: Service
service = Service
pService_
    }

-- | 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.
resumeServiceResponse_operationId :: Lens.Lens' ResumeServiceResponse (Prelude.Maybe Prelude.Text)
resumeServiceResponse_operationId :: Lens' ResumeServiceResponse (Maybe Text)
resumeServiceResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResumeServiceResponse' {Maybe Text
operationId :: Maybe Text
$sel:operationId:ResumeServiceResponse' :: ResumeServiceResponse -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: ResumeServiceResponse
s@ResumeServiceResponse' {} Maybe Text
a -> ResumeServiceResponse
s {$sel:operationId:ResumeServiceResponse' :: Maybe Text
operationId = Maybe Text
a} :: ResumeServiceResponse)

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

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

instance Prelude.NFData ResumeServiceResponse where
  rnf :: ResumeServiceResponse -> ()
rnf ResumeServiceResponse' {Int
Maybe Text
Service
service :: Service
httpStatus :: Int
operationId :: Maybe Text
$sel:service:ResumeServiceResponse' :: ResumeServiceResponse -> Service
$sel:httpStatus:ResumeServiceResponse' :: ResumeServiceResponse -> Int
$sel:operationId:ResumeServiceResponse' :: ResumeServiceResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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