{-# 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.IoTWireless.GetNetworkAnalyzerConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get network analyzer configuration.
module Amazonka.IoTWireless.GetNetworkAnalyzerConfiguration
  ( -- * Creating a Request
    GetNetworkAnalyzerConfiguration (..),
    newGetNetworkAnalyzerConfiguration,

    -- * Request Lenses
    getNetworkAnalyzerConfiguration_configurationName,

    -- * Destructuring the Response
    GetNetworkAnalyzerConfigurationResponse (..),
    newGetNetworkAnalyzerConfigurationResponse,

    -- * Response Lenses
    getNetworkAnalyzerConfigurationResponse_arn,
    getNetworkAnalyzerConfigurationResponse_description,
    getNetworkAnalyzerConfigurationResponse_name,
    getNetworkAnalyzerConfigurationResponse_traceContent,
    getNetworkAnalyzerConfigurationResponse_wirelessDevices,
    getNetworkAnalyzerConfigurationResponse_wirelessGateways,
    getNetworkAnalyzerConfigurationResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'GetNetworkAnalyzerConfiguration' 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:
--
-- 'configurationName', 'getNetworkAnalyzerConfiguration_configurationName' - Undocumented member.
newGetNetworkAnalyzerConfiguration ::
  -- | 'configurationName'
  Prelude.Text ->
  GetNetworkAnalyzerConfiguration
newGetNetworkAnalyzerConfiguration :: Text -> GetNetworkAnalyzerConfiguration
newGetNetworkAnalyzerConfiguration
  Text
pConfigurationName_ =
    GetNetworkAnalyzerConfiguration'
      { $sel:configurationName:GetNetworkAnalyzerConfiguration' :: Text
configurationName =
          Text
pConfigurationName_
      }

-- | Undocumented member.
getNetworkAnalyzerConfiguration_configurationName :: Lens.Lens' GetNetworkAnalyzerConfiguration Prelude.Text
getNetworkAnalyzerConfiguration_configurationName :: Lens' GetNetworkAnalyzerConfiguration Text
getNetworkAnalyzerConfiguration_configurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfiguration' {Text
configurationName :: Text
$sel:configurationName:GetNetworkAnalyzerConfiguration' :: GetNetworkAnalyzerConfiguration -> Text
configurationName} -> Text
configurationName) (\s :: GetNetworkAnalyzerConfiguration
s@GetNetworkAnalyzerConfiguration' {} Text
a -> GetNetworkAnalyzerConfiguration
s {$sel:configurationName:GetNetworkAnalyzerConfiguration' :: Text
configurationName = Text
a} :: GetNetworkAnalyzerConfiguration)

instance
  Core.AWSRequest
    GetNetworkAnalyzerConfiguration
  where
  type
    AWSResponse GetNetworkAnalyzerConfiguration =
      GetNetworkAnalyzerConfigurationResponse
  request :: (Service -> Service)
-> GetNetworkAnalyzerConfiguration
-> Request GetNetworkAnalyzerConfiguration
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetNetworkAnalyzerConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetNetworkAnalyzerConfiguration)))
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 Text
-> Maybe Text
-> Maybe TraceContent
-> Maybe [Text]
-> Maybe [Text]
-> Int
-> GetNetworkAnalyzerConfigurationResponse
GetNetworkAnalyzerConfigurationResponse'
            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
"Arn")
            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
"Description")
            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
"Name")
            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
"TraceContent")
            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
"WirelessDevices"
                            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
"WirelessGateways"
                            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
    GetNetworkAnalyzerConfiguration
  where
  hashWithSalt :: Int -> GetNetworkAnalyzerConfiguration -> Int
hashWithSalt
    Int
_salt
    GetNetworkAnalyzerConfiguration' {Text
configurationName :: Text
$sel:configurationName:GetNetworkAnalyzerConfiguration' :: GetNetworkAnalyzerConfiguration -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationName

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

instance
  Data.ToHeaders
    GetNetworkAnalyzerConfiguration
  where
  toHeaders :: GetNetworkAnalyzerConfiguration -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetNetworkAnalyzerConfiguration where
  toPath :: GetNetworkAnalyzerConfiguration -> ByteString
toPath GetNetworkAnalyzerConfiguration' {Text
configurationName :: Text
$sel:configurationName:GetNetworkAnalyzerConfiguration' :: GetNetworkAnalyzerConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/network-analyzer-configurations/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
configurationName
      ]

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

-- | /See:/ 'newGetNetworkAnalyzerConfigurationResponse' smart constructor.
data GetNetworkAnalyzerConfigurationResponse = GetNetworkAnalyzerConfigurationResponse'
  { -- | The Amazon Resource Name of the new resource.
    GetNetworkAnalyzerConfigurationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    GetNetworkAnalyzerConfigurationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    GetNetworkAnalyzerConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    GetNetworkAnalyzerConfigurationResponse -> Maybe TraceContent
traceContent :: Prelude.Maybe TraceContent,
    -- | List of wireless gateway resources that have been added to the network
    -- analyzer configuration.
    GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
wirelessDevices :: Prelude.Maybe [Prelude.Text],
    -- | List of wireless gateway resources that have been added to the network
    -- analyzer configuration.
    GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
wirelessGateways :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    GetNetworkAnalyzerConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetNetworkAnalyzerConfigurationResponse
-> GetNetworkAnalyzerConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNetworkAnalyzerConfigurationResponse
-> GetNetworkAnalyzerConfigurationResponse -> Bool
$c/= :: GetNetworkAnalyzerConfigurationResponse
-> GetNetworkAnalyzerConfigurationResponse -> Bool
== :: GetNetworkAnalyzerConfigurationResponse
-> GetNetworkAnalyzerConfigurationResponse -> Bool
$c== :: GetNetworkAnalyzerConfigurationResponse
-> GetNetworkAnalyzerConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [GetNetworkAnalyzerConfigurationResponse]
ReadPrec GetNetworkAnalyzerConfigurationResponse
Int -> ReadS GetNetworkAnalyzerConfigurationResponse
ReadS [GetNetworkAnalyzerConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetNetworkAnalyzerConfigurationResponse]
$creadListPrec :: ReadPrec [GetNetworkAnalyzerConfigurationResponse]
readPrec :: ReadPrec GetNetworkAnalyzerConfigurationResponse
$creadPrec :: ReadPrec GetNetworkAnalyzerConfigurationResponse
readList :: ReadS [GetNetworkAnalyzerConfigurationResponse]
$creadList :: ReadS [GetNetworkAnalyzerConfigurationResponse]
readsPrec :: Int -> ReadS GetNetworkAnalyzerConfigurationResponse
$creadsPrec :: Int -> ReadS GetNetworkAnalyzerConfigurationResponse
Prelude.Read, Int -> GetNetworkAnalyzerConfigurationResponse -> ShowS
[GetNetworkAnalyzerConfigurationResponse] -> ShowS
GetNetworkAnalyzerConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNetworkAnalyzerConfigurationResponse] -> ShowS
$cshowList :: [GetNetworkAnalyzerConfigurationResponse] -> ShowS
show :: GetNetworkAnalyzerConfigurationResponse -> String
$cshow :: GetNetworkAnalyzerConfigurationResponse -> String
showsPrec :: Int -> GetNetworkAnalyzerConfigurationResponse -> ShowS
$cshowsPrec :: Int -> GetNetworkAnalyzerConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep GetNetworkAnalyzerConfigurationResponse x
-> GetNetworkAnalyzerConfigurationResponse
forall x.
GetNetworkAnalyzerConfigurationResponse
-> Rep GetNetworkAnalyzerConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetNetworkAnalyzerConfigurationResponse x
-> GetNetworkAnalyzerConfigurationResponse
$cfrom :: forall x.
GetNetworkAnalyzerConfigurationResponse
-> Rep GetNetworkAnalyzerConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetNetworkAnalyzerConfigurationResponse' 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:
--
-- 'arn', 'getNetworkAnalyzerConfigurationResponse_arn' - The Amazon Resource Name of the new resource.
--
-- 'description', 'getNetworkAnalyzerConfigurationResponse_description' - Undocumented member.
--
-- 'name', 'getNetworkAnalyzerConfigurationResponse_name' - Undocumented member.
--
-- 'traceContent', 'getNetworkAnalyzerConfigurationResponse_traceContent' - Undocumented member.
--
-- 'wirelessDevices', 'getNetworkAnalyzerConfigurationResponse_wirelessDevices' - List of wireless gateway resources that have been added to the network
-- analyzer configuration.
--
-- 'wirelessGateways', 'getNetworkAnalyzerConfigurationResponse_wirelessGateways' - List of wireless gateway resources that have been added to the network
-- analyzer configuration.
--
-- 'httpStatus', 'getNetworkAnalyzerConfigurationResponse_httpStatus' - The response's http status code.
newGetNetworkAnalyzerConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetNetworkAnalyzerConfigurationResponse
newGetNetworkAnalyzerConfigurationResponse :: Int -> GetNetworkAnalyzerConfigurationResponse
newGetNetworkAnalyzerConfigurationResponse
  Int
pHttpStatus_ =
    GetNetworkAnalyzerConfigurationResponse'
      { $sel:arn:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
arn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:name:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:traceContent:GetNetworkAnalyzerConfigurationResponse' :: Maybe TraceContent
traceContent = forall a. Maybe a
Prelude.Nothing,
        $sel:wirelessDevices:GetNetworkAnalyzerConfigurationResponse' :: Maybe [Text]
wirelessDevices = forall a. Maybe a
Prelude.Nothing,
        $sel:wirelessGateways:GetNetworkAnalyzerConfigurationResponse' :: Maybe [Text]
wirelessGateways = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetNetworkAnalyzerConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The Amazon Resource Name of the new resource.
getNetworkAnalyzerConfigurationResponse_arn :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe Prelude.Text)
getNetworkAnalyzerConfigurationResponse_arn :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe Text)
getNetworkAnalyzerConfigurationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe Text
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:arn:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
arn = Maybe Text
a} :: GetNetworkAnalyzerConfigurationResponse)

-- | Undocumented member.
getNetworkAnalyzerConfigurationResponse_description :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe Prelude.Text)
getNetworkAnalyzerConfigurationResponse_description :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe Text)
getNetworkAnalyzerConfigurationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe Text
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:description:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
description = Maybe Text
a} :: GetNetworkAnalyzerConfigurationResponse)

-- | Undocumented member.
getNetworkAnalyzerConfigurationResponse_name :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe Prelude.Text)
getNetworkAnalyzerConfigurationResponse_name :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe Text)
getNetworkAnalyzerConfigurationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe Text
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:name:GetNetworkAnalyzerConfigurationResponse' :: Maybe Text
name = Maybe Text
a} :: GetNetworkAnalyzerConfigurationResponse)

-- | Undocumented member.
getNetworkAnalyzerConfigurationResponse_traceContent :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe TraceContent)
getNetworkAnalyzerConfigurationResponse_traceContent :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe TraceContent)
getNetworkAnalyzerConfigurationResponse_traceContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe TraceContent
traceContent :: Maybe TraceContent
$sel:traceContent:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe TraceContent
traceContent} -> Maybe TraceContent
traceContent) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe TraceContent
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:traceContent:GetNetworkAnalyzerConfigurationResponse' :: Maybe TraceContent
traceContent = Maybe TraceContent
a} :: GetNetworkAnalyzerConfigurationResponse)

-- | List of wireless gateway resources that have been added to the network
-- analyzer configuration.
getNetworkAnalyzerConfigurationResponse_wirelessDevices :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe [Prelude.Text])
getNetworkAnalyzerConfigurationResponse_wirelessDevices :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe [Text])
getNetworkAnalyzerConfigurationResponse_wirelessDevices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe [Text]
wirelessDevices :: Maybe [Text]
$sel:wirelessDevices:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
wirelessDevices} -> Maybe [Text]
wirelessDevices) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe [Text]
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:wirelessDevices:GetNetworkAnalyzerConfigurationResponse' :: Maybe [Text]
wirelessDevices = Maybe [Text]
a} :: GetNetworkAnalyzerConfigurationResponse) 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

-- | List of wireless gateway resources that have been added to the network
-- analyzer configuration.
getNetworkAnalyzerConfigurationResponse_wirelessGateways :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse (Prelude.Maybe [Prelude.Text])
getNetworkAnalyzerConfigurationResponse_wirelessGateways :: Lens' GetNetworkAnalyzerConfigurationResponse (Maybe [Text])
getNetworkAnalyzerConfigurationResponse_wirelessGateways = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Maybe [Text]
wirelessGateways :: Maybe [Text]
$sel:wirelessGateways:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
wirelessGateways} -> Maybe [Text]
wirelessGateways) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Maybe [Text]
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:wirelessGateways:GetNetworkAnalyzerConfigurationResponse' :: Maybe [Text]
wirelessGateways = Maybe [Text]
a} :: GetNetworkAnalyzerConfigurationResponse) 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.
getNetworkAnalyzerConfigurationResponse_httpStatus :: Lens.Lens' GetNetworkAnalyzerConfigurationResponse Prelude.Int
getNetworkAnalyzerConfigurationResponse_httpStatus :: Lens' GetNetworkAnalyzerConfigurationResponse Int
getNetworkAnalyzerConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetNetworkAnalyzerConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetNetworkAnalyzerConfigurationResponse
s@GetNetworkAnalyzerConfigurationResponse' {} Int
a -> GetNetworkAnalyzerConfigurationResponse
s {$sel:httpStatus:GetNetworkAnalyzerConfigurationResponse' :: Int
httpStatus = Int
a} :: GetNetworkAnalyzerConfigurationResponse)

instance
  Prelude.NFData
    GetNetworkAnalyzerConfigurationResponse
  where
  rnf :: GetNetworkAnalyzerConfigurationResponse -> ()
rnf GetNetworkAnalyzerConfigurationResponse' {Int
Maybe [Text]
Maybe Text
Maybe TraceContent
httpStatus :: Int
wirelessGateways :: Maybe [Text]
wirelessDevices :: Maybe [Text]
traceContent :: Maybe TraceContent
name :: Maybe Text
description :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Int
$sel:wirelessGateways:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
$sel:wirelessDevices:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe [Text]
$sel:traceContent:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe TraceContent
$sel:name:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
$sel:description:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
$sel:arn:GetNetworkAnalyzerConfigurationResponse' :: GetNetworkAnalyzerConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TraceContent
traceContent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
wirelessDevices
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
wirelessGateways
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus