{-# 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.EC2.ConfirmProductInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Determines whether a product code is associated with an instance. This
-- action can only be used by the owner of the product code. It is useful
-- when a product code owner must verify whether another user\'s instance
-- is eligible for support.
module Amazonka.EC2.ConfirmProductInstance
  ( -- * Creating a Request
    ConfirmProductInstance (..),
    newConfirmProductInstance,

    -- * Request Lenses
    confirmProductInstance_dryRun,
    confirmProductInstance_instanceId,
    confirmProductInstance_productCode,

    -- * Destructuring the Response
    ConfirmProductInstanceResponse (..),
    newConfirmProductInstanceResponse,

    -- * Response Lenses
    confirmProductInstanceResponse_ownerId,
    confirmProductInstanceResponse_return,
    confirmProductInstanceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newConfirmProductInstance' smart constructor.
data ConfirmProductInstance = ConfirmProductInstance'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    ConfirmProductInstance -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the instance.
    ConfirmProductInstance -> Text
instanceId :: Prelude.Text,
    -- | The product code. This must be a product code that you own.
    ConfirmProductInstance -> Text
productCode :: Prelude.Text
  }
  deriving (ConfirmProductInstance -> ConfirmProductInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfirmProductInstance -> ConfirmProductInstance -> Bool
$c/= :: ConfirmProductInstance -> ConfirmProductInstance -> Bool
== :: ConfirmProductInstance -> ConfirmProductInstance -> Bool
$c== :: ConfirmProductInstance -> ConfirmProductInstance -> Bool
Prelude.Eq, ReadPrec [ConfirmProductInstance]
ReadPrec ConfirmProductInstance
Int -> ReadS ConfirmProductInstance
ReadS [ConfirmProductInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfirmProductInstance]
$creadListPrec :: ReadPrec [ConfirmProductInstance]
readPrec :: ReadPrec ConfirmProductInstance
$creadPrec :: ReadPrec ConfirmProductInstance
readList :: ReadS [ConfirmProductInstance]
$creadList :: ReadS [ConfirmProductInstance]
readsPrec :: Int -> ReadS ConfirmProductInstance
$creadsPrec :: Int -> ReadS ConfirmProductInstance
Prelude.Read, Int -> ConfirmProductInstance -> ShowS
[ConfirmProductInstance] -> ShowS
ConfirmProductInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfirmProductInstance] -> ShowS
$cshowList :: [ConfirmProductInstance] -> ShowS
show :: ConfirmProductInstance -> String
$cshow :: ConfirmProductInstance -> String
showsPrec :: Int -> ConfirmProductInstance -> ShowS
$cshowsPrec :: Int -> ConfirmProductInstance -> ShowS
Prelude.Show, forall x. Rep ConfirmProductInstance x -> ConfirmProductInstance
forall x. ConfirmProductInstance -> Rep ConfirmProductInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConfirmProductInstance x -> ConfirmProductInstance
$cfrom :: forall x. ConfirmProductInstance -> Rep ConfirmProductInstance x
Prelude.Generic)

-- |
-- Create a value of 'ConfirmProductInstance' 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:
--
-- 'dryRun', 'confirmProductInstance_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'instanceId', 'confirmProductInstance_instanceId' - The ID of the instance.
--
-- 'productCode', 'confirmProductInstance_productCode' - The product code. This must be a product code that you own.
newConfirmProductInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'productCode'
  Prelude.Text ->
  ConfirmProductInstance
newConfirmProductInstance :: Text -> Text -> ConfirmProductInstance
newConfirmProductInstance Text
pInstanceId_ Text
pProductCode_ =
  ConfirmProductInstance'
    { $sel:dryRun:ConfirmProductInstance' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ConfirmProductInstance' :: Text
instanceId = Text
pInstanceId_,
      $sel:productCode:ConfirmProductInstance' :: Text
productCode = Text
pProductCode_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
confirmProductInstance_dryRun :: Lens.Lens' ConfirmProductInstance (Prelude.Maybe Prelude.Bool)
confirmProductInstance_dryRun :: Lens' ConfirmProductInstance (Maybe Bool)
confirmProductInstance_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfirmProductInstance' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ConfirmProductInstance' :: ConfirmProductInstance -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ConfirmProductInstance
s@ConfirmProductInstance' {} Maybe Bool
a -> ConfirmProductInstance
s {$sel:dryRun:ConfirmProductInstance' :: Maybe Bool
dryRun = Maybe Bool
a} :: ConfirmProductInstance)

-- | The ID of the instance.
confirmProductInstance_instanceId :: Lens.Lens' ConfirmProductInstance Prelude.Text
confirmProductInstance_instanceId :: Lens' ConfirmProductInstance Text
confirmProductInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfirmProductInstance' {Text
instanceId :: Text
$sel:instanceId:ConfirmProductInstance' :: ConfirmProductInstance -> Text
instanceId} -> Text
instanceId) (\s :: ConfirmProductInstance
s@ConfirmProductInstance' {} Text
a -> ConfirmProductInstance
s {$sel:instanceId:ConfirmProductInstance' :: Text
instanceId = Text
a} :: ConfirmProductInstance)

-- | The product code. This must be a product code that you own.
confirmProductInstance_productCode :: Lens.Lens' ConfirmProductInstance Prelude.Text
confirmProductInstance_productCode :: Lens' ConfirmProductInstance Text
confirmProductInstance_productCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfirmProductInstance' {Text
productCode :: Text
$sel:productCode:ConfirmProductInstance' :: ConfirmProductInstance -> Text
productCode} -> Text
productCode) (\s :: ConfirmProductInstance
s@ConfirmProductInstance' {} Text
a -> ConfirmProductInstance
s {$sel:productCode:ConfirmProductInstance' :: Text
productCode = Text
a} :: ConfirmProductInstance)

instance Core.AWSRequest ConfirmProductInstance where
  type
    AWSResponse ConfirmProductInstance =
      ConfirmProductInstanceResponse
  request :: (Service -> Service)
-> ConfirmProductInstance -> Request ConfirmProductInstance
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ConfirmProductInstance
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ConfirmProductInstance)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Maybe Bool -> Int -> ConfirmProductInstanceResponse
ConfirmProductInstanceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ownerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"return")
            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 ConfirmProductInstance where
  hashWithSalt :: Int -> ConfirmProductInstance -> Int
hashWithSalt Int
_salt ConfirmProductInstance' {Maybe Bool
Text
productCode :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:productCode:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:instanceId:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:dryRun:ConfirmProductInstance' :: ConfirmProductInstance -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
productCode

instance Prelude.NFData ConfirmProductInstance where
  rnf :: ConfirmProductInstance -> ()
rnf ConfirmProductInstance' {Maybe Bool
Text
productCode :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:productCode:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:instanceId:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:dryRun:ConfirmProductInstance' :: ConfirmProductInstance -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
productCode

instance Data.ToHeaders ConfirmProductInstance where
  toHeaders :: ConfirmProductInstance -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ConfirmProductInstance where
  toQuery :: ConfirmProductInstance -> QueryString
toQuery ConfirmProductInstance' {Maybe Bool
Text
productCode :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:productCode:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:instanceId:ConfirmProductInstance' :: ConfirmProductInstance -> Text
$sel:dryRun:ConfirmProductInstance' :: ConfirmProductInstance -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ConfirmProductInstance" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId,
        ByteString
"ProductCode" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
productCode
      ]

-- | /See:/ 'newConfirmProductInstanceResponse' smart constructor.
data ConfirmProductInstanceResponse = ConfirmProductInstanceResponse'
  { -- | The Amazon Web Services account ID of the instance owner. This is only
    -- present if the product code is attached to the instance.
    ConfirmProductInstanceResponse -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The return value of the request. Returns @true@ if the specified product
    -- code is owned by the requester and associated with the specified
    -- instance.
    ConfirmProductInstanceResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    ConfirmProductInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ConfirmProductInstanceResponse
-> ConfirmProductInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfirmProductInstanceResponse
-> ConfirmProductInstanceResponse -> Bool
$c/= :: ConfirmProductInstanceResponse
-> ConfirmProductInstanceResponse -> Bool
== :: ConfirmProductInstanceResponse
-> ConfirmProductInstanceResponse -> Bool
$c== :: ConfirmProductInstanceResponse
-> ConfirmProductInstanceResponse -> Bool
Prelude.Eq, ReadPrec [ConfirmProductInstanceResponse]
ReadPrec ConfirmProductInstanceResponse
Int -> ReadS ConfirmProductInstanceResponse
ReadS [ConfirmProductInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfirmProductInstanceResponse]
$creadListPrec :: ReadPrec [ConfirmProductInstanceResponse]
readPrec :: ReadPrec ConfirmProductInstanceResponse
$creadPrec :: ReadPrec ConfirmProductInstanceResponse
readList :: ReadS [ConfirmProductInstanceResponse]
$creadList :: ReadS [ConfirmProductInstanceResponse]
readsPrec :: Int -> ReadS ConfirmProductInstanceResponse
$creadsPrec :: Int -> ReadS ConfirmProductInstanceResponse
Prelude.Read, Int -> ConfirmProductInstanceResponse -> ShowS
[ConfirmProductInstanceResponse] -> ShowS
ConfirmProductInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfirmProductInstanceResponse] -> ShowS
$cshowList :: [ConfirmProductInstanceResponse] -> ShowS
show :: ConfirmProductInstanceResponse -> String
$cshow :: ConfirmProductInstanceResponse -> String
showsPrec :: Int -> ConfirmProductInstanceResponse -> ShowS
$cshowsPrec :: Int -> ConfirmProductInstanceResponse -> ShowS
Prelude.Show, forall x.
Rep ConfirmProductInstanceResponse x
-> ConfirmProductInstanceResponse
forall x.
ConfirmProductInstanceResponse
-> Rep ConfirmProductInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConfirmProductInstanceResponse x
-> ConfirmProductInstanceResponse
$cfrom :: forall x.
ConfirmProductInstanceResponse
-> Rep ConfirmProductInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'ConfirmProductInstanceResponse' 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:
--
-- 'ownerId', 'confirmProductInstanceResponse_ownerId' - The Amazon Web Services account ID of the instance owner. This is only
-- present if the product code is attached to the instance.
--
-- 'return'', 'confirmProductInstanceResponse_return' - The return value of the request. Returns @true@ if the specified product
-- code is owned by the requester and associated with the specified
-- instance.
--
-- 'httpStatus', 'confirmProductInstanceResponse_httpStatus' - The response's http status code.
newConfirmProductInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ConfirmProductInstanceResponse
newConfirmProductInstanceResponse :: Int -> ConfirmProductInstanceResponse
newConfirmProductInstanceResponse Int
pHttpStatus_ =
  ConfirmProductInstanceResponse'
    { $sel:ownerId:ConfirmProductInstanceResponse' :: Maybe Text
ownerId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:return':ConfirmProductInstanceResponse' :: Maybe Bool
return' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ConfirmProductInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Web Services account ID of the instance owner. This is only
-- present if the product code is attached to the instance.
confirmProductInstanceResponse_ownerId :: Lens.Lens' ConfirmProductInstanceResponse (Prelude.Maybe Prelude.Text)
confirmProductInstanceResponse_ownerId :: Lens' ConfirmProductInstanceResponse (Maybe Text)
confirmProductInstanceResponse_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfirmProductInstanceResponse' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:ConfirmProductInstanceResponse' :: ConfirmProductInstanceResponse -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: ConfirmProductInstanceResponse
s@ConfirmProductInstanceResponse' {} Maybe Text
a -> ConfirmProductInstanceResponse
s {$sel:ownerId:ConfirmProductInstanceResponse' :: Maybe Text
ownerId = Maybe Text
a} :: ConfirmProductInstanceResponse)

-- | The return value of the request. Returns @true@ if the specified product
-- code is owned by the requester and associated with the specified
-- instance.
confirmProductInstanceResponse_return :: Lens.Lens' ConfirmProductInstanceResponse (Prelude.Maybe Prelude.Bool)
confirmProductInstanceResponse_return :: Lens' ConfirmProductInstanceResponse (Maybe Bool)
confirmProductInstanceResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfirmProductInstanceResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':ConfirmProductInstanceResponse' :: ConfirmProductInstanceResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: ConfirmProductInstanceResponse
s@ConfirmProductInstanceResponse' {} Maybe Bool
a -> ConfirmProductInstanceResponse
s {$sel:return':ConfirmProductInstanceResponse' :: Maybe Bool
return' = Maybe Bool
a} :: ConfirmProductInstanceResponse)

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

instance
  Prelude.NFData
    ConfirmProductInstanceResponse
  where
  rnf :: ConfirmProductInstanceResponse -> ()
rnf ConfirmProductInstanceResponse' {Int
Maybe Bool
Maybe Text
httpStatus :: Int
return' :: Maybe Bool
ownerId :: Maybe Text
$sel:httpStatus:ConfirmProductInstanceResponse' :: ConfirmProductInstanceResponse -> Int
$sel:return':ConfirmProductInstanceResponse' :: ConfirmProductInstanceResponse -> Maybe Bool
$sel:ownerId:ConfirmProductInstanceResponse' :: ConfirmProductInstanceResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
return'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus