{-# 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.ListTrails
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists trails that are in the current account.
--
-- This operation returns paginated results.
module Amazonka.CloudTrail.ListTrails
  ( -- * Creating a Request
    ListTrails (..),
    newListTrails,

    -- * Request Lenses
    listTrails_nextToken,

    -- * Destructuring the Response
    ListTrailsResponse (..),
    newListTrailsResponse,

    -- * Response Lenses
    listTrailsResponse_nextToken,
    listTrailsResponse_trails,
    listTrailsResponse_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

-- | /See:/ 'newListTrails' smart constructor.
data ListTrails = ListTrails'
  { -- | The token to use to get the next page of results after a previous API
    -- call. This token must be passed in with the same parameters that were
    -- specified in the original call. For example, if the original call
    -- specified an AttributeKey of \'Username\' with a value of \'root\', the
    -- call with NextToken should include those same parameters.
    ListTrails -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListTrails -> ListTrails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTrails -> ListTrails -> Bool
$c/= :: ListTrails -> ListTrails -> Bool
== :: ListTrails -> ListTrails -> Bool
$c== :: ListTrails -> ListTrails -> Bool
Prelude.Eq, ReadPrec [ListTrails]
ReadPrec ListTrails
Int -> ReadS ListTrails
ReadS [ListTrails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTrails]
$creadListPrec :: ReadPrec [ListTrails]
readPrec :: ReadPrec ListTrails
$creadPrec :: ReadPrec ListTrails
readList :: ReadS [ListTrails]
$creadList :: ReadS [ListTrails]
readsPrec :: Int -> ReadS ListTrails
$creadsPrec :: Int -> ReadS ListTrails
Prelude.Read, Int -> ListTrails -> ShowS
[ListTrails] -> ShowS
ListTrails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTrails] -> ShowS
$cshowList :: [ListTrails] -> ShowS
show :: ListTrails -> String
$cshow :: ListTrails -> String
showsPrec :: Int -> ListTrails -> ShowS
$cshowsPrec :: Int -> ListTrails -> ShowS
Prelude.Show, forall x. Rep ListTrails x -> ListTrails
forall x. ListTrails -> Rep ListTrails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTrails x -> ListTrails
$cfrom :: forall x. ListTrails -> Rep ListTrails x
Prelude.Generic)

-- |
-- Create a value of 'ListTrails' 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:
--
-- 'nextToken', 'listTrails_nextToken' - The token to use to get the next page of results after a previous API
-- call. This token must be passed in with the same parameters that were
-- specified in the original call. For example, if the original call
-- specified an AttributeKey of \'Username\' with a value of \'root\', the
-- call with NextToken should include those same parameters.
newListTrails ::
  ListTrails
newListTrails :: ListTrails
newListTrails =
  ListTrails' {$sel:nextToken:ListTrails' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing}

-- | The token to use to get the next page of results after a previous API
-- call. This token must be passed in with the same parameters that were
-- specified in the original call. For example, if the original call
-- specified an AttributeKey of \'Username\' with a value of \'root\', the
-- call with NextToken should include those same parameters.
listTrails_nextToken :: Lens.Lens' ListTrails (Prelude.Maybe Prelude.Text)
listTrails_nextToken :: Lens' ListTrails (Maybe Text)
listTrails_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTrails' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTrails' :: ListTrails -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTrails
s@ListTrails' {} Maybe Text
a -> ListTrails
s {$sel:nextToken:ListTrails' :: Maybe Text
nextToken = Maybe Text
a} :: ListTrails)

instance Core.AWSPager ListTrails where
  page :: ListTrails -> AWSResponse ListTrails -> Maybe ListTrails
page ListTrails
rq AWSResponse ListTrails
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTrails
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTrailsResponse (Maybe Text)
listTrailsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTrails
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTrailsResponse (Maybe [TrailInfo])
listTrailsResponse_trails
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListTrails
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListTrails (Maybe Text)
listTrails_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListTrails
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTrailsResponse (Maybe Text)
listTrailsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListTrails where
  type AWSResponse ListTrails = ListTrailsResponse
  request :: (Service -> Service) -> ListTrails -> Request ListTrails
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 ListTrails
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTrails)))
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 Text -> Maybe [TrailInfo] -> Int -> ListTrailsResponse
ListTrailsResponse'
            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
"NextToken")
            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
"Trails" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListTrails where
  hashWithSalt :: Int -> ListTrails -> Int
hashWithSalt Int
_salt ListTrails' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTrails' :: ListTrails -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

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

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

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

