{-# 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.WorkSpacesWeb.GetBrowserSettings
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets browser settings.
module Amazonka.WorkSpacesWeb.GetBrowserSettings
  ( -- * Creating a Request
    GetBrowserSettings (..),
    newGetBrowserSettings,

    -- * Request Lenses
    getBrowserSettings_browserSettingsArn,

    -- * Destructuring the Response
    GetBrowserSettingsResponse (..),
    newGetBrowserSettingsResponse,

    -- * Response Lenses
    getBrowserSettingsResponse_browserSettings,
    getBrowserSettingsResponse_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.WorkSpacesWeb.Types

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

-- |
-- Create a value of 'GetBrowserSettings' 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:
--
-- 'browserSettingsArn', 'getBrowserSettings_browserSettingsArn' - The ARN of the browser settings.
newGetBrowserSettings ::
  -- | 'browserSettingsArn'
  Prelude.Text ->
  GetBrowserSettings
newGetBrowserSettings :: Text -> GetBrowserSettings
newGetBrowserSettings Text
pBrowserSettingsArn_ =
  GetBrowserSettings'
    { $sel:browserSettingsArn:GetBrowserSettings' :: Text
browserSettingsArn =
        Text
pBrowserSettingsArn_
    }

-- | The ARN of the browser settings.
getBrowserSettings_browserSettingsArn :: Lens.Lens' GetBrowserSettings Prelude.Text
getBrowserSettings_browserSettingsArn :: Lens' GetBrowserSettings Text
getBrowserSettings_browserSettingsArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBrowserSettings' {Text
browserSettingsArn :: Text
$sel:browserSettingsArn:GetBrowserSettings' :: GetBrowserSettings -> Text
browserSettingsArn} -> Text
browserSettingsArn) (\s :: GetBrowserSettings
s@GetBrowserSettings' {} Text
a -> GetBrowserSettings
s {$sel:browserSettingsArn:GetBrowserSettings' :: Text
browserSettingsArn = Text
a} :: GetBrowserSettings)

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

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

instance Data.ToHeaders GetBrowserSettings where
  toHeaders :: GetBrowserSettings -> 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.ToPath GetBrowserSettings where
  toPath :: GetBrowserSettings -> ByteString
toPath GetBrowserSettings' {Text
browserSettingsArn :: Text
$sel:browserSettingsArn:GetBrowserSettings' :: GetBrowserSettings -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/browserSettings/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
browserSettingsArn]

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

-- | /See:/ 'newGetBrowserSettingsResponse' smart constructor.
data GetBrowserSettingsResponse = GetBrowserSettingsResponse'
  { -- | The browser settings.
    GetBrowserSettingsResponse -> Maybe BrowserSettings
browserSettings :: Prelude.Maybe BrowserSettings,
    -- | The response's http status code.
    GetBrowserSettingsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBrowserSettingsResponse -> GetBrowserSettingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBrowserSettingsResponse -> GetBrowserSettingsResponse -> Bool
$c/= :: GetBrowserSettingsResponse -> GetBrowserSettingsResponse -> Bool
== :: GetBrowserSettingsResponse -> GetBrowserSettingsResponse -> Bool
$c== :: GetBrowserSettingsResponse -> GetBrowserSettingsResponse -> Bool
Prelude.Eq, Int -> GetBrowserSettingsResponse -> ShowS
[GetBrowserSettingsResponse] -> ShowS
GetBrowserSettingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBrowserSettingsResponse] -> ShowS
$cshowList :: [GetBrowserSettingsResponse] -> ShowS
show :: GetBrowserSettingsResponse -> String
$cshow :: GetBrowserSettingsResponse -> String
showsPrec :: Int -> GetBrowserSettingsResponse -> ShowS
$cshowsPrec :: Int -> GetBrowserSettingsResponse -> ShowS
Prelude.Show, forall x.
Rep GetBrowserSettingsResponse x -> GetBrowserSettingsResponse
forall x.
GetBrowserSettingsResponse -> Rep GetBrowserSettingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBrowserSettingsResponse x -> GetBrowserSettingsResponse
$cfrom :: forall x.
GetBrowserSettingsResponse -> Rep GetBrowserSettingsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBrowserSettingsResponse' 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:
--
-- 'browserSettings', 'getBrowserSettingsResponse_browserSettings' - The browser settings.
--
-- 'httpStatus', 'getBrowserSettingsResponse_httpStatus' - The response's http status code.
newGetBrowserSettingsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBrowserSettingsResponse
newGetBrowserSettingsResponse :: Int -> GetBrowserSettingsResponse
newGetBrowserSettingsResponse Int
pHttpStatus_ =
  GetBrowserSettingsResponse'
    { $sel:browserSettings:GetBrowserSettingsResponse' :: Maybe BrowserSettings
browserSettings =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBrowserSettingsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The browser settings.
getBrowserSettingsResponse_browserSettings :: Lens.Lens' GetBrowserSettingsResponse (Prelude.Maybe BrowserSettings)
getBrowserSettingsResponse_browserSettings :: Lens' GetBrowserSettingsResponse (Maybe BrowserSettings)
getBrowserSettingsResponse_browserSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBrowserSettingsResponse' {Maybe BrowserSettings
browserSettings :: Maybe BrowserSettings
$sel:browserSettings:GetBrowserSettingsResponse' :: GetBrowserSettingsResponse -> Maybe BrowserSettings
browserSettings} -> Maybe BrowserSettings
browserSettings) (\s :: GetBrowserSettingsResponse
s@GetBrowserSettingsResponse' {} Maybe BrowserSettings
a -> GetBrowserSettingsResponse
s {$sel:browserSettings:GetBrowserSettingsResponse' :: Maybe BrowserSettings
browserSettings = Maybe BrowserSettings
a} :: GetBrowserSettingsResponse)

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

instance Prelude.NFData GetBrowserSettingsResponse where
  rnf :: GetBrowserSettingsResponse -> ()
rnf GetBrowserSettingsResponse' {Int
Maybe BrowserSettings
httpStatus :: Int
browserSettings :: Maybe BrowserSettings
$sel:httpStatus:GetBrowserSettingsResponse' :: GetBrowserSettingsResponse -> Int
$sel:browserSettings:GetBrowserSettingsResponse' :: GetBrowserSettingsResponse -> Maybe BrowserSettings
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BrowserSettings
browserSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus