{-# 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.MGN.StartCutover
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Launches a Cutover Instance for specific Source Servers. This command
-- starts a LAUNCH job whose initiatedBy property is StartCutover and
-- changes the SourceServer.lifeCycle.state property to CUTTING_OVER.
module Amazonka.MGN.StartCutover
  ( -- * Creating a Request
    StartCutover (..),
    newStartCutover,

    -- * Request Lenses
    startCutover_tags,
    startCutover_sourceServerIDs,

    -- * Destructuring the Response
    StartCutoverResponse (..),
    newStartCutoverResponse,

    -- * Response Lenses
    startCutoverResponse_job,
    startCutoverResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartCutover' smart constructor.
data StartCutover = StartCutover'
  { -- | Start Cutover by Tags.
    StartCutover -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | Start Cutover by Source Server IDs.
    StartCutover -> NonEmpty Text
sourceServerIDs :: Prelude.NonEmpty Prelude.Text
  }
  deriving (StartCutover -> StartCutover -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCutover -> StartCutover -> Bool
$c/= :: StartCutover -> StartCutover -> Bool
== :: StartCutover -> StartCutover -> Bool
$c== :: StartCutover -> StartCutover -> Bool
Prelude.Eq, Int -> StartCutover -> ShowS
[StartCutover] -> ShowS
StartCutover -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCutover] -> ShowS
$cshowList :: [StartCutover] -> ShowS
show :: StartCutover -> String
$cshow :: StartCutover -> String
showsPrec :: Int -> StartCutover -> ShowS
$cshowsPrec :: Int -> StartCutover -> ShowS
Prelude.Show, forall x. Rep StartCutover x -> StartCutover
forall x. StartCutover -> Rep StartCutover x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartCutover x -> StartCutover
$cfrom :: forall x. StartCutover -> Rep StartCutover x
Prelude.Generic)

-- |
-- Create a value of 'StartCutover' 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:
--
-- 'tags', 'startCutover_tags' - Start Cutover by Tags.
--
-- 'sourceServerIDs', 'startCutover_sourceServerIDs' - Start Cutover by Source Server IDs.
newStartCutover ::
  -- | 'sourceServerIDs'
  Prelude.NonEmpty Prelude.Text ->
  StartCutover
newStartCutover :: NonEmpty Text -> StartCutover
newStartCutover NonEmpty Text
pSourceServerIDs_ =
  StartCutover'
    { $sel:tags:StartCutover' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceServerIDs:StartCutover' :: NonEmpty Text
sourceServerIDs =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pSourceServerIDs_
    }

-- | Start Cutover by Tags.
startCutover_tags :: Lens.Lens' StartCutover (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startCutover_tags :: Lens' StartCutover (Maybe (HashMap Text Text))
startCutover_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCutover' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:StartCutover' :: StartCutover -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: StartCutover
s@StartCutover' {} Maybe (Sensitive (HashMap Text Text))
a -> StartCutover
s {$sel:tags:StartCutover' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: StartCutover) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | Start Cutover by Source Server IDs.
startCutover_sourceServerIDs :: Lens.Lens' StartCutover (Prelude.NonEmpty Prelude.Text)
startCutover_sourceServerIDs :: Lens' StartCutover (NonEmpty Text)
startCutover_sourceServerIDs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCutover' {NonEmpty Text
sourceServerIDs :: NonEmpty Text
$sel:sourceServerIDs:StartCutover' :: StartCutover -> NonEmpty Text
sourceServerIDs} -> NonEmpty Text
sourceServerIDs) (\s :: StartCutover
s@StartCutover' {} NonEmpty Text
a -> StartCutover
s {$sel:sourceServerIDs:StartCutover' :: NonEmpty Text
sourceServerIDs = NonEmpty Text
a} :: StartCutover) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest StartCutover where
  type AWSResponse StartCutover = StartCutoverResponse
  request :: (Service -> Service) -> StartCutover -> Request StartCutover
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 StartCutover
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartCutover)))
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 Job -> Int -> StartCutoverResponse
StartCutoverResponse'
            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
"job")
            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))
      )

instance Prelude.Hashable StartCutover where
  hashWithSalt :: Int -> StartCutover -> Int
