{-# 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.PutEntityType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates or updates an entity type. An entity represents who is
-- performing the event. As part of a fraud prediction, you pass the entity
-- ID to indicate the specific entity who performed the event. An entity
-- type classifies the entity. Example classifications include customer,
-- merchant, or account.
module Amazonka.FraudDetector.PutEntityType
  ( -- * Creating a Request
    PutEntityType (..),
    newPutEntityType,

    -- * Request Lenses
    putEntityType_description,
    putEntityType_tags,
    putEntityType_name,

    -- * Destructuring the Response
    PutEntityTypeResponse (..),
    newPutEntityTypeResponse,

    -- * Response Lenses
    putEntityTypeResponse_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:/ 'newPutEntityType' smart constructor.
data PutEntityType = PutEntityType'
  { -- | The description.
    PutEntityType -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A collection of key and value pairs.
    PutEntityType -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the entity type.
    PutEntityType -> Text
name :: Prelude.Text
  }
  deriving (PutEntityType -> PutEntityType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutEntityType -> PutEntityType -> Bool
$c/= :: PutEntityType -> PutEntityType -> Bool
== :: PutEntityType -> PutEntityType -> Bool
$c== :: PutEntityType -> PutEntityType -> Bool
Prelude.Eq, ReadPrec [PutEntityType]
ReadPrec PutEntityType
Int -> ReadS PutEntityType
ReadS [PutEntityType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutEntityType]
$creadListPrec :: ReadPrec [PutEntityType]
readPrec :: ReadPrec PutEntityType
$creadPrec :: ReadPrec PutEntityType
readList :: ReadS [PutEntityType]
$creadList :: ReadS [PutEntityType]
readsPrec :: Int -> ReadS PutEntityType
$creadsPrec :: Int -> ReadS PutEntityType
Prelude.Read, Int -> PutEntityType -> ShowS
[PutEntityType] -> ShowS
PutEntityType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutEntityType] -> ShowS
$cshowList :: [PutEntityType] -> ShowS
show :: PutEntityType -> String
$cshow :: PutEntityType -> String
showsPrec :: Int -> PutEntityType -> ShowS
$cshowsPrec :: Int -> PutEntityType -> ShowS
Prelude.Show, forall x. Rep PutEntityType x -> PutEntityType
forall x. PutEntityType -> Rep PutEntityType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutEntityType x -> PutEntityType
$cfrom :: forall x. PutEntityType -> Rep PutEntityType x
Prelude.Generic)

-- |
-- Create a value of 'PutEntityType' 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:
--
-- 'description', 'putEntityType_description' - The description.
--
-- 'tags', 'putEntityType_tags' - A collection of key and value pairs.
--
-- 'name', 'putEntityType_name' - The name of the entity type.
newPutEntityType ::
  -- | 'name'
  Prelude.Text ->
  PutEntityType
newPutEntityType :: Text -> PutEntityType
newPutEntityType Text
pName_ =
  PutEntityType'
    { $sel:description:PutEntityType' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:PutEntityType' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:PutEntityType' :: Text
name = Text
pName_
    }

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

-- | A collection of key and value pairs.
putEntityType_tags :: Lens.Lens' PutEntityType (Prelude.Maybe [Tag])
putEntityType_tags :: Lens' PutEntityType (Maybe [Tag])
putEntityType_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutEntityType' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:PutEntityType' :: PutEntityType -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: PutEntityType
s@PutEntityType' {} Maybe [Tag]
a -> PutEntityType
s {$sel:tags:PutEntityType' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: PutEntityType) 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 name of the entity type.
putEntityType_name :: Lens.Lens' PutEntityType Prelude.Text
putEntityType_name :: Lens' PutEntityType Text
putEntityType_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutEntityType' {Text
name :: Text
$sel:name:PutEntityType' :: PutEntityType -> Text
name} -> Text
name) (\s :: PutEntityType
s@PutEntityType' {} Text
a -> PutEntityType
s {$sel:name:PutEntityType' :: Text
name = Text
a} :: PutEntityType)

instance Core.AWSRequest PutEntityType where
  type
    AWSResponse PutEntityType =
      PutEntityTypeResponse
  request :: (Service -> Service) -> PutEntityType -> Request PutEntityType
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 PutEntityType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutEntityType)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> PutEntityTypeResponse
PutEntityTypeResponse'
            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))
      )

instance Prelude.Hashable PutEntityType where
  hashWithSalt :: Int -> PutEntityType -> Int
hashWithSalt Int
_salt PutEntityType' {Maybe [Tag]
Maybe Text
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:name:PutEntityType' :: PutEntityType -> Text
$sel:tags:PutEntityType' :: PutEntityType -> Maybe [Tag]
$sel:description:PutEntityType' :: PutEntityType -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData PutEntityType where
  rnf :: PutEntityType -> ()
rnf PutEntityType' {Maybe [Tag]
Maybe Text
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:name:PutEntityType' :: PutEntityType -> Text
$sel:tags:PutEntityType' :: PutEntityType -> Maybe [Tag]
$sel:description:PutEntityType' :: PutEntityType -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders PutEntityType where
  toHeaders :: PutEntityType -> 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.PutEntityType" ::
                          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 PutEntityType where
  toJSON :: PutEntityType -> Value
toJSON PutEntityType' {Maybe [Tag]
Maybe Text
Text
name :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:name:PutEntityType' :: PutEntityType -> Text
$sel:tags:PutEntityType' :: PutEntityType -> Maybe [Tag]
$sel:description:PutEntityType' :: PutEntityType -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            (Key
"tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

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

-- |
-- Create a value of 'PutEntityTypeResponse' 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', 'putEntityTypeResponse_httpStatus' - The response's http status code.
newPutEntityTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutEntityTypeResponse
newPutEntityTypeResponse :: Int -> PutEntityTypeResponse
newPutEntityTypeResponse Int
pHttpStatus_ =
  PutEntityTypeResponse' {$sel:httpStatus:PutEntityTypeResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData PutEntityTypeResponse where
  rnf :: PutEntityTypeResponse -> ()
rnf PutEntityTypeResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutEntityTypeResponse' :: PutEntityTypeResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus