{-# 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.Synthetics.DescribeCanaries
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation returns a list of the canaries in your account, along
-- with full details about each canary.
--
-- This operation supports resource-level authorization using an IAM policy
-- and the @Names@ parameter. If you specify the @Names@ parameter, the
-- operation is successful only if you have authorization to view all the
-- canaries that you specify in your request. If you do not have permission
-- to view any of the canaries, the request fails with a 403 response.
--
-- You are required to use the @Names@ parameter if you are logged on to a
-- user or role that has an IAM policy that restricts which canaries that
-- you are allowed to view. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch_Synthetics_Canaries_Restricted.html Limiting a user to viewing specific canaries>.
module Amazonka.Synthetics.DescribeCanaries
  ( -- * Creating a Request
    DescribeCanaries (..),
    newDescribeCanaries,

    -- * Request Lenses
    describeCanaries_maxResults,
    describeCanaries_names,
    describeCanaries_nextToken,

    -- * Destructuring the Response
    DescribeCanariesResponse (..),
    newDescribeCanariesResponse,

    -- * Response Lenses
    describeCanariesResponse_canaries,
    describeCanariesResponse_nextToken,
    describeCanariesResponse_httpStatus,
  )
where

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
import Amazonka.Synthetics.Types

-- | /See:/ 'newDescribeCanaries' smart constructor.
data DescribeCanaries = DescribeCanaries'
  { -- | Specify this parameter to limit how many canaries are returned each time
    -- you use the @DescribeCanaries@ operation. If you omit this parameter,
    -- the default of 100 is used.
    DescribeCanaries -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Use this parameter to return only canaries that match the names that you
    -- specify here. You can specify as many as five canary names.
    --
    -- If you specify this parameter, the operation is successful only if you
    -- have authorization to view all the canaries that you specify in your
    -- request. If you do not have permission to view any of the canaries, the
    -- request fails with a 403 response.
    --
    -- You are required to use this parameter if you are logged on to a user or
    -- role that has an IAM policy that restricts which canaries that you are
    -- allowed to view. For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch_Synthetics_Canaries_Restricted.html Limiting a user to viewing specific canaries>.
    DescribeCanaries -> Maybe (NonEmpty Text)
names :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | A token that indicates that there is more data available. You can use
    -- this token in a subsequent operation to retrieve the next set of
    -- results.
    DescribeCanaries -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeCanaries -> DescribeCanaries -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCanaries -> DescribeCanaries -> Bool
$c/= :: DescribeCanaries -> DescribeCanaries -> Bool
== :: DescribeCanaries -> DescribeCanaries -> Bool
$c== :: DescribeCanaries -> DescribeCanaries -> Bool
Prelude.Eq, ReadPrec [DescribeCanaries]
ReadPrec DescribeCanaries
Int -> ReadS DescribeCanaries
ReadS [DescribeCanaries]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCanaries]
$creadListPrec :: ReadPrec [DescribeCanaries]
readPrec :: ReadPrec DescribeCanaries
$creadPrec :: ReadPrec DescribeCanaries
readList :: ReadS [DescribeCanaries]
$creadList :: ReadS [DescribeCanaries]
readsPrec :: Int -> ReadS DescribeCanaries
$creadsPrec :: Int -> ReadS DescribeCanaries
Prelude.Read, Int -> DescribeCanaries -> ShowS
[DescribeCanaries] -> ShowS
DescribeCanaries -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCanaries] -> ShowS
$cshowList :: [DescribeCanaries] -> ShowS
show :: DescribeCanaries -> String
$cshow :: DescribeCanaries -> String
showsPrec :: Int -> DescribeCanaries -> ShowS
$cshowsPrec :: Int -> DescribeCanaries -> ShowS
Prelude.Show, forall x. Rep DescribeCanaries x -> DescribeCanaries
forall x. DescribeCanaries -> Rep DescribeCanaries x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeCanaries x -> DescribeCanaries
$cfrom :: forall x. DescribeCanaries -> Rep DescribeCanaries x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCanaries' 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', 'describeCanaries_maxResults' - Specify this parameter to limit how many canaries are returned each time
-- you use the @DescribeCanaries@ operation. If you omit this parameter,
-- the default of 100 is used.
--
-- 'names', 'describeCanaries_names' - Use this parameter to return only canaries that match the names that you
-- specify here. You can specify as many as five canary names.
--
-- If you specify this parameter, the operation is successful only if you
-- have authorization to view all the canaries that you specify in your
-- request. If you do not have permission to view any of the canaries, the
-- request fails with a 403 response.
--
-- You are required to use this parameter if you are logged on to a user or
-- role that has an IAM policy that restricts which canaries that you are
-- allowed to view. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch_Synthetics_Canaries_Restricted.html Limiting a user to viewing specific canaries>.
--
-- 'nextToken', 'describeCanaries_nextToken' - A token that indicates that there is more data available. You can use
-- this token in a subsequent operation to retrieve the next set of
-- results.
newDescribeCanaries ::
  DescribeCanaries
newDescribeCanaries :: DescribeCanaries
newDescribeCanaries =
  DescribeCanaries'
    { $sel:maxResults:DescribeCanaries' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:names:DescribeCanaries' :: Maybe (NonEmpty Text)
names = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeCanaries' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Specify this parameter to limit how many canaries are returned each time
-- you use the @DescribeCanaries@ operation. If you omit this parameter,
-- the default of 100 is used.
describeCanaries_maxResults :: Lens.Lens' DescribeCanaries (Prelude.Maybe Prelude.Natural)
describeCanaries_maxResults :: Lens' DescribeCanaries (Maybe Natural)
describeCanaries_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCanaries' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeCanaries' :: DescribeCanaries -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeCanaries
s@DescribeCanaries' {} Maybe Natural
a -> DescribeCanaries
s {$sel:maxResults:DescribeCanaries' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeCanaries)

-- | Use this parameter to return only canaries that match the names that you
-- specify here. You can specify as many as five canary names.
--
-- If you specify this parameter, the operation is successful only if you
-- have authorization to view all the canaries that you specify in your
-- request. If you do not have permission to view any of the canaries, the
-- request fails with a 403 response.
--
-- You are required to use this parameter if you are logged on to a user or
-- role that has an IAM policy that restricts which canaries that you are
-- allowed to view. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch_Synthetics_Canaries_Restricted.html Limiting a user to viewing specific canaries>.
describeCanaries_names :: Lens.Lens' DescribeCanaries (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeCanaries_names :: Lens' DescribeCanaries (Maybe (NonEmpty Text))
describeCanaries_names = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCanaries' {Maybe (NonEmpty Text)
names :: Maybe (NonEmpty Text)
$sel:names:DescribeCanaries' :: DescribeCanaries -> Maybe (NonEmpty Text)
names} -> Maybe (NonEmpty Text)
names) (\s :: DescribeCanaries
s@DescribeCanaries' {} Maybe (NonEmpty Text)
a -> DescribeCanaries
s {$sel:names:DescribeCanaries' :: Maybe (NonEmpty Text)
names = Maybe (NonEmpty Text)
a} :: DescribeCanaries) 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

-- | A token that indicates that there is more data available. You can use
-- this token in a subsequent operation to retrieve the next set of
-- results.
describeCanaries_nextToken :: Lens.Lens' DescribeCanaries (Prelude.Maybe Prelude.Text)
describeCanaries_nextToken :: Lens' DescribeCanaries (Maybe Text)
describeCanaries_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCanaries' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeCanaries' :: DescribeCanaries -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeCanaries
s@DescribeCanaries' {} Maybe Text
a -> DescribeCanaries
s {$sel:nextToken:DescribeCanaries' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeCanaries)

instance Core.AWSRequest DescribeCanaries where
  type
    AWSResponse DescribeCanaries =
      DescribeCanariesResponse
  request :: (Service -> Service)
-> DescribeCanaries -> Request DescribeCanaries
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 DescribeCanaries
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeCanaries)))
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 [Canary] -> Maybe Text -> Int -> DescribeCanariesResponse
DescribeCanariesResponse'
            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
"Canaries" 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 DescribeCanaries where
  hashWithSalt :: Int -> DescribeCanaries -> Int
hashWithSalt Int
_salt DescribeCanaries' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
nextToken :: Maybe Text
names :: Maybe (NonEmpty Text)
maxResults :: Maybe Natural
$sel:nextToken:DescribeCanaries' :: DescribeCanaries -> Maybe Text
$sel:names:DescribeCanaries' :: DescribeCanaries -> Maybe (NonEmpty Text)
$sel:maxResults:DescribeCanaries' :: DescribeCanaries -> 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 (NonEmpty Text)
names
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData DescribeCanaries where
  rnf :: DescribeCanaries -> ()
rnf DescribeCanaries' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
nextToken :: Maybe Text
names :: Maybe (NonEmpty Text)
maxResults :: Maybe Natural
$sel:nextToken:DescribeCanaries' :: DescribeCanaries -> Maybe Text
$sel:names:DescribeCanaries' :: DescribeCanaries -> Maybe (NonEmpty Text)
$sel:maxResults:DescribeCanaries' :: DescribeCanaries -> 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 (NonEmpty Text)
names
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders DescribeCanaries where
  toHeaders :: DescribeCanaries -> 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 DescribeCanaries where
  toJSON :: DescribeCanaries -> Value
