{-# 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.Glacier.GetDataRetrievalPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation returns the current data retrieval policy for the account
-- and region specified in the GET request. For more information about data
-- retrieval policies, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/data-retrieval-policy.html Amazon Glacier Data Retrieval Policies>.
module Amazonka.Glacier.GetDataRetrievalPolicy
  ( -- * Creating a Request
    GetDataRetrievalPolicy (..),
    newGetDataRetrievalPolicy,

    -- * Request Lenses
    getDataRetrievalPolicy_accountId,

    -- * Destructuring the Response
    GetDataRetrievalPolicyResponse (..),
    newGetDataRetrievalPolicyResponse,

    -- * Response Lenses
    getDataRetrievalPolicyResponse_policy,
    getDataRetrievalPolicyResponse_httpStatus,
  )
where

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

-- | Input for GetDataRetrievalPolicy.
--
-- /See:/ 'newGetDataRetrievalPolicy' smart constructor.
data GetDataRetrievalPolicy = GetDataRetrievalPolicy'
  { -- | The @AccountId@ value is the AWS account ID. This value must match the
    -- AWS account ID associated with the credentials used to sign the request.
    -- You can either specify an AWS account ID or optionally a single \'@-@\'
    -- (hyphen), in which case Amazon Glacier uses the AWS account ID
    -- associated with the credentials used to sign the request. If you specify
    -- your account ID, do not include any hyphens (\'-\') in the ID.
    GetDataRetrievalPolicy -> Text
accountId :: Prelude.Text
  }
  deriving (GetDataRetrievalPolicy -> GetDataRetrievalPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataRetrievalPolicy -> GetDataRetrievalPolicy -> Bool
$c/= :: GetDataRetrievalPolicy -> GetDataRetrievalPolicy -> Bool
== :: GetDataRetrievalPolicy -> GetDataRetrievalPolicy -> Bool
$c== :: GetDataRetrievalPolicy -> GetDataRetrievalPolicy -> Bool
Prelude.Eq, ReadPrec [GetDataRetrievalPolicy]
ReadPrec GetDataRetrievalPolicy
Int -> ReadS GetDataRetrievalPolicy
ReadS [GetDataRetrievalPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataRetrievalPolicy]
$creadListPrec :: ReadPrec [GetDataRetrievalPolicy]
readPrec :: ReadPrec GetDataRetrievalPolicy
$creadPrec :: ReadPrec GetDataRetrievalPolicy
readList :: ReadS [GetDataRetrievalPolicy]
$creadList :: ReadS [GetDataRetrievalPolicy]
readsPrec :: Int -> ReadS GetDataRetrievalPolicy
$creadsPrec :: Int -> ReadS GetDataRetrievalPolicy
Prelude.Read, Int -> GetDataRetrievalPolicy -> ShowS
[GetDataRetrievalPolicy] -> ShowS
GetDataRetrievalPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataRetrievalPolicy] -> ShowS
$cshowList :: [GetDataRetrievalPolicy] -> ShowS
show :: GetDataRetrievalPolicy -> String
$cshow :: GetDataRetrievalPolicy -> String
showsPrec :: Int -> GetDataRetrievalPolicy -> ShowS
$cshowsPrec :: Int -> GetDataRetrievalPolicy -> ShowS
Prelude.Show, forall x. Rep GetDataRetrievalPolicy x -> GetDataRetrievalPolicy
forall x. GetDataRetrievalPolicy -> Rep GetDataRetrievalPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDataRetrievalPolicy x -> GetDataRetrievalPolicy
$cfrom :: forall x. GetDataRetrievalPolicy -> Rep GetDataRetrievalPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetDataRetrievalPolicy' 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:
--
-- 'accountId', 'getDataRetrievalPolicy_accountId' - The @AccountId@ value is the AWS account ID. This value must match the
-- AWS account ID associated with the credentials used to sign the request.
-- You can either specify an AWS account ID or optionally a single \'@-@\'
-- (hyphen), in which case Amazon Glacier uses the AWS account ID
-- associated with the credentials used to sign the request. If you specify
-- your account ID, do not include any hyphens (\'-\') in the ID.
newGetDataRetrievalPolicy ::
  -- | 'accountId'
  Prelude.Text ->
  GetDataRetrievalPolicy
newGetDataRetrievalPolicy :: Text -> GetDataRetrievalPolicy
newGetDataRetrievalPolicy Text
pAccountId_ =
  GetDataRetrievalPolicy' {$sel:accountId:GetDataRetrievalPolicy' :: Text
accountId = Text
pAccountId_}

-- | The @AccountId@ value is the AWS account ID. This value must match the
-- AWS account ID associated with the credentials used to sign the request.
-- You can either specify an AWS account ID or optionally a single \'@-@\'
-- (hyphen), in which case Amazon Glacier uses the AWS account ID
-- associated with the credentials used to sign the request. If you specify
-- your account ID, do not include any hyphens (\'-\') in the ID.
getDataRetrievalPolicy_accountId :: Lens.Lens' GetDataRetrievalPolicy Prelude.Text
getDataRetrievalPolicy_accountId :: Lens' GetDataRetrievalPolicy Text
getDataRetrievalPolicy_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataRetrievalPolicy' {Text
accountId :: Text
$sel:accountId:GetDataRetrievalPolicy' :: GetDataRetrievalPolicy -> Text
accountId} -> Text
accountId) (\s :: GetDataRetrievalPolicy
s@GetDataRetrievalPolicy' {} Text
a -> GetDataRetrievalPolicy
s {$sel:accountId:GetDataRetrievalPolicy' :: Text
accountId = Text
a} :: GetDataRetrievalPolicy)

instance Core.AWSRequest GetDataRetrievalPolicy where
  type
    AWSResponse GetDataRetrievalPolicy =
      GetDataRetrievalPolicyResponse
  request :: (Service -> Service)
-> GetDataRetrievalPolicy -> Request GetDataRetrievalPolicy
request Service -> Service
overrides =
    forall a. ByteString -> Request a -> Request a
Request.glacierVersionHeader (Service -> ByteString
Core.version Service
defaultService)
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDataRetrievalPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDataRetrievalPolicy)))
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 DataRetrievalPolicy -> Int -> GetDataRetrievalPolicyResponse
GetDataRetrievalPolicyResponse'
            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
"Policy")
            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 GetDataRetrievalPolicy where
  hashWithSalt :: Int -> GetDataRetrievalPolicy -> Int
hashWithSalt Int
_salt GetDataRetrievalPolicy' {Text
accountId :: Text
$sel:accountId:GetDataRetrievalPolicy' :: GetDataRetrievalPolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId

instance Prelude.NFData GetDataRetrievalPolicy where
  rnf :: GetDataRetrievalPolicy -> ()
rnf GetDataRetrievalPolicy' {Text
accountId :: Text
$sel:accountId:GetDataRetrievalPolicy' :: GetDataRetrievalPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
accountId

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

instance Data.ToPath GetDataRetrievalPolicy where
  toPath :: GetDataRetrievalPolicy -> ByteString
toPath GetDataRetrievalPolicy' {Text
accountId :: Text
$sel:accountId:GetDataRetrievalPolicy' :: GetDataRetrievalPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId,
        ByteString
"/policies/data-retrieval"
      ]

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

-- | Contains the Amazon S3 Glacier response to the @GetDataRetrievalPolicy@
-- request.
--
-- /See:/ 'newGetDataRetrievalPolicyResponse' smart constructor.
data GetDataRetrievalPolicyResponse = GetDataRetrievalPolicyResponse'
  { -- | Contains the returned data retrieval policy in JSON format.
    GetDataRetrievalPolicyResponse -> Maybe DataRetrievalPolicy
policy :: Prelude.Maybe DataRetrievalPolicy,
    -- | The response's http status code.
    GetDataRetrievalPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDataRetrievalPolicyResponse
-> GetDataRetrievalPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataRetrievalPolicyResponse
-> GetDataRetrievalPolicyResponse -> Bool
$c/= :: GetDataRetrievalPolicyResponse
-> GetDataRetrievalPolicyResponse -> Bool
== :: GetDataRetrievalPolicyResponse
-> GetDataRetrievalPolicyResponse -> Bool
$c== :: GetDataRetrievalPolicyResponse
-> GetDataRetrievalPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetDataRetrievalPolicyResponse]
ReadPrec GetDataRetrievalPolicyResponse
Int -> ReadS GetDataRetrievalPolicyResponse
ReadS [GetDataRetrievalPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataRetrievalPolicyResponse]
$creadListPrec :: ReadPrec [GetDataRetrievalPolicyResponse]
readPrec :: ReadPrec GetDataRetrievalPolicyResponse
$creadPrec :: ReadPrec GetDataRetrievalPolicyResponse
readList :: ReadS [GetDataRetrievalPolicyResponse]
$creadList :: ReadS [GetDataRetrievalPolicyResponse]
readsPrec :: Int -> ReadS GetDataRetrievalPolicyResponse
$creadsPrec :: Int -> ReadS GetDataRetrievalPolicyResponse
Prelude.Read, Int -> GetDataRetrievalPolicyResponse -> ShowS
[GetDataRetrievalPolicyResponse] -> ShowS
GetDataRetrievalPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataRetrievalPolicyResponse] -> ShowS
$cshowList :: [GetDataRetrievalPolicyResponse] -> ShowS
show :: GetDataRetrievalPolicyResponse -> String
$cshow :: GetDataRetrievalPolicyResponse -> String
showsPrec :: Int -> GetDataRetrievalPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetDataRetrievalPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep GetDataRetrievalPolicyResponse x
-> GetDataRetrievalPolicyResponse
forall x.
GetDataRetrievalPolicyResponse
-> Rep GetDataRetrievalPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDataRetrievalPolicyResponse x
-> GetDataRetrievalPolicyResponse
$cfrom :: forall x.
GetDataRetrievalPolicyResponse
-> Rep GetDataRetrievalPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDataRetrievalPolicyResponse' 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:
--
-- 'policy', 'getDataRetrievalPolicyResponse_policy' - Contains the returned data retrieval policy in JSON format.
--
-- 'httpStatus', 'getDataRetrievalPolicyResponse_httpStatus' - The response's http status code.
newGetDataRetrievalPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDataRetrievalPolicyResponse
newGetDataRetrievalPolicyResponse :: Int -> GetDataRetrievalPolicyResponse
newGetDataRetrievalPolicyResponse Int
pHttpStatus_ =
  GetDataRetrievalPolicyResponse'
    { $sel:policy:GetDataRetrievalPolicyResponse' :: Maybe DataRetrievalPolicy
policy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDataRetrievalPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the returned data retrieval policy in JSON format.
getDataRetrievalPolicyResponse_policy :: Lens.Lens' GetDataRetrievalPolicyResponse (Prelude.Maybe DataRetrievalPolicy)
getDataRetrievalPolicyResponse_policy :: Lens' GetDataRetrievalPolicyResponse (Maybe DataRetrievalPolicy)
getDataRetrievalPolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataRetrievalPolicyResponse' {Maybe DataRetrievalPolicy
policy :: Maybe DataRetrievalPolicy
$sel:policy:GetDataRetrievalPolicyResponse' :: GetDataRetrievalPolicyResponse -> Maybe DataRetrievalPolicy
policy} -> Maybe DataRetrievalPolicy
policy) (\s :: GetDataRetrievalPolicyResponse
s@GetDataRetrievalPolicyResponse' {} Maybe DataRetrievalPolicy
a -> GetDataRetrievalPolicyResponse
s {$sel:policy:GetDataRetrievalPolicyResponse' :: Maybe DataRetrievalPolicy
policy = Maybe DataRetrievalPolicy
a} :: GetDataRetrievalPolicyResponse)

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

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