{-# 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.MacieV2.CreateSampleFindings
-- 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 sample findings.
module Amazonka.MacieV2.CreateSampleFindings
  ( -- * Creating a Request
    CreateSampleFindings (..),
    newCreateSampleFindings,

    -- * Request Lenses
    createSampleFindings_findingTypes,

    -- * Destructuring the Response
    CreateSampleFindingsResponse (..),
    newCreateSampleFindingsResponse,

    -- * Response Lenses
    createSampleFindingsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateSampleFindings' smart constructor.
data CreateSampleFindings = CreateSampleFindings'
  { -- | An array of finding types, one for each type of sample finding to
    -- create. To create a sample of every type of finding that Amazon Macie
    -- supports, don\'t include this array in your request.
    CreateSampleFindings -> Maybe [FindingType]
findingTypes :: Prelude.Maybe [FindingType]
  }
  deriving (CreateSampleFindings -> CreateSampleFindings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSampleFindings -> CreateSampleFindings -> Bool
$c/= :: CreateSampleFindings -> CreateSampleFindings -> Bool
== :: CreateSampleFindings -> CreateSampleFindings -> Bool
$c== :: CreateSampleFindings -> CreateSampleFindings -> Bool
Prelude.Eq, ReadPrec [CreateSampleFindings]
ReadPrec CreateSampleFindings
Int -> ReadS CreateSampleFindings
ReadS [CreateSampleFindings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSampleFindings]
$creadListPrec :: ReadPrec [CreateSampleFindings]
readPrec :: ReadPrec CreateSampleFindings
$creadPrec :: ReadPrec CreateSampleFindings
readList :: ReadS [CreateSampleFindings]
$creadList :: ReadS [CreateSampleFindings]
readsPrec :: Int -> ReadS CreateSampleFindings
$creadsPrec :: Int -> ReadS CreateSampleFindings
Prelude.Read, Int -> CreateSampleFindings -> ShowS
[CreateSampleFindings] -> ShowS
CreateSampleFindings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSampleFindings] -> ShowS
$cshowList :: [CreateSampleFindings] -> ShowS
show :: CreateSampleFindings -> String
$cshow :: CreateSampleFindings -> String
showsPrec :: Int -> CreateSampleFindings -> ShowS
$cshowsPrec :: Int -> CreateSampleFindings -> ShowS
Prelude.Show, forall x. Rep CreateSampleFindings x -> CreateSampleFindings
forall x. CreateSampleFindings -> Rep CreateSampleFindings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSampleFindings x -> CreateSampleFindings
$cfrom :: forall x. CreateSampleFindings -> Rep CreateSampleFindings x
Prelude.Generic)

-- |
-- Create a value of 'CreateSampleFindings' 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:
--
-- 'findingTypes', 'createSampleFindings_findingTypes' - An array of finding types, one for each type of sample finding to
-- create. To create a sample of every type of finding that Amazon Macie
-- supports, don\'t include this array in your request.
newCreateSampleFindings ::
  CreateSampleFindings
newCreateSampleFindings :: CreateSampleFindings
newCreateSampleFindings =
  CreateSampleFindings'
    { $sel:findingTypes:CreateSampleFindings' :: Maybe [FindingType]
findingTypes =
        forall a. Maybe a
Prelude.Nothing
    }

-- | An array of finding types, one for each type of sample finding to
-- create. To create a sample of every type of finding that Amazon Macie
-- supports, don\'t include this array in your request.
createSampleFindings_findingTypes :: Lens.Lens' CreateSampleFindings (Prelude.Maybe [FindingType])
createSampleFindings_findingTypes :: Lens' CreateSampleFindings (Maybe [FindingType])
createSampleFindings_findingTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSampleFindings' {Maybe [FindingType]
findingTypes :: Maybe [FindingType]
$sel:findingTypes:CreateSampleFindings' :: CreateSampleFindings -> Maybe [FindingType]
findingTypes} -> Maybe [FindingType]
findingTypes) (\s :: CreateSampleFindings
s@CreateSampleFindings' {} Maybe [FindingType]
a -> CreateSampleFindings
s {$sel:findingTypes:CreateSampleFindings' :: Maybe [FindingType]
findingTypes = Maybe [FindingType]
a} :: CreateSampleFindings) 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

instance Core.AWSRequest CreateSampleFindings where
  type
    AWSResponse CreateSampleFindings =
      CreateSampleFindingsResponse
  request :: (Service -> Service)
-> CreateSampleFindings -> Request CreateSampleFindings
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 CreateSampleFindings
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSampleFindings)))
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 -> CreateSampleFindingsResponse
CreateSampleFindingsResponse'
            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 CreateSampleFindings where
  hashWithSalt :: Int -> CreateSampleFindings -> Int
hashWithSalt Int
_salt CreateSampleFindings' {Maybe [FindingType]
findingTypes :: Maybe [FindingType]
$sel:findingTypes:CreateSampleFindings' :: CreateSampleFindings -> Maybe [FindingType]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FindingType]
findingTypes

instance Prelude.NFData CreateSampleFindings where
  rnf :: CreateSampleFindings -> ()
rnf CreateSampleFindings' {Maybe [FindingType]
findingTypes :: Maybe [FindingType]
$sel:findingTypes:CreateSampleFindings' :: CreateSampleFindings -> Maybe [FindingType]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FindingType]
findingTypes

instance Data.ToHeaders CreateSampleFindings where
  toHeaders :: CreateSampleFindings -> 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.ToJSON CreateSampleFindings where
  toJSON :: CreateSampleFindings -> Value
toJSON CreateSampleFindings' {Maybe [FindingType]
findingTypes :: Maybe [FindingType]
$sel:findingTypes:CreateSampleFindings' :: CreateSampleFindings -> Maybe [FindingType]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"findingTypes" 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 [FindingType]
findingTypes]
      )

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

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

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

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

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

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