toJSON DescribeCanaries' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
nextToken :: Maybe Text
names :: Maybe (NonEmpty Text)
maxResults :: Maybe Natural
$sel:nextToken:DescribeCanaries' :: DescribeCanaries -> Maybe Text
$sel:names:DescribeCanaries' :: DescribeCanaries -> Maybe (NonEmpty Text)
$sel:maxResults:DescribeCanaries' :: DescribeCanaries -> 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
"Names" 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 (NonEmpty Text)
names,
            (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 DescribeCanaries where
  toPath :: DescribeCanaries -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/canaries"

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

-- | /See:/ 'newDescribeCanariesResponse' smart constructor.
data DescribeCanariesResponse = DescribeCanariesResponse'
  { -- | Returns an array. Each item in the array contains the full information
    -- about one canary.
    DescribeCanariesResponse -> Maybe [Canary]
canaries :: Prelude.Maybe [Canary],
    -- | A token that indicates that there is more data available. You can use
    -- this token in a subsequent @DescribeCanaries@ operation to retrieve the
    -- next set of results.
    DescribeCanariesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeCanariesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeCanariesResponse -> DescribeCanariesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCanariesResponse -> DescribeCanariesResponse -> Bool
$c/= :: DescribeCanariesResponse -> DescribeCanariesResponse -> Bool
== :: DescribeCanariesResponse -> DescribeCanariesResponse -> Bool
$c== :: DescribeCanariesResponse -> DescribeCanariesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCanariesResponse]
ReadPrec DescribeCanariesResponse
Int -> ReadS DescribeCanariesResponse
ReadS [DescribeCanariesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCanariesResponse]
$creadListPrec :: ReadPrec [DescribeCanariesResponse]
readPrec :: ReadPrec DescribeCanariesResponse
$creadPrec :: ReadPrec DescribeCanariesResponse
readList :: ReadS [DescribeCanariesResponse]
$creadList :: ReadS [DescribeCanariesResponse]
readsPrec :: Int -> ReadS DescribeCanariesResponse
$creadsPrec :: Int -> ReadS DescribeCanariesResponse
Prelude.Read, Int -> DescribeCanariesResponse -> ShowS
[DescribeCanariesResponse] -> ShowS
DescribeCanariesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCanariesResponse] -> ShowS
$cshowList :: [DescribeCanariesResponse] -> ShowS
show :: DescribeCanariesResponse -> String
$cshow :: DescribeCanariesResponse -> String
showsPrec :: Int -> DescribeCanariesResponse -> ShowS
$cshowsPrec :: Int -> DescribeCanariesResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCanariesResponse x -> DescribeCanariesResponse
forall x.
DescribeCanariesResponse -> Rep DescribeCanariesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCanariesResponse x -> DescribeCanariesResponse
$cfrom :: forall x.
DescribeCanariesResponse -> Rep DescribeCanariesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCanariesResponse' 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:
--
-- 'canaries', 'describeCanariesResponse_canaries' - Returns an array. Each item in the array contains the full information
-- about one canary.
--
-- 'nextToken', 'describeCanariesResponse_nextToken' - A token that indicates that there is more data available. You can use
-- this token in a subsequent @DescribeCanaries@ operation to retrieve the
-- next set of results.
--
-- 'httpStatus', 'describeCanariesResponse_httpStatus' - The response's http status code.
newDescribeCanariesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeCanariesResponse
newDescribeCanariesResponse :: Int -> DescribeCanariesResponse
newDescribeCanariesResponse Int
pHttpStatus_ =
  DescribeCanariesResponse'
    { $sel:canaries:DescribeCanariesResponse' :: Maybe [Canary]
canaries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeCanariesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeCanariesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns an array. Each item in the array contains the full information
-- about one canary.
describeCanariesResponse_canaries :: Lens.Lens' DescribeCanariesResponse (Prelude.Maybe [Canary])
describeCanariesResponse_canaries :: Lens' DescribeCanariesResponse (Maybe [Canary])
describeCanariesResponse_canaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCanariesResponse' {Maybe [Canary]
canaries :: Maybe [Canary]
$sel:canaries:DescribeCanariesResponse' :: DescribeCanariesResponse -> Maybe [Canary]
canaries} -> Maybe [Canary]
canaries) (\s :: DescribeCanariesResponse
s@DescribeCanariesResponse' {} Maybe [Canary]
a -> DescribeCanariesResponse
s {$sel:canaries:DescribeCanariesResponse' :: Maybe [Canary]
canaries = Maybe [Canary]
a} :: DescribeCanariesResponse) 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

-- | A token that indicates that there is more data available. You can use
-- this token in a subsequent @DescribeCanaries@ operation to retrieve the
-- next set of results.
describeCanariesResponse_nextToken :: Lens.Lens' DescribeCanariesResponse (Prelude.Maybe Prelude.Text)
describeCanariesResponse_nextToken :: Lens' DescribeCanariesResponse (Maybe Text)
describeCanariesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCanariesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeCanariesResponse' :: DescribeCanariesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeCanariesResponse
s@DescribeCanariesResponse' {} Maybe Text
a -> DescribeCanariesResponse
s {$sel:nextToken:DescribeCanariesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeCanariesResponse)

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

instance Prelude.NFData DescribeCanariesResponse where
  rnf :: DescribeCanariesResponse -> ()
rnf DescribeCanariesResponse' {Int
Maybe [Canary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
canaries :: Maybe [Canary]
$sel:httpStatus:DescribeCanariesResponse' :: DescribeCanariesResponse -> Int
$sel:nextToken:DescribeCanariesResponse' :: DescribeCanariesResponse -> Maybe Text
$sel:canaries:DescribeCanariesResponse' :: DescribeCanariesResponse -> Maybe [Canary]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Canary]
canaries
      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