{-# 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.GetRecommenderConfigurations
-- 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 all the recommender model configurations
-- that are associated with your Amazon Pinpoint account.
module Amazonka.Pinpoint.GetRecommenderConfigurations
  ( -- * Creating a Request
    GetRecommenderConfigurations (..),
    newGetRecommenderConfigurations,

    -- * Request Lenses
    getRecommenderConfigurations_pageSize,
    getRecommenderConfigurations_token,

    -- * Destructuring the Response
    GetRecommenderConfigurationsResponse (..),
    newGetRecommenderConfigurationsResponse,

    -- * Response Lenses
    getRecommenderConfigurationsResponse_httpStatus,
    getRecommenderConfigurationsResponse_listRecommenderConfigurationsResponse,
  )
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:/ 'newGetRecommenderConfigurations' smart constructor.
data GetRecommenderConfigurations = GetRecommenderConfigurations'
  { -- | The maximum number of items to include in each page of a paginated
    -- response. This parameter is not supported for application, campaign, and
    -- journey metrics.
    GetRecommenderConfigurations -> Maybe Text
pageSize :: Prelude.Maybe Prelude.Text,
    -- | The NextToken string that specifies which page of results to return in a
    -- paginated response.
    GetRecommenderConfigurations -> Maybe Text
token :: Prelude.Maybe Prelude.Text
  }
  deriving (GetRecommenderConfigurations
-> GetRecommenderConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecommenderConfigurations
-> GetRecommenderConfigurations -> Bool
$c/= :: GetRecommenderConfigurations
-> GetRecommenderConfigurations -> Bool
== :: GetRecommenderConfigurations
-> GetRecommenderConfigurations -> Bool
$c== :: GetRecommenderConfigurations
-> GetRecommenderConfigurations -> Bool
Prelude.Eq, ReadPrec [GetRecommenderConfigurations]
ReadPrec GetRecommenderConfigurations
Int -> ReadS GetRecommenderConfigurations
ReadS [GetRecommenderConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRecommenderConfigurations]
$creadListPrec :: ReadPrec [GetRecommenderConfigurations]
readPrec :: ReadPrec GetRecommenderConfigurations
$creadPrec :: ReadPrec GetRecommenderConfigurations
readList :: ReadS [GetRecommenderConfigurations]
$creadList :: ReadS [GetRecommenderConfigurations]
readsPrec :: Int -> ReadS GetRecommenderConfigurations
$creadsPrec :: Int -> ReadS GetRecommenderConfigurations
Prelude.Read, Int -> GetRecommenderConfigurations -> ShowS
[GetRecommenderConfigurations] -> ShowS
GetRecommenderConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecommenderConfigurations] -> ShowS
$cshowList :: [GetRecommenderConfigurations] -> ShowS
show :: GetRecommenderConfigurations -> String
$cshow :: GetRecommenderConfigurations -> String
showsPrec :: Int -> GetRecommenderConfigurations -> ShowS
$cshowsPrec :: Int -> GetRecommenderConfigurations -> ShowS
Prelude.Show, forall x.
Rep GetRecommenderConfigurations x -> GetRecommenderConfigurations
forall x.
GetRecommenderConfigurations -> Rep GetRecommenderConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRecommenderConfigurations x -> GetRecommenderConfigurations
$cfrom :: forall x.
GetRecommenderConfigurations -> Rep GetRecommenderConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'GetRecommenderConfigurations' 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:
--
-- 'pageSize', 'getRecommenderConfigurations_pageSize' - The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
--
-- 'token', 'getRecommenderConfigurations_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
newGetRecommenderConfigurations ::
  GetRecommenderConfigurations
newGetRecommenderConfigurations :: GetRecommenderConfigurations
newGetRecommenderConfigurations =
  GetRecommenderConfigurations'
    { $sel:pageSize:GetRecommenderConfigurations' :: Maybe Text
pageSize =
        forall a. Maybe a
Prelude.Nothing,
      $sel:token:GetRecommenderConfigurations' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
getRecommenderConfigurations_pageSize :: Lens.Lens' GetRecommenderConfigurations (Prelude.Maybe Prelude.Text)
getRecommenderConfigurations_pageSize :: Lens' GetRecommenderConfigurations (Maybe Text)
getRecommenderConfigurations_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecommenderConfigurations' {Maybe Text
pageSize :: Maybe Text
$sel:pageSize:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
pageSize} -> Maybe Text
pageSize) (\s :: GetRecommenderConfigurations
s@GetRecommenderConfigurations' {} Maybe Text
a -> GetRecommenderConfigurations
s {$sel:pageSize:GetRecommenderConfigurations' :: Maybe Text
pageSize = Maybe Text
a} :: GetRecommenderConfigurations)

