{-# 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.DirectoryService.UpdateRadius
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the Remote Authentication Dial In User Service (RADIUS) server
-- information for an AD Connector or Microsoft AD directory.
module Amazonka.DirectoryService.UpdateRadius
  ( -- * Creating a Request
    UpdateRadius (..),
    newUpdateRadius,

    -- * Request Lenses
    updateRadius_directoryId,
    updateRadius_radiusSettings,

    -- * Destructuring the Response
    UpdateRadiusResponse (..),
    newUpdateRadiusResponse,

    -- * Response Lenses
    updateRadiusResponse_httpStatus,
  )
where

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

-- | Contains the inputs for the UpdateRadius operation.
--
-- /See:/ 'newUpdateRadius' smart constructor.
data UpdateRadius = UpdateRadius'
  { -- | The identifier of the directory for which to update the RADIUS server
    -- information.
    UpdateRadius -> Text
directoryId :: Prelude.Text,
    -- | A RadiusSettings object that contains information about the RADIUS
    -- server.
    UpdateRadius -> RadiusSettings
radiusSettings :: RadiusSettings
  }
  deriving (UpdateRadius -> UpdateRadius -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRadius -> UpdateRadius -> Bool
$c/= :: UpdateRadius -> UpdateRadius -> Bool
== :: UpdateRadius -> UpdateRadius -> Bool
$c== :: UpdateRadius -> UpdateRadius -> Bool
Prelude.Eq, Int -> UpdateRadius -> ShowS
[UpdateRadius] -> ShowS
UpdateRadius -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRadius] -> ShowS
$cshowList :: [UpdateRadius] -> ShowS
show :: UpdateRadius -> String
$cshow :: UpdateRadius -> String
showsPrec :: Int -> UpdateRadius -> ShowS
$cshowsPrec :: Int -> UpdateRadius -> ShowS
Prelude.Show, forall x. Rep UpdateRadius x -> UpdateRadius
forall x. UpdateRadius -> Rep UpdateRadius x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRadius x -> UpdateRadius
$cfrom :: forall x. UpdateRadius -> Rep UpdateRadius x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRadius' 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:
--
-- 'directoryId', 'updateRadius_directoryId' - The identifier of the directory for which to update the RADIUS server
-- information.
--
-- 'radiusSettings', 'updateRadius_radiusSettings' - A RadiusSettings object that contains information about the RADIUS
-- server.
newUpdateRadius ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'radiusSettings'
  RadiusSettings ->
  UpdateRadius
newUpdateRadius :: Text -> RadiusSettings -> UpdateRadius
newUpdateRadius Text
pDirectoryId_ RadiusSettings
pRadiusSettings_ =
  UpdateRadius'
    { $sel:directoryId:UpdateRadius' :: Text
directoryId = Text
pDirectoryId_,
      $sel:radiusSettings:UpdateRadius' :: RadiusSettings
radiusSettings = RadiusSettings
pRadiusSettings_
    }

-- | The identifier of the directory for which to update the RADIUS server
-- information.
updateRadius_directoryId :: Lens.Lens' UpdateRadius Prelude.Text
updateRadius_directoryId :: Lens' UpdateRadius Text
updateRadius_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRadius' {Text
directoryId :: Text
$sel:directoryId:UpdateRadius' :: UpdateRadius -> Text
directoryId} -> Text
directoryId) (\s :: UpdateRadius
s@UpdateRadius' {} Text
a -> UpdateRadius
s {$sel:directoryId:UpdateRadius' :: Text
directoryId = Text
a} :: UpdateRadius)

-- | A RadiusSettings object that contains information about the RADIUS
-- server.
updateRadius_radiusSettings :: Lens.Lens' UpdateRadius RadiusSettings
updateRadius_radiusSettings :: Lens' UpdateRadius RadiusSettings
updateRadius_radiusSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRadius' {RadiusSettings
radiusSettings :: RadiusSettings
$sel:radiusSettings:UpdateRadius' :: UpdateRadius -> RadiusSettings
radiusSettings} -> RadiusSettings
radiusSettings) (\s :: UpdateRadius
s@UpdateRadius' {} RadiusSettings
a -> UpdateRadius
s {$sel:radiusSettings:UpdateRadius' :: RadiusSettings
radiusSettings = RadiusSettings
a} :: UpdateRadius)

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

instance Prelude.NFData UpdateRadius where
  rnf :: UpdateRadius -> ()
rnf UpdateRadius' {Text
RadiusSettings
radiusSettings :: RadiusSettings
directoryId :: Text
$sel:radiusSettings:UpdateRadius' :: UpdateRadius -> RadiusSettings
$sel:directoryId:UpdateRadius' :: UpdateRadius -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RadiusSettings
radiusSettings

instance Data.ToHeaders UpdateRadius where
  toHeaders :: UpdateRadius -> 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
"DirectoryService_20150416.UpdateRadius" ::
                          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 UpdateRadius where
  toJSON :: UpdateRadius -> Value
toJSON UpdateRadius' {Text
RadiusSettings
radiusSettings :: RadiusSettings
directoryId :: Text
$sel:radiusSettings:UpdateRadius' :: UpdateRadius -> RadiusSettings
$sel:directoryId:UpdateRadius' :: UpdateRadius -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"DirectoryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
directoryId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"RadiusSettings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RadiusSettings
radiusSettings)
          ]
      )

instance Data.ToPath UpdateRadius where
  toPath :: UpdateRadius -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | Contains the results of the UpdateRadius operation.
--
-- /See:/ 'newUpdateRadiusResponse' smart constructor.
data UpdateRadiusResponse = UpdateRadiusResponse'
  { -- | The response's http status code.
    UpdateRadiusResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRadiusResponse -> UpdateRadiusResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRadiusResponse -> UpdateRadiusResponse -> Bool
$c/= :: UpdateRadiusResponse -> UpdateRadiusResponse -> Bool
== :: UpdateRadiusResponse -> UpdateRadiusResponse -> Bool
$c== :: UpdateRadiusResponse -> UpdateRadiusResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRadiusResponse]
ReadPrec UpdateRadiusResponse
Int -> ReadS UpdateRadiusResponse
ReadS [UpdateRadiusResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRadiusResponse]
$creadListPrec :: ReadPrec [UpdateRadiusResponse]
readPrec :: ReadPrec UpdateRadiusResponse
$creadPrec :: ReadPrec UpdateRadiusResponse
readList :: ReadS [UpdateRadiusResponse]
$creadList :: ReadS [UpdateRadiusResponse]
readsPrec :: Int -> ReadS UpdateRadiusResponse
$creadsPrec :: Int -> ReadS UpdateRadiusResponse
Prelude.Read, Int -> UpdateRadiusResponse -> ShowS
[UpdateRadiusResponse] -> ShowS
UpdateRadiusResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRadiusResponse] -> ShowS
$cshowList :: [UpdateRadiusResponse] -> ShowS
show :: UpdateRadiusResponse -> String
$cshow :: UpdateRadiusResponse -> String
showsPrec :: Int -> UpdateRadiusResponse -> ShowS
$cshowsPrec :: Int -> UpdateRadiusResponse -> ShowS
Prelude.Show, forall x. Rep UpdateRadiusResponse x -> UpdateRadiusResponse
forall x. UpdateRadiusResponse -> Rep UpdateRadiusResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRadiusResponse x -> UpdateRadiusResponse
$cfrom :: forall x. UpdateRadiusResponse -> Rep UpdateRadiusResponse x
Prelude.Generic)

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

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

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