{-# 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.AssociateIpGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates the specified IP access control group with the specified
-- directory.
module Amazonka.WorkSpaces.AssociateIpGroups
  ( -- * Creating a Request
    AssociateIpGroups (..),
    newAssociateIpGroups,

    -- * Request Lenses
    associateIpGroups_directoryId,
    associateIpGroups_groupIds,

    -- * Destructuring the Response
    AssociateIpGroupsResponse (..),
    newAssociateIpGroupsResponse,

    -- * Response Lenses
    associateIpGroupsResponse_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:/ 'newAssociateIpGroups' smart constructor.
data AssociateIpGroups = AssociateIpGroups'
  { -- | The identifier of the directory.
    AssociateIpGroups -> Text
directoryId :: Prelude.Text,
    -- | The identifiers of one or more IP access control groups.
    AssociateIpGroups -> [Text]
groupIds :: [Prelude.Text]
  }
  deriving (AssociateIpGroups -> AssociateIpGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateIpGroups -> AssociateIpGroups -> Bool
$c/= :: AssociateIpGroups -> AssociateIpGroups -> Bool
== :: AssociateIpGroups -> AssociateIpGroups -> Bool
$c== :: AssociateIpGroups -> AssociateIpGroups -> Bool
Prelude.Eq, ReadPrec [AssociateIpGroups]
ReadPrec AssociateIpGroups
Int -> ReadS AssociateIpGroups
ReadS [AssociateIpGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateIpGroups]
$creadListPrec :: ReadPrec [AssociateIpGroups]
readPrec :: ReadPrec AssociateIpGroups
$creadPrec :: ReadPrec AssociateIpGroups
readList :: ReadS [AssociateIpGroups]
$creadList :: ReadS [AssociateIpGroups]
readsPrec :: Int -> ReadS AssociateIpGroups
$creadsPrec :: Int -> ReadS AssociateIpGroups
Prelude.Read, Int -> AssociateIpGroups -> ShowS
[AssociateIpGroups] -> ShowS
AssociateIpGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateIpGroups] -> ShowS
$cshowList :: [AssociateIpGroups] -> ShowS
show :: AssociateIpGroups -> String
$cshow :: AssociateIpGroups -> String
showsPrec :: Int -> AssociateIpGroups -> ShowS
$cshowsPrec :: Int -> AssociateIpGroups -> ShowS
Prelude.Show, forall x. Rep AssociateIpGroups x -> AssociateIpGroups
forall x. AssociateIpGroups -> Rep AssociateIpGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateIpGroups x -> AssociateIpGroups
$cfrom :: forall x. AssociateIpGroups -> Rep AssociateIpGroups x
Prelude.Generic)

-- |
-- Create a value of 'AssociateIpGroups' 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', 'associateIpGroups_directoryId' - The identifier of the directory.
--
-- 'groupIds', 'associateIpGroups_groupIds' - The identifiers of one or more IP access control groups.
newAssociateIpGroups ::
  -- | 'directoryId'
  Prelude.Text ->
  AssociateIpGroups
newAssociateIpGroups :: Text -> AssociateIpGroups
newAssociateIpGroups Text
pDirectoryId_ =
  AssociateIpGroups'
    { $sel:directoryId:AssociateIpGroups' :: Text
directoryId = Text
pDirectoryId_,
      $sel:groupIds:AssociateIpGroups' :: [Text]
groupIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | The identifier of the directory.
associateIpGroups_directoryId :: Lens.Lens' AssociateIpGroups Prelude.Text
associateIpGroups_directoryId :: Lens' AssociateIpGroups Text
associateIpGroups_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateIpGroups' {Text
directoryId :: Text
$sel:directoryId:AssociateIpGroups' :: AssociateIpGroups -> Text
directoryId} -> Text
directoryId) (\s :: AssociateIpGroups
s@AssociateIpGroups' {} Text
a -> AssociateIpGroups
s {$sel:directoryId:AssociateIpGroups' :: Text
directoryId = Text
a} :: AssociateIpGroups)

-- | The identifiers of one or more IP access control groups.
associateIpGroups_groupIds :: Lens.Lens' AssociateIpGroups [Prelude.Text]
associateIpGroups_groupIds :: Lens' AssociateIpGroups [Text]
associateIpGroups_groupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateIpGroups' {[Text]
groupIds :: [Text]
$sel:groupIds:AssociateIpGroups' :: AssociateIpGroups -> [Text]
groupIds} -> [Text]
groupIds) (\s :: AssociateIpGroups
s@AssociateIpGroups' {} [Text]
a -> AssociateIpGroups
s {$sel:groupIds:AssociateIpGroups' :: [Text]
groupIds = [Text]
a} :: AssociateIpGroups) 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 AssociateIpGroups where
  type
    AWSResponse AssociateIpGroups =
      AssociateIpGroupsResponse
  request :: (Service -> Service)
-> AssociateIpGroups -> Request AssociateIpGroups
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 AssociateIpGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateIpGroups)))
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 -> AssociateIpGroupsResponse
AssociateIpGroupsResponse'
            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 AssociateIpGroups where
  hashWithSalt :: Int -> AssociateIpGroups -> Int
hashWithSalt Int
_salt AssociateIpGroups' {[Text]
Text
groupIds :: [Text]
directoryId :: Text
$sel:groupIds:AssociateIpGroups' :: AssociateIpGroups -> [Text]
$sel:directoryId:AssociateIpGroups' :: AssociateIpGroups -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
groupIds

instance Prelude.NFData AssociateIpGroups where
  rnf :: AssociateIpGroups -> ()
rnf AssociateIpGroups' {[Text]
Text
groupIds :: [Text]
directoryId :: Text
$sel:groupIds:AssociateIpGroups' :: AssociateIpGroups -> [Text]
$sel:directoryId:AssociateIpGroups' :: AssociateIpGroups -> 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 [Text]
groupIds

instance Data.ToHeaders AssociateIpGroups where
  toHeaders :: AssociateIpGroups -> 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.AssociateIpGroups" ::
                          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 AssociateIpGroups where
  toJSON :: AssociateIpGroups -> Value
toJSON AssociateIpGroups' {[Text]
Text
groupIds :: [Text]
directoryId :: Text
$sel:groupIds:AssociateIpGroups' :: AssociateIpGroups -> [Text]
$sel:directoryId:AssociateIpGroups' :: AssociateIpGroups -> 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
"GroupIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
groupIds)
          ]
      )

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

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

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

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

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

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