-- | /See:/ 'newListTrailsResponse' smart constructor.
data ListTrailsResponse = ListTrailsResponse'
  { -- | The token to use to get the next page of results after a previous API
    -- call. If the token does not appear, there are no more results to return.
    -- The token must be passed in with the same parameters as the previous
    -- call. For example, if the original call specified an AttributeKey of
    -- \'Username\' with a value of \'root\', the call with NextToken should
    -- include those same parameters.
    ListTrailsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Returns the name, ARN, and home region of trails in the current account.
    ListTrailsResponse -> Maybe [TrailInfo]
trails :: Prelude.Maybe [TrailInfo],
    -- | The response's http status code.
    ListTrailsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTrailsResponse -> ListTrailsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTrailsResponse -> ListTrailsResponse -> Bool
$c/= :: ListTrailsResponse -> ListTrailsResponse -> Bool
== :: ListTrailsResponse -> ListTrailsResponse -> Bool
$c== :: ListTrailsResponse -> ListTrailsResponse -> Bool
Prelude.Eq, ReadPrec [ListTrailsResponse]
ReadPrec ListTrailsResponse
Int -> ReadS ListTrailsResponse
ReadS [ListTrailsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTrailsResponse]
$creadListPrec :: ReadPrec [ListTrailsResponse]
readPrec :: ReadPrec ListTrailsResponse
$creadPrec :: ReadPrec ListTrailsResponse
readList :: ReadS [ListTrailsResponse]
$creadList :: ReadS [ListTrailsResponse]
readsPrec :: Int -> ReadS ListTrailsResponse
$creadsPrec :: Int -> ReadS ListTrailsResponse
Prelude.Read, Int -> ListTrailsResponse -> ShowS
[ListTrailsResponse] -> ShowS
ListTrailsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTrailsResponse] -> ShowS
$cshowList :: [ListTrailsResponse] -> ShowS
show :: ListTrailsResponse -> String
$cshow :: ListTrailsResponse -> String
showsPrec :: Int -> ListTrailsResponse -> ShowS
$cshowsPrec :: Int -> ListTrailsResponse -> ShowS
Prelude.Show, forall x. Rep ListTrailsResponse x -> ListTrailsResponse
forall x. ListTrailsResponse -> Rep ListTrailsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTrailsResponse x -> ListTrailsResponse
$cfrom :: forall x. ListTrailsResponse -> Rep ListTrailsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTrailsResponse' 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:
--
-- 'nextToken', 'listTrailsResponse_nextToken' - The token to use to get the next page of results after a previous API
-- call. If the token does not appear, there are no more results to return.
-- The token must be passed in with the same parameters as the previous
-- call. For example, if the original call specified an AttributeKey of
-- \'Username\' with a value of \'root\', the call with NextToken should
-- include those same parameters.
--
-- 'trails', 'listTrailsResponse_trails' - Returns the name, ARN, and home region of trails in the current account.
--
-- 'httpStatus', 'listTrailsResponse_httpStatus' - The response's http status code.
newListTrailsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTrailsResponse
newListTrailsResponse :: Int -> ListTrailsResponse
newListTrailsResponse Int
pHttpStatus_ =
  ListTrailsResponse'
    { $sel:nextToken:ListTrailsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:trails:ListTrailsResponse' :: Maybe [TrailInfo]
trails = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTrailsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token to use to get the next page of results after a previous API
-- call. If the token does not appear, there are no more results to return.
-- The token must be passed in with the same parameters as the previous
-- call. For example, if the original call specified an AttributeKey of
-- \'Username\' with a value of \'root\', the call with NextToken should
-- include those same parameters.
listTrailsResponse_nextToken :: Lens.Lens' ListTrailsResponse (Prelude.Maybe Prelude.Text)
listTrailsResponse_nextToken :: Lens' ListTrailsResponse (Maybe Text)
listTrailsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTrailsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTrailsResponse' :: ListTrailsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTrailsResponse
s@ListTrailsResponse' {} Maybe Text
a -> ListTrailsResponse
s {$sel:nextToken:ListTrailsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTrailsResponse)

-- | Returns the name, ARN, and home region of trails in the current account.
listTrailsResponse_trails :: Lens.Lens' ListTrailsResponse (Prelude.Maybe [TrailInfo])
listTrailsResponse_trails :: Lens' ListTrailsResponse (Maybe [TrailInfo])
listTrailsResponse_trails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTrailsResponse' {Maybe [TrailInfo]
trails :: Maybe [TrailInfo]
$sel:trails:ListTrailsResponse' :: ListTrailsResponse -> Maybe [TrailInfo]
trails} -> Maybe [TrailInfo]
trails) (\s :: ListTrailsResponse
s@ListTrailsResponse' {} Maybe [TrailInfo]
a -> ListTrailsResponse
s {$sel:trails:ListTrailsResponse' :: Maybe [TrailInfo]
trails = Maybe [TrailInfo]
a} :: ListTrailsResponse) 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 response's http status code.
listTrailsResponse_httpStatus :: Lens.Lens' ListTrailsResponse Prelude.Int
listTrailsResponse_httpStatus :: Lens' ListTrailsResponse Int
listTrailsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTrailsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListTrailsResponse' :: ListTrailsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListTrailsResponse
s@ListTrailsResponse' {} Int
a -> ListTrailsResponse
s {$sel:httpStatus:ListTrailsResponse' :: Int
httpStatus = Int
a} :: ListTrailsResponse)

instance Prelude.NFData ListTrailsResponse where
  rnf :: ListTrailsResponse -> ()
rnf ListTrailsResponse' {Int
Maybe [TrailInfo]
Maybe Text
httpStatus :: Int
trails :: Maybe [TrailInfo]
nextToken :: Maybe Text
$sel:httpStatus:ListTrailsResponse' :: ListTrailsResponse -> Int
$sel:trails:ListTrailsResponse' :: ListTrailsResponse -> Maybe [TrailInfo]
$sel:nextToken:ListTrailsResponse' :: ListTrailsResponse -> Maybe Text
..} =
    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 Maybe [TrailInfo]
trails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus