{-# 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.Pinpoint.GetRecommenderConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about an Amazon Pinpoint configuration for a
-- recommender model.
module Amazonka.Pinpoint.GetRecommenderConfiguration
  ( -- * Creating a Request
    GetRecommenderConfiguration (..),
    newGetRecommenderConfiguration,

    -- * Request Lenses
    getRecommenderConfiguration_recommenderId,

    -- * Destructuring the Response
    GetRecommenderConfigurationResponse (..),
    newGetRecommenderConfigurationResponse,

    -- * Response Lenses
    getRecommenderConfigurationResponse_httpStatus,
    getRecommenderConfigurationResponse_recommenderConfigurationResponse,
  )
where

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

-- | /See:/ 'newGetRecommenderConfiguration' smart constructor.
data GetRecommenderConfiguration = GetRecommenderConfiguration'
  { -- | The unique identifier for the recommender model configuration. This
    -- identifier is displayed as the __Recommender ID__ on the Amazon Pinpoint
    -- console.
    GetRecommenderConfiguration -> Text
recommenderId :: Prelude.Text
  }
  deriving (GetRecommenderConfiguration -> GetRecommenderConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecommenderConfiguration -> GetRecommenderConfiguration -> Bool
$c/= :: GetRecommenderConfiguration -> GetRecommenderConfiguration -> Bool
== :: GetRecommenderConfiguration -> GetRecommenderConfiguration -> Bool
$c== :: GetRecommenderConfiguration -> GetRecommenderConfiguration -> Bool
Prelude.Eq, ReadPrec [GetRecommenderConfiguration]
ReadPrec GetRecommenderConfiguration
Int -> ReadS GetRecommenderConfiguration
ReadS [GetRecommenderConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRecommenderConfiguration]
$creadListPrec :: ReadPrec [GetRecommenderConfiguration]
readPrec :: ReadPrec GetRecommenderConfiguration
$creadPrec :: ReadPrec GetRecommenderConfiguration
readList :: ReadS [GetRecommenderConfiguration]
$creadList :: ReadS [GetRecommenderConfiguration]
readsPrec :: Int -> ReadS GetRecommenderConfiguration
$creadsPrec :: Int -> ReadS GetRecommenderConfiguration
Prelude.Read, Int -> GetRecommenderConfiguration -> ShowS
[GetRecommenderConfiguration] -> ShowS
GetRecommenderConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecommenderConfiguration] -> ShowS
$cshowList :: [GetRecommenderConfiguration] -> ShowS
show :: GetRecommenderConfiguration -> String
$cshow :: GetRecommenderConfiguration -> String
showsPrec :: Int -> GetRecommenderConfiguration -> ShowS
$cshowsPrec :: Int -> GetRecommenderConfiguration -> ShowS
Prelude.Show, forall x.
Rep GetRecommenderConfiguration x -> GetRecommenderConfiguration
forall x.
GetRecommenderConfiguration -> Rep GetRecommenderConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRecommenderConfiguration x -> GetRecommenderConfiguration
$cfrom :: forall x.
GetRecommenderConfiguration -> Rep GetRecommenderConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetRecommenderConfiguration' 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:
--
-- 'recommenderId', 'getRecommenderConfiguration_recommenderId' - The unique identifier for the recommender model configuration. This
-- identifier is displayed as the __Recommender ID__ on the Amazon Pinpoint
-- console.
newGetRecommenderConfiguration ::
  -- | 'recommenderId'
  Prelude.Text ->
  GetRecommenderConfiguration
newGetRecommenderConfiguration :: Text -> GetRecommenderConfiguration
newGetRecommenderConfiguration Text
pRecommenderId_ =
  GetRecommenderConfiguration'
    { $sel:recommenderId:GetRecommenderConfiguration' :: Text
recommenderId =
        Text
pRecommenderId_
    }

-- | The unique identifier for the recommender model configuration. This
-- identifier is displayed as the __Recommender ID__ on the Amazon Pinpoint
-- console.
getRecommenderConfiguration_recommenderId :: Lens.Lens' GetRecommenderConfiguration Prelude.Text
getRecommenderConfiguration_recommenderId :: Lens' GetRecommenderConfiguration Text
getRecommenderConfiguration_recommenderId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecommenderConfiguration' {Text
recommenderId :: Text
$sel:recommenderId:GetRecommenderConfiguration' :: GetRecommenderConfiguration -> Text
recommenderId} -> Text
recommenderId) (\s :: GetRecommenderConfiguration
s@GetRecommenderConfiguration' {} Text
a -> GetRecommenderConfiguration
s {$sel:recommenderId:GetRecommenderConfiguration' :: Text
recommenderId = Text
a} :: GetRecommenderConfiguration)

instance Core.AWSRequest GetRecommenderConfiguration where
  type
    AWSResponse GetRecommenderConfiguration =
      GetRecommenderConfigurationResponse
  request :: (Service -> Service)
-> GetRecommenderConfiguration
-> Request GetRecommenderConfiguration
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 GetRecommenderConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRecommenderConfiguration)))
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 ->
          Int
-> RecommenderConfigurationResponse
-> GetRecommenderConfigurationResponse
GetRecommenderConfigurationResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable GetRecommenderConfiguration where
  hashWithSalt :: Int -> GetRecommenderConfiguration -> Int
hashWithSalt Int
_salt GetRecommenderConfiguration' {Text
recommenderId :: Text
$sel:recommenderId:GetRecommenderConfiguration' :: GetRecommenderConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recommenderId

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

instance Data.ToHeaders GetRecommenderConfiguration where
  toHeaders :: GetRecommenderConfiguration -> 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 GetRecommenderConfiguration where
  toPath :: GetRecommenderConfiguration -> ByteString
toPath GetRecommenderConfiguration' {Text
recommenderId :: Text
$sel:recommenderId:GetRecommenderConfiguration' :: GetRecommenderConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/recommenders/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
recommenderId]

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

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

-- |
-- Create a value of 'GetRecommenderConfigurationResponse' 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:
--
-- 'httpStatus', 'getRecommenderConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'recommenderConfigurationResponse', 'getRecommenderConfigurationResponse_recommenderConfigurationResponse' - Undocumented member.
newGetRecommenderConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'recommenderConfigurationResponse'
  RecommenderConfigurationResponse ->
  GetRecommenderConfigurationResponse
newGetRecommenderConfigurationResponse :: Int
-> RecommenderConfigurationResponse
-> GetRecommenderConfigurationResponse
newGetRecommenderConfigurationResponse
  Int
pHttpStatus_
  RecommenderConfigurationResponse
pRecommenderConfigurationResponse_ =
    GetRecommenderConfigurationResponse'
      { $sel:httpStatus:GetRecommenderConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:recommenderConfigurationResponse:GetRecommenderConfigurationResponse' :: RecommenderConfigurationResponse
recommenderConfigurationResponse =
          RecommenderConfigurationResponse
pRecommenderConfigurationResponse_
      }

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

-- | Undocumented member.
getRecommenderConfigurationResponse_recommenderConfigurationResponse :: Lens.Lens' GetRecommenderConfigurationResponse RecommenderConfigurationResponse
getRecommenderConfigurationResponse_recommenderConfigurationResponse :: Lens'
  GetRecommenderConfigurationResponse
  RecommenderConfigurationResponse
getRecommenderConfigurationResponse_recommenderConfigurationResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecommenderConfigurationResponse' {RecommenderConfigurationResponse
recommenderConfigurationResponse :: RecommenderConfigurationResponse
$sel:recommenderConfigurationResponse:GetRecommenderConfigurationResponse' :: GetRecommenderConfigurationResponse
-> RecommenderConfigurationResponse
recommenderConfigurationResponse} -> RecommenderConfigurationResponse
recommenderConfigurationResponse) (\s :: GetRecommenderConfigurationResponse
s@GetRecommenderConfigurationResponse' {} RecommenderConfigurationResponse
a -> GetRecommenderConfigurationResponse
s {$sel:recommenderConfigurationResponse:GetRecommenderConfigurationResponse' :: RecommenderConfigurationResponse
recommenderConfigurationResponse = RecommenderConfigurationResponse
a} :: GetRecommenderConfigurationResponse)

instance
  Prelude.NFData
    GetRecommenderConfigurationResponse
  where
  rnf :: GetRecommenderConfigurationResponse -> ()
rnf GetRecommenderConfigurationResponse' {Int
RecommenderConfigurationResponse
recommenderConfigurationResponse :: RecommenderConfigurationResponse
httpStatus :: Int
$sel:recommenderConfigurationResponse:GetRecommenderConfigurationResponse' :: GetRecommenderConfigurationResponse
-> RecommenderConfigurationResponse
$sel:httpStatus:GetRecommenderConfigurationResponse' :: GetRecommenderConfigurationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RecommenderConfigurationResponse
recommenderConfigurationResponse