{-# 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.FraudDetector.GetEntityTypes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets all entity types or a specific entity type if a name is specified.
-- This is a paginated API. If you provide a null @maxResults@, this action
-- retrieves a maximum of 10 records per page. If you provide a
-- @maxResults@, the value must be between 5 and 10. To get the next page
-- results, provide the pagination token from the @GetEntityTypesResponse@
-- as part of your request. A null pagination token fetches the records
-- from the beginning.
module Amazonka.FraudDetector.GetEntityTypes
  ( -- * Creating a Request
    GetEntityTypes (..),
    newGetEntityTypes,

    -- * Request Lenses
    getEntityTypes_maxResults,
    getEntityTypes_name,
    getEntityTypes_nextToken,

    -- * Destructuring the Response
    GetEntityTypesResponse (..),
    newGetEntityTypesResponse,

    -- * Response Lenses
    getEntityTypesResponse_entityTypes,
    getEntityTypesResponse_nextToken,
    getEntityTypesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetEntityTypes' smart constructor.
data GetEntityTypes = GetEntityTypes'
  { -- | The maximum number of objects to return for the request.
    GetEntityTypes -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The name.
    GetEntityTypes -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The next token for the subsequent request.
    GetEntityTypes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetEntityTypes -> GetEntityTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEntityTypes -> GetEntityTypes -> Bool
$c/= :: GetEntityTypes -> GetEntityTypes -> Bool
== :: GetEntityTypes -> GetEntityTypes -> Bool
$c== :: GetEntityTypes -> GetEntityTypes -> Bool
Prelude.Eq, ReadPrec [GetEntityTypes]
ReadPrec GetEntityTypes
Int -> ReadS GetEntityTypes
ReadS [GetEntityTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEntityTypes]
$creadListPrec :: ReadPrec [GetEntityTypes]
readPrec :: ReadPrec GetEntityTypes
$creadPrec :: ReadPrec GetEntityTypes
readList :: ReadS [GetEntityTypes]
$creadList :: ReadS [GetEntityTypes]
readsPrec :: Int -> ReadS GetEntityTypes
$creadsPrec :: Int -> ReadS GetEntityTypes
Prelude.Read, Int -> GetEntityTypes -> ShowS
[GetEntityTypes] -> ShowS
GetEntityTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEntityTypes] -> ShowS
$cshowList :: [GetEntityTypes] -> ShowS
show :: GetEntityTypes -> String
$cshow :: GetEntityTypes -> String
showsPrec :: Int -> GetEntityTypes -> ShowS
$cshowsPrec :: Int -> GetEntityTypes -> ShowS
Prelude.Show, forall x. Rep GetEntityTypes x -> GetEntityTypes
forall x. GetEntityTypes -> Rep GetEntityTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEntityTypes x -> GetEntityTypes
$cfrom :: forall x. GetEntityTypes -> Rep GetEntityTypes x
Prelude.Generic)

-- |
-- Create a value of 'GetEntityTypes' 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:
--
-- 'maxResults', 'getEntityTypes_maxResults' - The maximum number of objects to return for the request.
--
-- 'name', 'getEntityTypes_name' - The name.
--
-- 'nextToken', 'getEntityTypes_nextToken' - The next token for the subsequent request.
newGetEntityTypes ::
  GetEntityTypes
newGetEntityTypes :: GetEntityTypes
newGetEntityTypes =
  GetEntityTypes'
    { $sel:maxResults:GetEntityTypes' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetEntityTypes' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetEntityTypes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of objects to return for the request.
getEntityTypes_maxResults :: Lens.Lens' GetEntityTypes (Prelude.Maybe Prelude.Natural)
getEntityTypes_maxResults :: Lens' GetEntityTypes (Maybe Natural)
getEntityTypes_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityTypes' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetEntityTypes' :: GetEntityTypes -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetEntityTypes
s@GetEntityTypes' {} Maybe Natural
a -> GetEntityTypes
s {$sel:maxResults:GetEntityTypes' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetEntityTypes)

-- | The name.
getEntityTypes_name :: Lens.Lens' GetEntityTypes (Prelude.Maybe Prelude.Text)
getEntityTypes_name :: Lens' GetEntityTypes (Maybe Text)
getEntityTypes_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityTypes' {Maybe Text
name :: Maybe Text
$sel:name:GetEntityTypes' :: GetEntityTypes -> Maybe Text
name} -> Maybe Text
name) (\s :: GetEntityTypes
s@GetEntityTypes' {} Maybe Text
a -> GetEntityTypes
s {$sel:name:GetEntityTypes' :: Maybe Text
name = Maybe Text
a} :: GetEntityTypes)

-- | The next token for the subsequent request.
getEntityTypes_nextToken :: Lens.Lens' GetEntityTypes (Prelude.Maybe Prelude.Text)
getEntityTypes_nextToken :: Lens' GetEntityTypes (Maybe Text)
getEntityTypes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityTypes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetEntityTypes' :: GetEntityTypes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetEntityTypes
s@GetEntityTypes' {} Maybe Text
a -> GetEntityTypes
s {$sel:nextToken:GetEntityTypes' :: Maybe Text
nextToken = Maybe Text
a} :: GetEntityTypes)

instance Core.AWSRequest GetEntityTypes where
  type
    AWSResponse GetEntityTypes =
      GetEntityTypesResponse
  request :: (Service -> Service) -> GetEntityTypes -> Request GetEntityTypes
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 GetEntityTypes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetEntityTypes)))
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 [EntityType] -> Maybe Text -> Int -> GetEntityTypesResponse
GetEntityTypesResponse'
            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
"entityTypes" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextToken")
            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 GetEntityTypes where
  hashWithSalt :: Int -> GetEntityTypes -> Int
hashWithSalt Int
_salt GetEntityTypes' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
name :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:name:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:maxResults:GetEntityTypes' :: GetEntityTypes -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData GetEntityTypes where
  rnf :: GetEntityTypes -> ()
rnf GetEntityTypes' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
name :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:name:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:maxResults:GetEntityTypes' :: GetEntityTypes -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

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

instance Data.ToJSON GetEntityTypes where
  toJSON :: GetEntityTypes -> Value
toJSON GetEntityTypes' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
name :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:name:GetEntityTypes' :: GetEntityTypes -> Maybe Text
$sel:maxResults:GetEntityTypes' :: GetEntityTypes -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken
          ]
      )

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

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

-- | /See:/ 'newGetEntityTypesResponse' smart constructor.
data GetEntityTypesResponse = GetEntityTypesResponse'
  { -- | An array of entity types.
    GetEntityTypesResponse -> Maybe [EntityType]
entityTypes :: Prelude.Maybe [EntityType],
    -- | The next page token.
    GetEntityTypesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetEntityTypesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetEntityTypesResponse -> GetEntityTypesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEntityTypesResponse -> GetEntityTypesResponse -> Bool
$c/= :: GetEntityTypesResponse -> GetEntityTypesResponse -> Bool
== :: GetEntityTypesResponse -> GetEntityTypesResponse -> Bool
$c== :: GetEntityTypesResponse -> GetEntityTypesResponse -> Bool
Prelude.Eq, ReadPrec [GetEntityTypesResponse]
ReadPrec GetEntityTypesResponse
Int -> ReadS GetEntityTypesResponse
ReadS [GetEntityTypesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEntityTypesResponse]
$creadListPrec :: ReadPrec [GetEntityTypesResponse]
readPrec :: ReadPrec GetEntityTypesResponse
$creadPrec :: ReadPrec GetEntityTypesResponse
readList :: ReadS [GetEntityTypesResponse]
$creadList :: ReadS [GetEntityTypesResponse]
readsPrec :: Int -> ReadS GetEntityTypesResponse
$creadsPrec :: Int -> ReadS GetEntityTypesResponse
Prelude.Read, Int -> GetEntityTypesResponse -> ShowS
[GetEntityTypesResponse] -> ShowS
GetEntityTypesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEntityTypesResponse] -> ShowS
$cshowList :: [GetEntityTypesResponse] -> ShowS
show :: GetEntityTypesResponse -> String
$cshow :: GetEntityTypesResponse -> String
showsPrec :: Int -> GetEntityTypesResponse -> ShowS
$cshowsPrec :: Int -> GetEntityTypesResponse -> ShowS
Prelude.Show, forall x. Rep GetEntityTypesResponse x -> GetEntityTypesResponse
forall x. GetEntityTypesResponse -> Rep GetEntityTypesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEntityTypesResponse x -> GetEntityTypesResponse
$cfrom :: forall x. GetEntityTypesResponse -> Rep GetEntityTypesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetEntityTypesResponse' 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:
--
-- 'entityTypes', 'getEntityTypesResponse_entityTypes' - An array of entity types.
--
-- 'nextToken', 'getEntityTypesResponse_nextToken' - The next page token.
--
-- 'httpStatus', 'getEntityTypesResponse_httpStatus' - The response's http status code.
newGetEntityTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetEntityTypesResponse
newGetEntityTypesResponse :: Int -> GetEntityTypesResponse
newGetEntityTypesResponse Int
pHttpStatus_ =
  GetEntityTypesResponse'
    { $sel:entityTypes:GetEntityTypesResponse' :: Maybe [EntityType]
entityTypes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetEntityTypesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetEntityTypesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of entity types.
getEntityTypesResponse_entityTypes :: Lens.Lens' GetEntityTypesResponse (Prelude.Maybe [EntityType])
getEntityTypesResponse_entityTypes :: Lens' GetEntityTypesResponse (Maybe [EntityType])
getEntityTypesResponse_entityTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityTypesResponse' {Maybe [EntityType]
entityTypes :: Maybe [EntityType]
$sel:entityTypes:GetEntityTypesResponse' :: GetEntityTypesResponse -> Maybe [EntityType]
entityTypes} -> Maybe [EntityType]
entityTypes) (\s :: GetEntityTypesResponse
s@GetEntityTypesResponse' {} Maybe [EntityType]
a -> GetEntityTypesResponse
s {$sel:entityTypes:GetEntityTypesResponse' :: Maybe [EntityType]
entityTypes = Maybe [EntityType]
a} :: GetEntityTypesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The next page token.
getEntityTypesResponse_nextToken :: Lens.Lens' GetEntityTypesResponse (Prelude.Maybe Prelude.Text)
getEntityTypesResponse_nextToken :: Lens' GetEntityTypesResponse (Maybe Text)
getEntityTypesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityTypesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetEntityTypesResponse' :: GetEntityTypesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetEntityTypesResponse
s@GetEntityTypesResponse' {} Maybe Text
a -> GetEntityTypesResponse
s {$sel:nextToken:GetEntityTypesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetEntityTypesResponse)

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

instance Prelude.NFData GetEntityTypesResponse where
  rnf :: GetEntityTypesResponse -> ()
rnf GetEntityTypesResponse' {Int
Maybe [EntityType]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
entityTypes :: Maybe [EntityType]
$sel:httpStatus:GetEntityTypesResponse' :: GetEntityTypesResponse -> Int
$sel:nextToken:GetEntityTypesResponse' :: GetEntityTypesResponse -> Maybe Text
$sel:entityTypes:GetEntityTypesResponse' :: GetEntityTypesResponse -> Maybe [EntityType]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [EntityType]
entityTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus