{-# 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.StartDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Initiate a manual deployment of the latest commit in a source code
-- repository or the latest image in a source image repository to an App
-- Runner service.
--
-- For a source code repository, App Runner retrieves the commit and builds
-- a Docker image. For a source image repository, App Runner retrieves the
-- latest Docker image. In both cases, App Runner then deploys the new
-- image to your service and starts a new container instance.
--
-- 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.StartDeployment
  ( -- * Creating a Request
    StartDeployment (..),
    newStartDeployment,

    -- * Request Lenses
    startDeployment_serviceArn,

    -- * Destructuring the Response
    StartDeploymentResponse (..),
    newStartDeploymentResponse,

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

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

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

instance Core.AWSRequest StartDeployment where
  type
    AWSResponse StartDeployment =
      StartDeploymentResponse
  request :: (Service -> Service) -> StartDeployment -> Request StartDeployment
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 StartDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartDeployment)))
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 -> Text -> StartDeploymentResponse
StartDeploymentResponse'
            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
"OperationId")
      )

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

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

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

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

-- | /See:/ 'newStartDeploymentResponse' smart constructor.
data StartDeploymentResponse = StartDeploymentResponse'
  { -- | The response's http status code.
    StartDeploymentResponse -> Int
httpStatus :: Prelude.Int,
    -- | 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.
    StartDeploymentResponse -> Text
operationId :: Prelude.Text
  }
  deriving (StartDeploymentResponse -> StartDeploymentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
$c/= :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
== :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
$c== :: StartDeploymentResponse -> StartDeploymentResponse -> Bool
Prelude.Eq, ReadPrec [StartDeploymentResponse]
ReadPrec StartDeploymentResponse
Int -> ReadS StartDeploymentResponse
ReadS [StartDeploymentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartDeploymentResponse]
$creadListPrec :: ReadPrec [StartDeploymentResponse]
readPrec :: ReadPrec StartDeploymentResponse
$creadPrec :: ReadPrec StartDeploymentResponse
readList :: ReadS [StartDeploymentResponse]
$creadList :: ReadS [StartDeploymentResponse]
readsPrec :: Int -> ReadS StartDeploymentResponse
$creadsPrec :: Int -> ReadS StartDeploymentResponse
Prelude.Read, Int -> StartDeploymentResponse -> ShowS
[StartDeploymentResponse] -> ShowS
StartDeploymentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartDeploymentResponse] -> ShowS
$cshowList :: [StartDeploymentResponse] -> ShowS
show :: StartDeploymentResponse -> String
$cshow :: StartDeploymentResponse -> String
showsPrec :: Int -> StartDeploymentResponse -> ShowS
$cshowsPrec :: Int -> StartDeploymentResponse -> ShowS
Prelude.Show, forall x. Rep StartDeploymentResponse x -> StartDeploymentResponse
forall x. StartDeploymentResponse -> Rep StartDeploymentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartDeploymentResponse x -> StartDeploymentResponse
$cfrom :: forall x. StartDeploymentResponse -> Rep StartDeploymentResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartDeploymentResponse' 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', 'startDeploymentResponse_httpStatus' - The response's http status code.
--
-- 'operationId', 'startDeploymentResponse_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.
newStartDeploymentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'operationId'
  Prelude.Text ->
  StartDeploymentResponse
newStartDeploymentResponse :: Int -> Text -> StartDeploymentResponse
newStartDeploymentResponse Int
pHttpStatus_ Text
pOperationId_ =
  StartDeploymentResponse'
    { $sel:httpStatus:StartDeploymentResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:operationId:StartDeploymentResponse' :: Text
operationId = Text
pOperationId_
    }

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

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

instance Prelude.NFData StartDeploymentResponse where
  rnf :: StartDeploymentResponse -> ()
rnf StartDeploymentResponse' {Int
Text
operationId :: Text
httpStatus :: Int
$sel:operationId:StartDeploymentResponse' :: StartDeploymentResponse -> Text
$sel:httpStatus:StartDeploymentResponse' :: StartDeploymentResponse -> 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 Text
operationId