hashWithSalt Int
_salt StartCutover' {Maybe (Sensitive (HashMap Text Text))
NonEmpty Text
sourceServerIDs :: NonEmpty Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerIDs:StartCutover' :: StartCutover -> NonEmpty Text
$sel:tags:StartCutover' :: StartCutover -> Maybe (Sensitive (HashMap Text Text))
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
sourceServerIDs

instance Prelude.NFData StartCutover where
  rnf :: StartCutover -> ()
rnf StartCutover' {Maybe (Sensitive (HashMap Text Text))
NonEmpty Text
sourceServerIDs :: NonEmpty Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerIDs:StartCutover' :: StartCutover -> NonEmpty Text
$sel:tags:StartCutover' :: StartCutover -> Maybe (Sensitive (HashMap Text Text))
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
sourceServerIDs

instance Data.ToHeaders StartCutover where
  toHeaders :: StartCutover -> 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 StartCutover where
  toJSON :: StartCutover -> Value
toJSON StartCutover' {Maybe (Sensitive (HashMap Text Text))
NonEmpty Text
sourceServerIDs :: NonEmpty Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerIDs:StartCutover' :: StartCutover -> NonEmpty Text
$sel:tags:StartCutover' :: StartCutover -> Maybe (Sensitive (HashMap Text Text))
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" 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 (Sensitive (HashMap Text Text))
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"sourceServerIDs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
sourceServerIDs)
          ]
      )

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

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

-- | /See:/ 'newStartCutoverResponse' smart constructor.
data StartCutoverResponse = StartCutoverResponse'
  { -- | Start Cutover Job response.
    StartCutoverResponse -> Maybe Job
job :: Prelude.Maybe Job,
    -- | The response's http status code.
    StartCutoverResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartCutoverResponse -> StartCutoverResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCutoverResponse -> StartCutoverResponse -> Bool
$c/= :: StartCutoverResponse -> StartCutoverResponse -> Bool
== :: StartCutoverResponse -> StartCutoverResponse -> Bool
$c== :: StartCutoverResponse -> StartCutoverResponse -> Bool
Prelude.Eq, Int -> StartCutoverResponse -> ShowS
[StartCutoverResponse] -> ShowS
StartCutoverResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCutoverResponse] -> ShowS
$cshowList :: [StartCutoverResponse] -> ShowS
show :: StartCutoverResponse -> String
$cshow :: StartCutoverResponse -> String
showsPrec :: Int -> StartCutoverResponse -> ShowS
$cshowsPrec :: Int -> StartCutoverResponse -> ShowS
Prelude.Show, forall x. Rep StartCutoverResponse x -> StartCutoverResponse
forall x. StartCutoverResponse -> Rep StartCutoverResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartCutoverResponse x -> StartCutoverResponse
$cfrom :: forall x. StartCutoverResponse -> Rep StartCutoverResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartCutoverResponse' 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:
--
-- 'job', 'startCutoverResponse_job' - Start Cutover Job response.
--
-- 'httpStatus', 'startCutoverResponse_httpStatus' - The response's http status code.
newStartCutoverResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartCutoverResponse
newStartCutoverResponse :: Int -> StartCutoverResponse
newStartCutoverResponse Int
pHttpStatus_ =
  StartCutoverResponse'
    { $sel:job:StartCutoverResponse' :: Maybe Job
job = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartCutoverResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Start Cutover Job response.
startCutoverResponse_job :: Lens.Lens' StartCutoverResponse (Prelude.Maybe Job)
startCutoverResponse_job :: Lens' StartCutoverResponse (Maybe Job)
startCutoverResponse_job = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCutoverResponse' {Maybe Job
job :: Maybe Job
$sel:job:StartCutoverResponse' :: StartCutoverResponse -> Maybe Job
job} -> Maybe Job
job) (\s :: StartCutoverResponse
s@StartCutoverResponse' {} Maybe Job
a -> StartCutoverResponse
s {$sel:job:StartCutoverResponse' :: Maybe Job
job = Maybe Job
a} :: StartCutoverResponse)

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

instance Prelude.NFData StartCutoverResponse where
  rnf :: StartCutoverResponse -> ()
rnf StartCutoverResponse' {Int
Maybe Job
httpStatus :: Int
job :: Maybe Job
$sel:httpStatus:StartCutoverResponse' :: StartCutoverResponse -> Int
$sel:job:StartCutoverResponse' :: StartCutoverResponse -> Maybe Job
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Job
job
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus