{-# 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.CloudTrail.StopLogging
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Suspends the recording of Amazon Web Services API calls and log file
-- delivery for the specified trail. Under most circumstances, there is no
-- need to use this action. You can update a trail without stopping it
-- first. This action is the only way to stop recording. For a trail
-- enabled in all regions, this operation must be called from the region in
-- which the trail was created, or an @InvalidHomeRegionException@ will
-- occur. This operation cannot be called on the shadow trails (replicated
-- trails in other regions) of a trail enabled in all regions.
module Amazonka.CloudTrail.StopLogging
  ( -- * Creating a Request
    StopLogging (..),
    newStopLogging,

    -- * Request Lenses
    stopLogging_name,

    -- * Destructuring the Response
    StopLoggingResponse (..),
    newStopLoggingResponse,

    -- * Response Lenses
    stopLoggingResponse_httpStatus,
  )
where

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

-- | Passes the request to CloudTrail to stop logging Amazon Web Services API
-- calls for the specified account.
--
-- /See:/ 'newStopLogging' smart constructor.
data StopLogging = StopLogging'
  { -- | Specifies the name or the CloudTrail ARN of the trail for which
    -- CloudTrail will stop logging Amazon Web Services API calls. The
    -- following is the format of a trail ARN.
    --
    -- @arn:aws:cloudtrail:us-east-2:123456789012:trail\/MyTrail@
    StopLogging -> Text
name :: Prelude.Text
  }
  deriving (StopLogging -> StopLogging -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopLogging -> StopLogging -> Bool
$c/= :: StopLogging -> StopLogging -> Bool
== :: StopLogging -> StopLogging -> Bool
$c== :: StopLogging -> StopLogging -> Bool
Prelude.Eq, ReadPrec [StopLogging]
ReadPrec StopLogging
Int -> ReadS StopLogging
ReadS [StopLogging]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopLogging]
$creadListPrec :: ReadPrec [StopLogging]
readPrec :: ReadPrec StopLogging
$creadPrec :: ReadPrec StopLogging
readList :: ReadS [StopLogging]
$creadList :: ReadS [StopLogging]
readsPrec :: Int -> ReadS StopLogging
$creadsPrec :: Int -> ReadS StopLogging
Prelude.Read, Int -> StopLogging -> ShowS
[StopLogging] -> ShowS
StopLogging -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopLogging] -> ShowS
$cshowList :: [StopLogging] -> ShowS
show :: StopLogging -> String
$cshow :: StopLogging -> String
showsPrec :: Int -> StopLogging -> ShowS
$cshowsPrec :: Int -> StopLogging -> ShowS
Prelude.Show, forall x. Rep StopLogging x -> StopLogging
forall x. StopLogging -> Rep StopLogging x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopLogging x -> StopLogging
$cfrom :: forall x. StopLogging -> Rep StopLogging x
Prelude.Generic)

-- |
-- Create a value of 'StopLogging' 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:
--
-- 'name', 'stopLogging_name' - Specifies the name or the CloudTrail ARN of the trail for which
-- CloudTrail will stop logging Amazon Web Services API calls. The
-- following is the format of a trail ARN.
--
-- @arn:aws:cloudtrail:us-east-2:123456789012:trail\/MyTrail@
newStopLogging ::
  -- | 'name'
  Prelude.Text ->
  StopLogging
newStopLogging :: Text -> StopLogging
newStopLogging Text
pName_ = StopLogging' {$sel:name:StopLogging' :: Text
name = Text
pName_}

-- | Specifies the name or the CloudTrail ARN of the trail for which
-- CloudTrail will stop logging Amazon Web Services API calls. The
-- following is the format of a trail ARN.
--
-- @arn:aws:cloudtrail:us-east-2:123456789012:trail\/MyTrail@
stopLogging_name :: Lens.Lens' StopLogging Prelude.Text
stopLogging_name :: Lens' StopLogging Text
stopLogging_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopLogging' {Text
name :: Text
$sel:name:StopLogging' :: StopLogging -> Text
name} -> Text
name) (\s :: StopLogging
s@StopLogging' {} Text
a -> StopLogging
s {$sel:name:StopLogging' :: Text
name = Text
a} :: StopLogging)

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

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

instance Data.ToHeaders StopLogging where
  toHeaders :: StopLogging -> 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
"com.amazonaws.cloudtrail.v20131101.CloudTrail_20131101.StopLogging" ::
                          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 StopLogging where
  toJSON :: StopLogging -> Value
toJSON StopLogging' {Text
name :: Text
$sel:name:StopLogging' :: StopLogging -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [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 StopLogging where
  toPath :: StopLogging -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | Returns the objects or data listed below if successful. Otherwise,
-- returns an error.
--
-- /See:/ 'newStopLoggingResponse' smart constructor.
data StopLoggingResponse = StopLoggingResponse'
  { -- | The response's http status code.
    StopLoggingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopLoggingResponse -> StopLoggingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopLoggingResponse -> StopLoggingResponse -> Bool
$c/= :: StopLoggingResponse -> StopLoggingResponse -> Bool
== :: StopLoggingResponse -> StopLoggingResponse -> Bool
$c== :: StopLoggingResponse -> StopLoggingResponse -> Bool
Prelude.Eq, ReadPrec [StopLoggingResponse]
ReadPrec StopLoggingResponse
Int -> ReadS StopLoggingResponse
ReadS [StopLoggingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopLoggingResponse]
$creadListPrec :: ReadPrec [StopLoggingResponse]
readPrec :: ReadPrec StopLoggingResponse
$creadPrec :: ReadPrec StopLoggingResponse
readList :: ReadS [StopLoggingResponse]
$creadList :: ReadS [StopLoggingResponse]
readsPrec :: Int -> ReadS StopLoggingResponse
$creadsPrec :: Int -> ReadS StopLoggingResponse
Prelude.Read, Int -> StopLoggingResponse -> ShowS
[StopLoggingResponse] -> ShowS
StopLoggingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopLoggingResponse] -> ShowS
$cshowList :: [StopLoggingResponse] -> ShowS
show :: StopLoggingResponse -> String
$cshow :: StopLoggingResponse -> String
showsPrec :: Int -> StopLoggingResponse -> ShowS
$cshowsPrec :: Int -> StopLoggingResponse -> ShowS
Prelude.Show, forall x. Rep StopLoggingResponse x -> StopLoggingResponse
forall x. StopLoggingResponse -> Rep StopLoggingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopLoggingResponse x -> StopLoggingResponse
$cfrom :: forall x. StopLoggingResponse -> Rep StopLoggingResponse x
Prelude.Generic)

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

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

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