{-# 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.PutInstancePublicPorts
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Opens ports for a specific Amazon Lightsail instance, and specifies the
-- IP addresses allowed to connect to the instance through the ports, and
-- the protocol. This action also closes all currently open ports that are
-- not included in the request. Include all of the ports and the protocols
-- you want to open in your @PutInstancePublicPorts@request. Or use the
-- @OpenInstancePublicPorts@ action to open ports without closing currently
-- open ports.
--
-- The @PutInstancePublicPorts@ action supports tag-based access control
-- via resource tags applied to the resource identified by @instanceName@.
-- For more information, see the
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-controlling-access-using-tags Amazon Lightsail Developer Guide>.
module Amazonka.Lightsail.PutInstancePublicPorts
  ( -- * Creating a Request
    PutInstancePublicPorts (..),
    newPutInstancePublicPorts,

    -- * Request Lenses
    putInstancePublicPorts_portInfos,
    putInstancePublicPorts_instanceName,

    -- * Destructuring the Response
    PutInstancePublicPortsResponse (..),
    newPutInstancePublicPortsResponse,

    -- * Response Lenses
    putInstancePublicPortsResponse_operation,
    putInstancePublicPortsResponse_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:/ 'newPutInstancePublicPorts' smart constructor.
data PutInstancePublicPorts = PutInstancePublicPorts'
  { -- | An array of objects to describe the ports to open for the specified
    -- instance.
    PutInstancePublicPorts -> [PortInfo]
portInfos :: [PortInfo],
    -- | The name of the instance for which to open ports.
    PutInstancePublicPorts -> Text
instanceName :: Prelude.Text
  }
  deriving (PutInstancePublicPorts -> PutInstancePublicPorts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutInstancePublicPorts -> PutInstancePublicPorts -> Bool
$c/= :: PutInstancePublicPorts -> PutInstancePublicPorts -> Bool
== :: PutInstancePublicPorts -> PutInstancePublicPorts -> Bool
$c== :: PutInstancePublicPorts -> PutInstancePublicPorts -> Bool
Prelude.Eq, ReadPrec [PutInstancePublicPorts]
ReadPrec PutInstancePublicPorts
Int -> ReadS PutInstancePublicPorts
ReadS [PutInstancePublicPorts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutInstancePublicPorts]
$creadListPrec :: ReadPrec [PutInstancePublicPorts]
readPrec :: ReadPrec PutInstancePublicPorts
$creadPrec :: ReadPrec PutInstancePublicPorts
readList :: ReadS [PutInstancePublicPorts]
$creadList :: ReadS [PutInstancePublicPorts]
readsPrec :: Int -> ReadS PutInstancePublicPorts
$creadsPrec :: Int -> ReadS PutInstancePublicPorts
Prelude.Read, Int -> PutInstancePublicPorts -> ShowS
[PutInstancePublicPorts] -> ShowS
PutInstancePublicPorts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutInstancePublicPorts] -> ShowS
$cshowList :: [PutInstancePublicPorts] -> ShowS
show :: PutInstancePublicPorts -> String
$cshow :: PutInstancePublicPorts -> String
showsPrec :: Int -> PutInstancePublicPorts -> ShowS
$cshowsPrec :: Int -> PutInstancePublicPorts -> ShowS
Prelude.Show, forall x. Rep PutInstancePublicPorts x -> PutInstancePublicPorts
forall x. PutInstancePublicPorts -> Rep PutInstancePublicPorts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutInstancePublicPorts x -> PutInstancePublicPorts
$cfrom :: forall x. PutInstancePublicPorts -> Rep PutInstancePublicPorts x
Prelude.Generic)

-- |
-- Create a value of 'PutInstancePublicPorts' 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:
--
-- 'portInfos', 'putInstancePublicPorts_portInfos' - An array of objects to describe the ports to open for the specified
-- instance.
--
-- 'instanceName', 'putInstancePublicPorts_instanceName' - The name of the instance for which to open ports.
newPutInstancePublicPorts ::
  -- | 'instanceName'
  Prelude.Text ->
  PutInstancePublicPorts
newPutInstancePublicPorts :: Text -> PutInstancePublicPorts
newPutInstancePublicPorts Text
pInstanceName_ =
  PutInstancePublicPorts'
    { $sel:portInfos:PutInstancePublicPorts' :: [PortInfo]
portInfos = forall a. Monoid a => a
Prelude.mempty,
      $sel:instanceName:PutInstancePublicPorts' :: Text
instanceName = Text
pInstanceName_
    }

-- | An array of objects to describe the ports to open for the specified
-- instance.
putInstancePublicPorts_portInfos :: Lens.Lens' PutInstancePublicPorts [PortInfo]
putInstancePublicPorts_portInfos :: Lens' PutInstancePublicPorts [PortInfo]
putInstancePublicPorts_portInfos = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInstancePublicPorts' {[PortInfo]
portInfos :: [PortInfo]
$sel:portInfos:PutInstancePublicPorts' :: PutInstancePublicPorts -> [PortInfo]
portInfos} -> [PortInfo]
portInfos) (\s :: PutInstancePublicPorts
s@PutInstancePublicPorts' {} [PortInfo]
a -> PutInstancePublicPorts
s {$sel:portInfos:PutInstancePublicPorts' :: [PortInfo]
portInfos = [PortInfo]
a} :: PutInstancePublicPorts) 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

-- | The name of the instance for which to open ports.
putInstancePublicPorts_instanceName :: Lens.Lens' PutInstancePublicPorts Prelude.Text
putInstancePublicPorts_instanceName :: Lens' PutInstancePublicPorts Text
putInstancePublicPorts_instanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutInstancePublicPorts' {Text
instanceName :: Text
$sel:instanceName:PutInstancePublicPorts' :: PutInstancePublicPorts -> Text
instanceName} -> Text
instanceName) (\s :: PutInstancePublicPorts
s@PutInstancePublicPorts' {} Text
a -> PutInstancePublicPorts
s {$sel:instanceName:PutInstancePublicPorts' :: Text
instanceName = Text
a} :: PutInstancePublicPorts)

instance Core.AWSRequest PutInstancePublicPorts where
  type
    AWSResponse PutInstancePublicPorts =
      PutInstancePublicPortsResponse
  request :: (Service -> Service)
-> PutInstancePublicPorts -> Request PutInstancePublicPorts
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 PutInstancePublicPorts
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutInstancePublicPorts)))
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 -> PutInstancePublicPortsResponse
PutInstancePublicPortsResponse'
            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 PutInstancePublicPorts where
  hashWithSalt :: Int -> PutInstancePublicPorts -> Int
hashWithSalt Int
_salt PutInstancePublicPorts' {[PortInfo]
Text
instanceName :: Text
portInfos :: [PortInfo]
$sel:instanceName:PutInstancePublicPorts' :: PutInstancePublicPorts -> Text
$sel:portInfos:PutInstancePublicPorts' :: PutInstancePublicPorts -> [PortInfo]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [PortInfo]
portInfos
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceName

instance Prelude.NFData PutInstancePublicPorts where
  rnf :: PutInstancePublicPorts -> ()
rnf PutInstancePublicPorts' {[PortInfo]
Text
instanceName :: Text
portInfos :: [PortInfo]
$sel:instanceName:PutInstancePublicPorts' :: PutInstancePublicPorts -> Text
$sel:portInfos:PutInstancePublicPorts' :: PutInstancePublicPorts -> [PortInfo]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [PortInfo]
portInfos
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceName

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

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

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

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

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

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

instance
  Prelude.NFData
    PutInstancePublicPortsResponse
  where
  rnf :: PutInstancePublicPortsResponse -> ()
rnf PutInstancePublicPortsResponse' {Int
Maybe Operation
httpStatus :: Int
operation :: Maybe Operation
$sel:httpStatus:PutInstancePublicPortsResponse' :: PutInstancePublicPortsResponse -> Int
$sel:operation:PutInstancePublicPortsResponse' :: PutInstancePublicPortsResponse -> 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