{-# 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.WorkSpaces.AuthorizeIpRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds one or more rules to the specified IP access control group.
--
-- This action gives users permission to access their WorkSpaces from the
-- CIDR address ranges specified in the rules.
module Amazonka.WorkSpaces.AuthorizeIpRules
  ( -- * Creating a Request
    AuthorizeIpRules (..),
    newAuthorizeIpRules,

    -- * Request Lenses
    authorizeIpRules_groupId,
    authorizeIpRules_userRules,

    -- * Destructuring the Response
    AuthorizeIpRulesResponse (..),
    newAuthorizeIpRulesResponse,

    -- * Response Lenses
    authorizeIpRulesResponse_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.WorkSpaces.Types

-- | /See:/ 'newAuthorizeIpRules' smart constructor.
data AuthorizeIpRules = AuthorizeIpRules'
  { -- | The identifier of the group.
    AuthorizeIpRules -> Text
groupId :: Prelude.Text,
    -- | The rules to add to the group.
    AuthorizeIpRules -> [IpRuleItem]
userRules :: [IpRuleItem]
  }
  deriving (AuthorizeIpRules -> AuthorizeIpRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizeIpRules -> AuthorizeIpRules -> Bool
$c/= :: AuthorizeIpRules -> AuthorizeIpRules -> Bool
== :: AuthorizeIpRules -> AuthorizeIpRules -> Bool
$c== :: AuthorizeIpRules -> AuthorizeIpRules -> Bool
Prelude.Eq, ReadPrec [AuthorizeIpRules]
ReadPrec AuthorizeIpRules
Int -> ReadS AuthorizeIpRules
ReadS [AuthorizeIpRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AuthorizeIpRules]
$creadListPrec :: ReadPrec [AuthorizeIpRules]
readPrec :: ReadPrec AuthorizeIpRules
$creadPrec :: ReadPrec AuthorizeIpRules
readList :: ReadS [AuthorizeIpRules]
$creadList :: ReadS [AuthorizeIpRules]
readsPrec :: Int -> ReadS AuthorizeIpRules
$creadsPrec :: Int -> ReadS AuthorizeIpRules
Prelude.Read, Int -> AuthorizeIpRules -> ShowS
[AuthorizeIpRules] -> ShowS
AuthorizeIpRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizeIpRules] -> ShowS
$cshowList :: [AuthorizeIpRules] -> ShowS
show :: AuthorizeIpRules -> String
$cshow :: AuthorizeIpRules -> String
showsPrec :: Int -> AuthorizeIpRules -> ShowS
$cshowsPrec :: Int -> AuthorizeIpRules -> ShowS
Prelude.Show, forall x. Rep AuthorizeIpRules x -> AuthorizeIpRules
forall x. AuthorizeIpRules -> Rep AuthorizeIpRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthorizeIpRules x -> AuthorizeIpRules
$cfrom :: forall x. AuthorizeIpRules -> Rep AuthorizeIpRules x
Prelude.Generic)

-- |
-- Create a value of 'AuthorizeIpRules' 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:
--
-- 'groupId', 'authorizeIpRules_groupId' - The identifier of the group.
--
-- 'userRules', 'authorizeIpRules_userRules' - The rules to add to the group.
newAuthorizeIpRules ::
  -- | 'groupId'
  Prelude.Text ->
  AuthorizeIpRules
newAuthorizeIpRules :: Text -> AuthorizeIpRules
newAuthorizeIpRules Text
pGroupId_ =
  AuthorizeIpRules'
    { $sel:groupId:AuthorizeIpRules' :: Text
groupId = Text
pGroupId_,
      $sel:userRules:AuthorizeIpRules' :: [IpRuleItem]
userRules = forall a. Monoid a => a
Prelude.mempty
    }

-- | The identifier of the group.
authorizeIpRules_groupId :: Lens.Lens' AuthorizeIpRules Prelude.Text
authorizeIpRules_groupId :: Lens' AuthorizeIpRules Text
authorizeIpRules_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeIpRules' {Text
groupId :: Text
$sel:groupId:AuthorizeIpRules' :: AuthorizeIpRules -> Text
groupId} -> Text
groupId) (\s :: AuthorizeIpRules
s@AuthorizeIpRules' {} Text
a -> AuthorizeIpRules
s {$sel:groupId:AuthorizeIpRules' :: Text
groupId = Text
a} :: AuthorizeIpRules)

-- | The rules to add to the group.
authorizeIpRules_userRules :: Lens.Lens' AuthorizeIpRules [IpRuleItem]
authorizeIpRules_userRules :: Lens' AuthorizeIpRules [IpRuleItem]
authorizeIpRules_userRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeIpRules' {[IpRuleItem]
userRules :: [IpRuleItem]
$sel:userRules:AuthorizeIpRules' :: AuthorizeIpRules -> [IpRuleItem]
userRules} -> [IpRuleItem]
userRules) (\s :: AuthorizeIpRules
s@AuthorizeIpRules' {} [IpRuleItem]
a -> AuthorizeIpRules
s {$sel:userRules:AuthorizeIpRules' :: [IpRuleItem]
userRules = [IpRuleItem]
a} :: AuthorizeIpRules) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest AuthorizeIpRules where
  type
    AWSResponse AuthorizeIpRules =
      AuthorizeIpRulesResponse
  request :: (Service -> Service)
-> AuthorizeIpRules -> Request AuthorizeIpRules
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 AuthorizeIpRules
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AuthorizeIpRules)))
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 -> AuthorizeIpRulesResponse
AuthorizeIpRulesResponse'
            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 AuthorizeIpRules where
  hashWithSalt :: Int -> AuthorizeIpRules -> Int
hashWithSalt Int
_salt AuthorizeIpRules' {[IpRuleItem]
Text
userRules :: [IpRuleItem]
groupId :: Text
$sel:userRules:AuthorizeIpRules' :: AuthorizeIpRules -> [IpRuleItem]
$sel:groupId:AuthorizeIpRules' :: AuthorizeIpRules -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [IpRuleItem]
userRules

instance Prelude.NFData AuthorizeIpRules where
  rnf :: AuthorizeIpRules -> ()
rnf AuthorizeIpRules' {[IpRuleItem]
Text
userRules :: [IpRuleItem]
groupId :: Text
$sel:userRules:AuthorizeIpRules' :: AuthorizeIpRules -> [IpRuleItem]
$sel:groupId:AuthorizeIpRules' :: AuthorizeIpRules -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [IpRuleItem]
userRules

instance Data.ToHeaders AuthorizeIpRules where
  toHeaders :: AuthorizeIpRules -> 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
"WorkspacesService.AuthorizeIpRules" ::
                          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 AuthorizeIpRules where
  toJSON :: AuthorizeIpRules -> Value
toJSON AuthorizeIpRules' {[IpRuleItem]
Text
userRules :: [IpRuleItem]
groupId :: Text
$sel:userRules:AuthorizeIpRules' :: AuthorizeIpRules -> [IpRuleItem]
$sel:groupId:AuthorizeIpRules' :: AuthorizeIpRules -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"GroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupId),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserRules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [IpRuleItem]
userRules)
          ]
      )

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

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

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

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

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

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