{-# 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.OpenSearchServerless.GetSecurityPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a configured OpenSearch Serverless security
-- policy. For more information, see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/serverless-network.html Network access for Amazon OpenSearch Serverless>
-- and
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/serverless-encryption.html Encryption at rest for Amazon OpenSearch Serverless>.
module Amazonka.OpenSearchServerless.GetSecurityPolicy
  ( -- * Creating a Request
    GetSecurityPolicy (..),
    newGetSecurityPolicy,

    -- * Request Lenses
    getSecurityPolicy_name,
    getSecurityPolicy_type,

    -- * Destructuring the Response
    GetSecurityPolicyResponse (..),
    newGetSecurityPolicyResponse,

    -- * Response Lenses
    getSecurityPolicyResponse_securityPolicyDetail,
    getSecurityPolicyResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetSecurityPolicy' smart constructor.
data GetSecurityPolicy = GetSecurityPolicy'
  { -- | The name of the security policy.
    GetSecurityPolicy -> Text
name :: Prelude.Text,
    -- | The type of security policy.
    GetSecurityPolicy -> SecurityPolicyType
type' :: SecurityPolicyType
  }
  deriving (GetSecurityPolicy -> GetSecurityPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSecurityPolicy -> GetSecurityPolicy -> Bool
$c/= :: GetSecurityPolicy -> GetSecurityPolicy -> Bool
== :: GetSecurityPolicy -> GetSecurityPolicy -> Bool
$c== :: GetSecurityPolicy -> GetSecurityPolicy -> Bool
Prelude.Eq, ReadPrec [GetSecurityPolicy]
ReadPrec GetSecurityPolicy
Int -> ReadS GetSecurityPolicy
ReadS [GetSecurityPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSecurityPolicy]
$creadListPrec :: ReadPrec [GetSecurityPolicy]
readPrec :: ReadPrec GetSecurityPolicy
$creadPrec :: ReadPrec GetSecurityPolicy
readList :: ReadS [GetSecurityPolicy]
$creadList :: ReadS [GetSecurityPolicy]
readsPrec :: Int -> ReadS GetSecurityPolicy
$creadsPrec :: Int -> ReadS GetSecurityPolicy
Prelude.Read, Int -> GetSecurityPolicy -> ShowS
[GetSecurityPolicy] -> ShowS
GetSecurityPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSecurityPolicy] -> ShowS
$cshowList :: [GetSecurityPolicy] -> ShowS
show :: GetSecurityPolicy -> String
$cshow :: GetSecurityPolicy -> String
showsPrec :: Int -> GetSecurityPolicy -> ShowS
$cshowsPrec :: Int -> GetSecurityPolicy -> ShowS
Prelude.Show, forall x. Rep GetSecurityPolicy x -> GetSecurityPolicy
forall x. GetSecurityPolicy -> Rep GetSecurityPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSecurityPolicy x -> GetSecurityPolicy
$cfrom :: forall x. GetSecurityPolicy -> Rep GetSecurityPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetSecurityPolicy' 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:
--
-- 'name', 'getSecurityPolicy_name' - The name of the security policy.
--
-- 'type'', 'getSecurityPolicy_type' - The type of security policy.
newGetSecurityPolicy ::
  -- | 'name'
  Prelude.Text ->
  -- | 'type''
  SecurityPolicyType ->
  GetSecurityPolicy
newGetSecurityPolicy :: Text -> SecurityPolicyType -> GetSecurityPolicy
newGetSecurityPolicy Text
pName_ SecurityPolicyType
pType_ =
  GetSecurityPolicy' {$sel:name:GetSecurityPolicy' :: Text
name = Text
pName_, $sel:type':GetSecurityPolicy' :: SecurityPolicyType
type' = SecurityPolicyType
pType_}

-- | The name of the security policy.
getSecurityPolicy_name :: Lens.Lens' GetSecurityPolicy Prelude.Text
getSecurityPolicy_name :: Lens' GetSecurityPolicy Text
getSecurityPolicy_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSecurityPolicy' {Text
name :: Text
$sel:name:GetSecurityPolicy' :: GetSecurityPolicy -> Text
name} -> Text
name) (\s :: GetSecurityPolicy
s@GetSecurityPolicy' {} Text
a -> GetSecurityPolicy
s {$sel:name:GetSecurityPolicy' :: Text
name = Text
a} :: GetSecurityPolicy)

-- | The type of security policy.
getSecurityPolicy_type :: Lens.Lens' GetSecurityPolicy SecurityPolicyType
getSecurityPolicy_type :: Lens' GetSecurityPolicy SecurityPolicyType
getSecurityPolicy_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSecurityPolicy' {SecurityPolicyType
type' :: SecurityPolicyType
$sel:type':GetSecurityPolicy' :: GetSecurityPolicy -> SecurityPolicyType
type'} -> SecurityPolicyType
type') (\s :: GetSecurityPolicy
s@GetSecurityPolicy' {} SecurityPolicyType
a -> GetSecurityPolicy
s {$sel:type':GetSecurityPolicy' :: SecurityPolicyType
type' = SecurityPolicyType
a} :: GetSecurityPolicy)

instance Core.AWSRequest GetSecurityPolicy where
  type
    AWSResponse GetSecurityPolicy =
      GetSecurityPolicyResponse
  request :: (Service -> Service)
-> GetSecurityPolicy -> Request GetSecurityPolicy
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 GetSecurityPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSecurityPolicy)))
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 SecurityPolicyDetail -> Int -> GetSecurityPolicyResponse
GetSecurityPolicyResponse'
            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
"securityPolicyDetail")
            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 GetSecurityPolicy where
  hashWithSalt :: Int -> GetSecurityPolicy -> Int
hashWithSalt Int
_salt GetSecurityPolicy' {Text
SecurityPolicyType
type' :: SecurityPolicyType
name :: Text
$sel:type':GetSecurityPolicy' :: GetSecurityPolicy -> SecurityPolicyType
$sel:name:GetSecurityPolicy' :: GetSecurityPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SecurityPolicyType
type'

instance Prelude.NFData GetSecurityPolicy where
  rnf :: GetSecurityPolicy -> ()
rnf GetSecurityPolicy' {Text
SecurityPolicyType
type' :: SecurityPolicyType
name :: Text
$sel:type':GetSecurityPolicy' :: GetSecurityPolicy -> SecurityPolicyType
$sel:name:GetSecurityPolicy' :: GetSecurityPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SecurityPolicyType
type'

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

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

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

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

-- | /See:/ 'newGetSecurityPolicyResponse' smart constructor.
data GetSecurityPolicyResponse = GetSecurityPolicyResponse'
  { -- | Details about the requested security policy.
    GetSecurityPolicyResponse -> Maybe SecurityPolicyDetail
securityPolicyDetail :: Prelude.Maybe SecurityPolicyDetail,
    -- | The response's http status code.
    GetSecurityPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSecurityPolicyResponse -> GetSecurityPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSecurityPolicyResponse -> GetSecurityPolicyResponse -> Bool
$c/= :: GetSecurityPolicyResponse -> GetSecurityPolicyResponse -> Bool
== :: GetSecurityPolicyResponse -> GetSecurityPolicyResponse -> Bool
$c== :: GetSecurityPolicyResponse -> GetSecurityPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetSecurityPolicyResponse]
ReadPrec GetSecurityPolicyResponse
Int -> ReadS GetSecurityPolicyResponse
ReadS [GetSecurityPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSecurityPolicyResponse]
$creadListPrec :: ReadPrec [GetSecurityPolicyResponse]
readPrec :: ReadPrec GetSecurityPolicyResponse
$creadPrec :: ReadPrec GetSecurityPolicyResponse
readList :: ReadS [GetSecurityPolicyResponse]
$creadList :: ReadS [GetSecurityPolicyResponse]
readsPrec :: Int -> ReadS GetSecurityPolicyResponse
$creadsPrec :: Int -> ReadS GetSecurityPolicyResponse
Prelude.Read, Int -> GetSecurityPolicyResponse -> ShowS
[GetSecurityPolicyResponse] -> ShowS
GetSecurityPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSecurityPolicyResponse] -> ShowS
$cshowList :: [GetSecurityPolicyResponse] -> ShowS
show :: GetSecurityPolicyResponse -> String
$cshow :: GetSecurityPolicyResponse -> String
showsPrec :: Int -> GetSecurityPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetSecurityPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep GetSecurityPolicyResponse x -> GetSecurityPolicyResponse
forall x.
GetSecurityPolicyResponse -> Rep GetSecurityPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSecurityPolicyResponse x -> GetSecurityPolicyResponse
$cfrom :: forall x.
GetSecurityPolicyResponse -> Rep GetSecurityPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSecurityPolicyResponse' 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:
--
-- 'securityPolicyDetail', 'getSecurityPolicyResponse_securityPolicyDetail' - Details about the requested security policy.
--
-- 'httpStatus', 'getSecurityPolicyResponse_httpStatus' - The response's http status code.
newGetSecurityPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSecurityPolicyResponse
newGetSecurityPolicyResponse :: Int -> GetSecurityPolicyResponse
newGetSecurityPolicyResponse Int
pHttpStatus_ =
  GetSecurityPolicyResponse'
    { $sel:securityPolicyDetail:GetSecurityPolicyResponse' :: Maybe SecurityPolicyDetail
securityPolicyDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSecurityPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about the requested security policy.
getSecurityPolicyResponse_securityPolicyDetail :: Lens.Lens' GetSecurityPolicyResponse (Prelude.Maybe SecurityPolicyDetail)
getSecurityPolicyResponse_securityPolicyDetail :: Lens' GetSecurityPolicyResponse (Maybe SecurityPolicyDetail)
getSecurityPolicyResponse_securityPolicyDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSecurityPolicyResponse' {Maybe SecurityPolicyDetail
securityPolicyDetail :: Maybe SecurityPolicyDetail
$sel:securityPolicyDetail:GetSecurityPolicyResponse' :: GetSecurityPolicyResponse -> Maybe SecurityPolicyDetail
securityPolicyDetail} -> Maybe SecurityPolicyDetail
securityPolicyDetail) (\s :: GetSecurityPolicyResponse
s@GetSecurityPolicyResponse' {} Maybe SecurityPolicyDetail
a -> GetSecurityPolicyResponse
s {$sel:securityPolicyDetail:GetSecurityPolicyResponse' :: Maybe SecurityPolicyDetail
securityPolicyDetail = Maybe SecurityPolicyDetail
a} :: GetSecurityPolicyResponse)

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

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