-- | The NextToken string that specifies which page of results to return in a
-- paginated response.
getRecommenderConfigurations_token :: Lens.Lens' GetRecommenderConfigurations (Prelude.Maybe Prelude.Text)
getRecommenderConfigurations_token :: Lens' GetRecommenderConfigurations (Maybe Text)
getRecommenderConfigurations_token = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecommenderConfigurations' {Maybe Text
token :: Maybe Text
$sel:token:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
token} -> Maybe Text
token) (\s :: GetRecommenderConfigurations
s@GetRecommenderConfigurations' {} Maybe Text
a -> GetRecommenderConfigurations
s {$sel:token:GetRecommenderConfigurations' :: Maybe Text
token = Maybe Text
a} :: GetRecommenderConfigurations)

instance Core.AWSRequest GetRecommenderConfigurations where
  type
    AWSResponse GetRecommenderConfigurations =
      GetRecommenderConfigurationsResponse
  request :: (Service -> Service)
-> GetRecommenderConfigurations
-> Request GetRecommenderConfigurations
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 GetRecommenderConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRecommenderConfigurations)))
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
-> ListRecommenderConfigurationsResponse
-> GetRecommenderConfigurationsResponse
GetRecommenderConfigurationsResponse'
            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
    GetRecommenderConfigurations
  where
  hashWithSalt :: Int -> GetRecommenderConfigurations -> Int
hashWithSalt Int
_salt GetRecommenderConfigurations' {Maybe Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:token:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
$sel:pageSize:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
token

instance Prelude.NFData GetRecommenderConfigurations where
  rnf :: GetRecommenderConfigurations -> ()
rnf GetRecommenderConfigurations' {Maybe Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:token:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
$sel:pageSize:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
token

instance Data.ToHeaders GetRecommenderConfigurations where
  toHeaders :: GetRecommenderConfigurations -> 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 GetRecommenderConfigurations where
  toPath :: GetRecommenderConfigurations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/recommenders"

instance Data.ToQuery GetRecommenderConfigurations where
  toQuery :: GetRecommenderConfigurations -> QueryString
toQuery GetRecommenderConfigurations' {Maybe Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:token:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
$sel:pageSize:GetRecommenderConfigurations' :: GetRecommenderConfigurations -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"page-size" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
pageSize, ByteString
"token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
token]

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

-- |
-- Create a value of 'GetRecommenderConfigurationsResponse' 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', 'getRecommenderConfigurationsResponse_httpStatus' - The response's http status code.
--
-- 'listRecommenderConfigurationsResponse', 'getRecommenderConfigurationsResponse_listRecommenderConfigurationsResponse' - Undocumented member.
newGetRecommenderConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'listRecommenderConfigurationsResponse'
  ListRecommenderConfigurationsResponse ->
  GetRecommenderConfigurationsResponse
newGetRecommenderConfigurationsResponse :: Int
-> ListRecommenderConfigurationsResponse
-> GetRecommenderConfigurationsResponse
newGetRecommenderConfigurationsResponse
  Int
pHttpStatus_
  ListRecommenderConfigurationsResponse
pListRecommenderConfigurationsResponse_ =
    GetRecommenderConfigurationsResponse'
      { $sel:httpStatus:GetRecommenderConfigurationsResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:listRecommenderConfigurationsResponse:GetRecommenderConfigurationsResponse' :: ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse =
          ListRecommenderConfigurationsResponse
pListRecommenderConfigurationsResponse_
      }

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

-- | Undocumented member.
getRecommenderConfigurationsResponse_listRecommenderConfigurationsResponse :: Lens.Lens' GetRecommenderConfigurationsResponse ListRecommenderConfigurationsResponse
getRecommenderConfigurationsResponse_listRecommenderConfigurationsResponse :: Lens'
  GetRecommenderConfigurationsResponse
  ListRecommenderConfigurationsResponse
getRecommenderConfigurationsResponse_listRecommenderConfigurationsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecommenderConfigurationsResponse' {ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse :: ListRecommenderConfigurationsResponse
$sel:listRecommenderConfigurationsResponse:GetRecommenderConfigurationsResponse' :: GetRecommenderConfigurationsResponse
-> ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse} -> ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse) (\s :: GetRecommenderConfigurationsResponse
s@GetRecommenderConfigurationsResponse' {} ListRecommenderConfigurationsResponse
a -> GetRecommenderConfigurationsResponse
s {$sel:listRecommenderConfigurationsResponse:GetRecommenderConfigurationsResponse' :: ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse = ListRecommenderConfigurationsResponse
a} :: GetRecommenderConfigurationsResponse)

instance
  Prelude.NFData
    GetRecommenderConfigurationsResponse
  where
  rnf :: GetRecommenderConfigurationsResponse -> ()
rnf GetRecommenderConfigurationsResponse' {Int
ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse :: ListRecommenderConfigurationsResponse
httpStatus :: Int
$sel:listRecommenderConfigurationsResponse:GetRecommenderConfigurationsResponse' :: GetRecommenderConfigurationsResponse
-> ListRecommenderConfigurationsResponse
$sel:httpStatus:GetRecommenderConfigurationsResponse' :: GetRecommenderConfigurationsResponse -> 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 ListRecommenderConfigurationsResponse
listRecommenderConfigurationsResponse