{-# 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.Lightsail.CreateCloudFormationStack
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an AWS CloudFormation stack, which creates a new Amazon EC2
-- instance from an exported Amazon Lightsail snapshot. This operation
-- results in a CloudFormation stack record that can be used to track the
-- AWS CloudFormation stack created. Use the
-- @get cloud formation stack records@ operation to get a list of the
-- CloudFormation stacks created.
--
-- Wait until after your new Amazon EC2 instance is created before running
-- the @create cloud formation stack@ operation again with the same export
-- snapshot record.
module Amazonka.Lightsail.CreateCloudFormationStack
  ( -- * Creating a Request
    CreateCloudFormationStack (..),
    newCreateCloudFormationStack,

    -- * Request Lenses
    createCloudFormationStack_instances,

    -- * Destructuring the Response
    CreateCloudFormationStackResponse (..),
    newCreateCloudFormationStackResponse,

    -- * Response Lenses
    createCloudFormationStackResponse_operations,
    createCloudFormationStackResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateCloudFormationStack' smart constructor.
data CreateCloudFormationStack = CreateCloudFormationStack'
  { -- | An array of parameters that will be used to create the new Amazon EC2
    -- instance. You can only pass one instance entry at a time in this array.
    -- You will get an invalid parameter error if you pass more than one
    -- instance entry in this array.
    CreateCloudFormationStack -> [InstanceEntry]
instances :: [InstanceEntry]
  }
  deriving (CreateCloudFormationStack -> CreateCloudFormationStack -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCloudFormationStack -> CreateCloudFormationStack -> Bool
$c/= :: CreateCloudFormationStack -> CreateCloudFormationStack -> Bool
== :: CreateCloudFormationStack -> CreateCloudFormationStack -> Bool
$c== :: CreateCloudFormationStack -> CreateCloudFormationStack -> Bool
Prelude.Eq, ReadPrec [CreateCloudFormationStack]
ReadPrec CreateCloudFormationStack
Int -> ReadS CreateCloudFormationStack
ReadS [CreateCloudFormationStack]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCloudFormationStack]
$creadListPrec :: ReadPrec [CreateCloudFormationStack]
readPrec :: ReadPrec CreateCloudFormationStack
$creadPrec :: ReadPrec CreateCloudFormationStack
readList :: ReadS [CreateCloudFormationStack]
$creadList :: ReadS [CreateCloudFormationStack]
readsPrec :: Int -> ReadS CreateCloudFormationStack
$creadsPrec :: Int -> ReadS CreateCloudFormationStack
Prelude.Read, Int -> CreateCloudFormationStack -> ShowS
[CreateCloudFormationStack] -> ShowS
CreateCloudFormationStack -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCloudFormationStack] -> ShowS
$cshowList :: [CreateCloudFormationStack] -> ShowS
show :: CreateCloudFormationStack -> String
$cshow :: CreateCloudFormationStack -> String
showsPrec :: Int -> CreateCloudFormationStack -> ShowS
$cshowsPrec :: Int -> CreateCloudFormationStack -> ShowS
Prelude.Show, forall x.
Rep CreateCloudFormationStack x -> CreateCloudFormationStack
forall x.
CreateCloudFormationStack -> Rep CreateCloudFormationStack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCloudFormationStack x -> CreateCloudFormationStack
$cfrom :: forall x.
CreateCloudFormationStack -> Rep CreateCloudFormationStack x
Prelude.Generic)

-- |
-- Create a value of 'CreateCloudFormationStack' 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:
--
-- 'instances', 'createCloudFormationStack_instances' - An array of parameters that will be used to create the new Amazon EC2
-- instance. You can only pass one instance entry at a time in this array.
-- You will get an invalid parameter error if you pass more than one
-- instance entry in this array.
newCreateCloudFormationStack ::
  CreateCloudFormationStack
newCreateCloudFormationStack :: CreateCloudFormationStack
newCreateCloudFormationStack =
  CreateCloudFormationStack'
    { $sel:instances:CreateCloudFormationStack' :: [InstanceEntry]
instances =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | An array of parameters that will be used to create the new Amazon EC2
-- instance. You can only pass one instance entry at a time in this array.
-- You will get an invalid parameter error if you pass more than one
-- instance entry in this array.
createCloudFormationStack_instances :: Lens.Lens' CreateCloudFormationStack [InstanceEntry]
createCloudFormationStack_instances :: Lens' CreateCloudFormationStack [InstanceEntry]
createCloudFormationStack_instances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFormationStack' {[InstanceEntry]
instances :: [InstanceEntry]
$sel:instances:CreateCloudFormationStack' :: CreateCloudFormationStack -> [InstanceEntry]
instances} -> [InstanceEntry]
instances) (\s :: CreateCloudFormationStack
s@CreateCloudFormationStack' {} [InstanceEntry]
a -> CreateCloudFormationStack
s {$sel:instances:CreateCloudFormationStack' :: [InstanceEntry]
instances = [InstanceEntry]
a} :: CreateCloudFormationStack) 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 CreateCloudFormationStack where
  type
    AWSResponse CreateCloudFormationStack =
      CreateCloudFormationStackResponse
  request :: (Service -> Service)
-> CreateCloudFormationStack -> Request CreateCloudFormationStack
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 CreateCloudFormationStack
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateCloudFormationStack)))
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 [Operation] -> Int -> CreateCloudFormationStackResponse
CreateCloudFormationStackResponse'
            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
"operations" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 CreateCloudFormationStack where
  hashWithSalt :: Int -> CreateCloudFormationStack -> Int
hashWithSalt Int
_salt CreateCloudFormationStack' {[InstanceEntry]
instances :: [InstanceEntry]
$sel:instances:CreateCloudFormationStack' :: CreateCloudFormationStack -> [InstanceEntry]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [InstanceEntry]
instances

instance Prelude.NFData CreateCloudFormationStack where
  rnf :: CreateCloudFormationStack -> ()
rnf CreateCloudFormationStack' {[InstanceEntry]
instances :: [InstanceEntry]
$sel:instances:CreateCloudFormationStack' :: CreateCloudFormationStack -> [InstanceEntry]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [InstanceEntry]
instances

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

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

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

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

-- | /See:/ 'newCreateCloudFormationStackResponse' smart constructor.
data CreateCloudFormationStackResponse = CreateCloudFormationStackResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    CreateCloudFormationStackResponse -> Maybe [Operation]
operations :: Prelude.Maybe [Operation],
    -- | The response's http status code.
    CreateCloudFormationStackResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCloudFormationStackResponse
-> CreateCloudFormationStackResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCloudFormationStackResponse
-> CreateCloudFormationStackResponse -> Bool
$c/= :: CreateCloudFormationStackResponse
-> CreateCloudFormationStackResponse -> Bool
== :: CreateCloudFormationStackResponse
-> CreateCloudFormationStackResponse -> Bool
$c== :: CreateCloudFormationStackResponse
-> CreateCloudFormationStackResponse -> Bool
Prelude.Eq, ReadPrec [CreateCloudFormationStackResponse]
ReadPrec CreateCloudFormationStackResponse
Int -> ReadS CreateCloudFormationStackResponse
ReadS [CreateCloudFormationStackResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCloudFormationStackResponse]
$creadListPrec :: ReadPrec [CreateCloudFormationStackResponse]
readPrec :: ReadPrec CreateCloudFormationStackResponse
$creadPrec :: ReadPrec CreateCloudFormationStackResponse
readList :: ReadS [CreateCloudFormationStackResponse]
$creadList :: ReadS [CreateCloudFormationStackResponse]
readsPrec :: Int -> ReadS CreateCloudFormationStackResponse
$creadsPrec :: Int -> ReadS CreateCloudFormationStackResponse
Prelude.Read, Int -> CreateCloudFormationStackResponse -> ShowS
[CreateCloudFormationStackResponse] -> ShowS
CreateCloudFormationStackResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCloudFormationStackResponse] -> ShowS
$cshowList :: [CreateCloudFormationStackResponse] -> ShowS
show :: CreateCloudFormationStackResponse -> String
$cshow :: CreateCloudFormationStackResponse -> String
showsPrec :: Int -> CreateCloudFormationStackResponse -> ShowS
$cshowsPrec :: Int -> CreateCloudFormationStackResponse -> ShowS
Prelude.Show, forall x.
Rep CreateCloudFormationStackResponse x
-> CreateCloudFormationStackResponse
forall x.
CreateCloudFormationStackResponse
-> Rep CreateCloudFormationStackResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCloudFormationStackResponse x
-> CreateCloudFormationStackResponse
$cfrom :: forall x.
CreateCloudFormationStackResponse
-> Rep CreateCloudFormationStackResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCloudFormationStackResponse' 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:
--
-- 'operations', 'createCloudFormationStackResponse_operations' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'createCloudFormationStackResponse_httpStatus' - The response's http status code.
newCreateCloudFormationStackResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCloudFormationStackResponse
newCreateCloudFormationStackResponse :: Int -> CreateCloudFormationStackResponse
newCreateCloudFormationStackResponse Int
pHttpStatus_ =
  CreateCloudFormationStackResponse'
    { $sel:operations:CreateCloudFormationStackResponse' :: Maybe [Operation]
operations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCloudFormationStackResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
createCloudFormationStackResponse_operations :: Lens.Lens' CreateCloudFormationStackResponse (Prelude.Maybe [Operation])
createCloudFormationStackResponse_operations :: Lens' CreateCloudFormationStackResponse (Maybe [Operation])
createCloudFormationStackResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFormationStackResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:CreateCloudFormationStackResponse' :: CreateCloudFormationStackResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: CreateCloudFormationStackResponse
s@CreateCloudFormationStackResponse' {} Maybe [Operation]
a -> CreateCloudFormationStackResponse
s {$sel:operations:CreateCloudFormationStackResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: CreateCloudFormationStackResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    CreateCloudFormationStackResponse
  where
  rnf :: CreateCloudFormationStackResponse -> ()
rnf CreateCloudFormationStackResponse' {Int
Maybe [Operation]
httpStatus :: Int
operations :: Maybe [Operation]
$sel:httpStatus:CreateCloudFormationStackResponse' :: CreateCloudFormationStackResponse -> Int
$sel:operations:CreateCloudFormationStackResponse' :: CreateCloudFormationStackResponse -> Maybe [Operation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Operation]
operations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus