{-# 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.UnpeerVpc
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Unpeers the Lightsail VPC from the user\'s default VPC.
module Amazonka.Lightsail.UnpeerVpc
  ( -- * Creating a Request
    UnpeerVpc (..),
    newUnpeerVpc,

    -- * Destructuring the Response
    UnpeerVpcResponse (..),
    newUnpeerVpcResponse,

    -- * Response Lenses
    unpeerVpcResponse_operation,
    unpeerVpcResponse_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:/ 'newUnpeerVpc' smart constructor.
data UnpeerVpc = UnpeerVpc'
  {
  }
  deriving (UnpeerVpc -> UnpeerVpc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnpeerVpc -> UnpeerVpc -> Bool
$c/= :: UnpeerVpc -> UnpeerVpc -> Bool
== :: UnpeerVpc -> UnpeerVpc -> Bool
$c== :: UnpeerVpc -> UnpeerVpc -> Bool
Prelude.Eq, ReadPrec [UnpeerVpc]
ReadPrec UnpeerVpc
Int -> ReadS UnpeerVpc
ReadS [UnpeerVpc]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnpeerVpc]
$creadListPrec :: ReadPrec [UnpeerVpc]
readPrec :: ReadPrec UnpeerVpc
$creadPrec :: ReadPrec UnpeerVpc
readList :: ReadS [UnpeerVpc]
$creadList :: ReadS [UnpeerVpc]
readsPrec :: Int -> ReadS UnpeerVpc
$creadsPrec :: Int -> ReadS UnpeerVpc
Prelude.Read, Int -> UnpeerVpc -> ShowS
[UnpeerVpc] -> ShowS
UnpeerVpc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnpeerVpc] -> ShowS
$cshowList :: [UnpeerVpc] -> ShowS
show :: UnpeerVpc -> String
$cshow :: UnpeerVpc -> String
showsPrec :: Int -> UnpeerVpc -> ShowS
$cshowsPrec :: Int -> UnpeerVpc -> ShowS
Prelude.Show, forall x. Rep UnpeerVpc x -> UnpeerVpc
forall x. UnpeerVpc -> Rep UnpeerVpc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnpeerVpc x -> UnpeerVpc
$cfrom :: forall x. UnpeerVpc -> Rep UnpeerVpc x
Prelude.Generic)

-- |
-- Create a value of 'UnpeerVpc' 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.
newUnpeerVpc ::
  UnpeerVpc
newUnpeerVpc :: UnpeerVpc
newUnpeerVpc = UnpeerVpc
UnpeerVpc'

instance Core.AWSRequest UnpeerVpc where
  type AWSResponse UnpeerVpc = UnpeerVpcResponse
  request :: (Service -> Service) -> UnpeerVpc -> Request UnpeerVpc
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 UnpeerVpc
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UnpeerVpc)))
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 -> UnpeerVpcResponse
UnpeerVpcResponse'
            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
"operation")
            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 UnpeerVpc where
  hashWithSalt :: Int -> UnpeerVpc -> Int
hashWithSalt Int
_salt UnpeerVpc
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData UnpeerVpc where
  rnf :: UnpeerVpc -> ()
rnf UnpeerVpc
_ = ()

instance Data.ToHeaders UnpeerVpc where
  toHeaders :: UnpeerVpc -> 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.UnpeerVpc" ::
                          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 UnpeerVpc where
  toJSON :: UnpeerVpc -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'UnpeerVpcResponse' 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:
--
-- 'operation', 'unpeerVpcResponse_operation' - 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', 'unpeerVpcResponse_httpStatus' - The response's http status code.
newUnpeerVpcResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UnpeerVpcResponse
newUnpeerVpcResponse :: Int -> UnpeerVpcResponse
newUnpeerVpcResponse Int
pHttpStatus_ =
  UnpeerVpcResponse'
    { $sel:operation:UnpeerVpcResponse' :: Maybe Operation
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UnpeerVpcResponse' :: 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.
unpeerVpcResponse_operation :: Lens.Lens' UnpeerVpcResponse (Prelude.Maybe Operation)
unpeerVpcResponse_operation :: Lens' UnpeerVpcResponse (Maybe Operation)
unpeerVpcResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UnpeerVpcResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:UnpeerVpcResponse' :: UnpeerVpcResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: UnpeerVpcResponse
s@UnpeerVpcResponse' {} Maybe Operation
a -> UnpeerVpcResponse
s {$sel:operation:UnpeerVpcResponse' :: Maybe Operation
operation = Maybe Operation
a} :: UnpeerVpcResponse)

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

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