{-# 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.Evidently.StartLaunch
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts an existing launch. To create a launch, use
-- <https://docs.aws.amazon.com/cloudwatchevidently/latest/APIReference/API_CreateLaunch.html CreateLaunch>.
module Amazonka.Evidently.StartLaunch
  ( -- * Creating a Request
    StartLaunch (..),
    newStartLaunch,

    -- * Request Lenses
    startLaunch_launch,
    startLaunch_project,

    -- * Destructuring the Response
    StartLaunchResponse (..),
    newStartLaunchResponse,

    -- * Response Lenses
    startLaunchResponse_httpStatus,
    startLaunchResponse_launch,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Evidently.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartLaunch' smart constructor.
data StartLaunch = StartLaunch'
  { -- | The name of the launch to start.
    StartLaunch -> Text
launch :: Prelude.Text,
    -- | The name or ARN of the project that contains the launch to start.
    StartLaunch -> Text
project :: Prelude.Text
  }
  deriving (StartLaunch -> StartLaunch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartLaunch -> StartLaunch -> Bool
$c/= :: StartLaunch -> StartLaunch -> Bool
== :: StartLaunch -> StartLaunch -> Bool
$c== :: StartLaunch -> StartLaunch -> Bool
Prelude.Eq, ReadPrec [StartLaunch]
ReadPrec StartLaunch
Int -> ReadS StartLaunch
ReadS [StartLaunch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartLaunch]
$creadListPrec :: ReadPrec [StartLaunch]
readPrec :: ReadPrec StartLaunch
$creadPrec :: ReadPrec StartLaunch
readList :: ReadS [StartLaunch]
$creadList :: ReadS [StartLaunch]
readsPrec :: Int -> ReadS StartLaunch
$creadsPrec :: Int -> ReadS StartLaunch
Prelude.Read, Int -> StartLaunch -> ShowS
[StartLaunch] -> ShowS
StartLaunch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartLaunch] -> ShowS
$cshowList :: [StartLaunch] -> ShowS
show :: StartLaunch -> String
$cshow :: StartLaunch -> String
showsPrec :: Int -> StartLaunch -> ShowS
$cshowsPrec :: Int -> StartLaunch -> ShowS
Prelude.Show, forall x. Rep StartLaunch x -> StartLaunch
forall x. StartLaunch -> Rep StartLaunch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartLaunch x -> StartLaunch
$cfrom :: forall x. StartLaunch -> Rep StartLaunch x
Prelude.Generic)

-- |
-- Create a value of 'StartLaunch' 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:
--
-- 'launch', 'startLaunch_launch' - The name of the launch to start.
--
-- 'project', 'startLaunch_project' - The name or ARN of the project that contains the launch to start.
newStartLaunch ::
  -- | 'launch'
  Prelude.Text ->
  -- | 'project'
  Prelude.Text ->
  StartLaunch
newStartLaunch :: Text -> Text -> StartLaunch
newStartLaunch Text
pLaunch_ Text
pProject_ =
  StartLaunch'
    { $sel:launch:StartLaunch' :: Text
launch = Text
pLaunch_,
      $sel:project:StartLaunch' :: Text
project = Text
pProject_
    }

-- | The name of the launch to start.
startLaunch_launch :: Lens.Lens' StartLaunch Prelude.Text
startLaunch_launch :: Lens' StartLaunch Text
startLaunch_launch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartLaunch' {Text
launch :: Text
$sel:launch:StartLaunch' :: StartLaunch -> Text
launch} -> Text
launch) (\s :: StartLaunch
s@StartLaunch' {} Text
a -> StartLaunch
s {$sel:launch:StartLaunch' :: Text
launch = Text
a} :: StartLaunch)

-- | The name or ARN of the project that contains the launch to start.
startLaunch_project :: Lens.Lens' StartLaunch Prelude.Text
startLaunch_project :: Lens' StartLaunch Text
startLaunch_project = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartLaunch' {Text
project :: Text
$sel:project:StartLaunch' :: StartLaunch -> Text
project} -> Text
project) (\s :: StartLaunch
s@StartLaunch' {} Text
a -> StartLaunch
s {$sel:project:StartLaunch' :: Text
project = Text
a} :: StartLaunch)

instance Core.AWSRequest StartLaunch where
  type AWSResponse StartLaunch = StartLaunchResponse
  request :: (Service -> Service) -> StartLaunch -> Request StartLaunch
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 StartLaunch
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartLaunch)))
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 -> Launch -> StartLaunchResponse
StartLaunchResponse'
            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
"launch")
      )

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

instance Prelude.NFData StartLaunch where
  rnf :: StartLaunch -> ()
rnf StartLaunch' {Text
project :: Text
launch :: Text
$sel:project:StartLaunch' :: StartLaunch -> Text
$sel:launch:StartLaunch' :: StartLaunch -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
launch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
project

instance Data.ToHeaders StartLaunch where
  toHeaders :: StartLaunch -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartLaunch where
  toJSON :: StartLaunch -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StartLaunch where
  toPath :: StartLaunch -> ByteString
toPath StartLaunch' {Text
project :: Text
launch :: Text
$sel:project:StartLaunch' :: StartLaunch -> Text
$sel:launch:StartLaunch' :: StartLaunch -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/projects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
project,
        ByteString
"/launches/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
launch,
        ByteString
"/start"
      ]

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

-- | /See:/ 'newStartLaunchResponse' smart constructor.
data StartLaunchResponse = StartLaunchResponse'
  { -- | The response's http status code.
    StartLaunchResponse -> Int
httpStatus :: Prelude.Int,
    -- | A structure that contains information about the launch that was started.
    StartLaunchResponse -> Launch
launch :: Launch
  }
  deriving (StartLaunchResponse -> StartLaunchResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartLaunchResponse -> StartLaunchResponse -> Bool
$c/= :: StartLaunchResponse -> StartLaunchResponse -> Bool
== :: StartLaunchResponse -> StartLaunchResponse -> Bool
$c== :: StartLaunchResponse -> StartLaunchResponse -> Bool
Prelude.Eq, ReadPrec [StartLaunchResponse]
ReadPrec StartLaunchResponse
Int -> ReadS StartLaunchResponse
ReadS [StartLaunchResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartLaunchResponse]
$creadListPrec :: ReadPrec [StartLaunchResponse]
readPrec :: ReadPrec StartLaunchResponse
$creadPrec :: ReadPrec StartLaunchResponse
readList :: ReadS [StartLaunchResponse]
$creadList :: ReadS [StartLaunchResponse]
readsPrec :: Int -> ReadS StartLaunchResponse
$creadsPrec :: Int -> ReadS StartLaunchResponse
Prelude.Read, Int -> StartLaunchResponse -> ShowS
[StartLaunchResponse] -> ShowS
StartLaunchResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartLaunchResponse] -> ShowS
$cshowList :: [StartLaunchResponse] -> ShowS
show :: StartLaunchResponse -> String
$cshow :: StartLaunchResponse -> String
showsPrec :: Int -> StartLaunchResponse -> ShowS
$cshowsPrec :: Int -> StartLaunchResponse -> ShowS
Prelude.Show, forall x. Rep StartLaunchResponse x -> StartLaunchResponse
forall x. StartLaunchResponse -> Rep StartLaunchResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartLaunchResponse x -> StartLaunchResponse
$cfrom :: forall x. StartLaunchResponse -> Rep StartLaunchResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartLaunchResponse' 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', 'startLaunchResponse_httpStatus' - The response's http status code.
--
-- 'launch', 'startLaunchResponse_launch' - A structure that contains information about the launch that was started.
newStartLaunchResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'launch'
  Launch ->
  StartLaunchResponse
newStartLaunchResponse :: Int -> Launch -> StartLaunchResponse
newStartLaunchResponse Int
pHttpStatus_ Launch
pLaunch_ =
  StartLaunchResponse'
    { $sel:httpStatus:StartLaunchResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:launch:StartLaunchResponse' :: Launch
launch = Launch
pLaunch_
    }

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

-- | A structure that contains information about the launch that was started.
startLaunchResponse_launch :: Lens.Lens' StartLaunchResponse Launch
startLaunchResponse_launch :: Lens' StartLaunchResponse Launch
startLaunchResponse_launch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartLaunchResponse' {Launch
launch :: Launch
$sel:launch:StartLaunchResponse' :: StartLaunchResponse -> Launch
launch} -> Launch
launch) (\s :: StartLaunchResponse
s@StartLaunchResponse' {} Launch
a -> StartLaunchResponse
s {$sel:launch:StartLaunchResponse' :: Launch
launch = Launch
a} :: StartLaunchResponse)

instance Prelude.NFData StartLaunchResponse where
  rnf :: StartLaunchResponse -> ()
rnf StartLaunchResponse' {Int
Launch
launch :: Launch
httpStatus :: Int
$sel:launch:StartLaunchResponse' :: StartLaunchResponse -> Launch
$sel:httpStatus:StartLaunchResponse' :: StartLaunchResponse -> 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 Launch
launch