{-# 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.AuditManager.GetAssessmentFramework
-- 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 a framework from Audit Manager.
module Amazonka.AuditManager.GetAssessmentFramework
  ( -- * Creating a Request
    GetAssessmentFramework (..),
    newGetAssessmentFramework,

    -- * Request Lenses
    getAssessmentFramework_frameworkId,

    -- * Destructuring the Response
    GetAssessmentFrameworkResponse (..),
    newGetAssessmentFrameworkResponse,

    -- * Response Lenses
    getAssessmentFrameworkResponse_framework,
    getAssessmentFrameworkResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'GetAssessmentFramework' 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:
--
-- 'frameworkId', 'getAssessmentFramework_frameworkId' - The identifier for the framework.
newGetAssessmentFramework ::
  -- | 'frameworkId'
  Prelude.Text ->
  GetAssessmentFramework
newGetAssessmentFramework :: Text -> GetAssessmentFramework
newGetAssessmentFramework Text
pFrameworkId_ =
  GetAssessmentFramework'
    { $sel:frameworkId:GetAssessmentFramework' :: Text
frameworkId =
        Text
pFrameworkId_
    }

-- | The identifier for the framework.
getAssessmentFramework_frameworkId :: Lens.Lens' GetAssessmentFramework Prelude.Text
getAssessmentFramework_frameworkId :: Lens' GetAssessmentFramework Text
getAssessmentFramework_frameworkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentFramework' {Text
frameworkId :: Text
$sel:frameworkId:GetAssessmentFramework' :: GetAssessmentFramework -> Text
frameworkId} -> Text
frameworkId) (\s :: GetAssessmentFramework
s@GetAssessmentFramework' {} Text
a -> GetAssessmentFramework
s {$sel:frameworkId:GetAssessmentFramework' :: Text
frameworkId = Text
a} :: GetAssessmentFramework)

instance Core.AWSRequest GetAssessmentFramework where
  type
    AWSResponse GetAssessmentFramework =
      GetAssessmentFrameworkResponse
  request :: (Service -> Service)
-> GetAssessmentFramework -> Request GetAssessmentFramework
request Service -> Service
overrides =
    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 GetAssessmentFramework
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAssessmentFramework)))
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 Framework -> Int -> GetAssessmentFrameworkResponse
GetAssessmentFrameworkResponse'
            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
"framework")
            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 GetAssessmentFramework where
  hashWithSalt :: Int -> GetAssessmentFramework -> Int
hashWithSalt Int
_salt GetAssessmentFramework' {Text
frameworkId :: Text
$sel:frameworkId:GetAssessmentFramework' :: GetAssessmentFramework -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
frameworkId

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

instance Data.ToHeaders GetAssessmentFramework where
  toHeaders :: GetAssessmentFramework -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetAssessmentFramework where
  toPath :: GetAssessmentFramework -> ByteString
toPath GetAssessmentFramework' {Text
frameworkId :: Text
$sel:frameworkId:GetAssessmentFramework' :: GetAssessmentFramework -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/assessmentFrameworks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
frameworkId]

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

-- | /See:/ 'newGetAssessmentFrameworkResponse' smart constructor.
data GetAssessmentFrameworkResponse = GetAssessmentFrameworkResponse'
  { -- | The framework that the @GetAssessmentFramework@ API returned.
    GetAssessmentFrameworkResponse -> Maybe Framework
framework :: Prelude.Maybe Framework,
    -- | The response's http status code.
    GetAssessmentFrameworkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAssessmentFrameworkResponse
-> GetAssessmentFrameworkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssessmentFrameworkResponse
-> GetAssessmentFrameworkResponse -> Bool
$c/= :: GetAssessmentFrameworkResponse
-> GetAssessmentFrameworkResponse -> Bool
== :: GetAssessmentFrameworkResponse
-> GetAssessmentFrameworkResponse -> Bool
$c== :: GetAssessmentFrameworkResponse
-> GetAssessmentFrameworkResponse -> Bool
Prelude.Eq, ReadPrec [GetAssessmentFrameworkResponse]
ReadPrec GetAssessmentFrameworkResponse
Int -> ReadS GetAssessmentFrameworkResponse
ReadS [GetAssessmentFrameworkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssessmentFrameworkResponse]
$creadListPrec :: ReadPrec [GetAssessmentFrameworkResponse]
readPrec :: ReadPrec GetAssessmentFrameworkResponse
$creadPrec :: ReadPrec GetAssessmentFrameworkResponse
readList :: ReadS [GetAssessmentFrameworkResponse]
$creadList :: ReadS [GetAssessmentFrameworkResponse]
readsPrec :: Int -> ReadS GetAssessmentFrameworkResponse
$creadsPrec :: Int -> ReadS GetAssessmentFrameworkResponse
Prelude.Read, Int -> GetAssessmentFrameworkResponse -> ShowS
[GetAssessmentFrameworkResponse] -> ShowS
GetAssessmentFrameworkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssessmentFrameworkResponse] -> ShowS
$cshowList :: [GetAssessmentFrameworkResponse] -> ShowS
show :: GetAssessmentFrameworkResponse -> String
$cshow :: GetAssessmentFrameworkResponse -> String
showsPrec :: Int -> GetAssessmentFrameworkResponse -> ShowS
$cshowsPrec :: Int -> GetAssessmentFrameworkResponse -> ShowS
Prelude.Show, forall x.
Rep GetAssessmentFrameworkResponse x
-> GetAssessmentFrameworkResponse
forall x.
GetAssessmentFrameworkResponse
-> Rep GetAssessmentFrameworkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAssessmentFrameworkResponse x
-> GetAssessmentFrameworkResponse
$cfrom :: forall x.
GetAssessmentFrameworkResponse
-> Rep GetAssessmentFrameworkResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAssessmentFrameworkResponse' 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:
--
-- 'framework', 'getAssessmentFrameworkResponse_framework' - The framework that the @GetAssessmentFramework@ API returned.
--
-- 'httpStatus', 'getAssessmentFrameworkResponse_httpStatus' - The response's http status code.
newGetAssessmentFrameworkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAssessmentFrameworkResponse
newGetAssessmentFrameworkResponse :: Int -> GetAssessmentFrameworkResponse
newGetAssessmentFrameworkResponse Int
pHttpStatus_ =
  GetAssessmentFrameworkResponse'
    { $sel:framework:GetAssessmentFrameworkResponse' :: Maybe Framework
framework =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAssessmentFrameworkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The framework that the @GetAssessmentFramework@ API returned.
getAssessmentFrameworkResponse_framework :: Lens.Lens' GetAssessmentFrameworkResponse (Prelude.Maybe Framework)
getAssessmentFrameworkResponse_framework :: Lens' GetAssessmentFrameworkResponse (Maybe Framework)
getAssessmentFrameworkResponse_framework = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentFrameworkResponse' {Maybe Framework
framework :: Maybe Framework
$sel:framework:GetAssessmentFrameworkResponse' :: GetAssessmentFrameworkResponse -> Maybe Framework
framework} -> Maybe Framework
framework) (\s :: GetAssessmentFrameworkResponse
s@GetAssessmentFrameworkResponse' {} Maybe Framework
a -> GetAssessmentFrameworkResponse
s {$sel:framework:GetAssessmentFrameworkResponse' :: Maybe Framework
framework = Maybe Framework
a} :: GetAssessmentFrameworkResponse)

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

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