{-# 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.DescribeClientProperties
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list that describes one or more specified Amazon WorkSpaces
-- clients.
module Amazonka.WorkSpaces.DescribeClientProperties
  ( -- * Creating a Request
    DescribeClientProperties (..),
    newDescribeClientProperties,

    -- * Request Lenses
    describeClientProperties_resourceIds,

    -- * Destructuring the Response
    DescribeClientPropertiesResponse (..),
    newDescribeClientPropertiesResponse,

    -- * Response Lenses
    describeClientPropertiesResponse_clientPropertiesList,
    describeClientPropertiesResponse_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:/ 'newDescribeClientProperties' smart constructor.
data DescribeClientProperties = DescribeClientProperties'
  { -- | The resource identifier, in the form of directory IDs.
    DescribeClientProperties -> NonEmpty Text
resourceIds :: Prelude.NonEmpty Prelude.Text
  }
  deriving (DescribeClientProperties -> DescribeClientProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeClientProperties -> DescribeClientProperties -> Bool
$c/= :: DescribeClientProperties -> DescribeClientProperties -> Bool
== :: DescribeClientProperties -> DescribeClientProperties -> Bool
$c== :: DescribeClientProperties -> DescribeClientProperties -> Bool
Prelude.Eq, ReadPrec [DescribeClientProperties]
ReadPrec DescribeClientProperties
Int -> ReadS DescribeClientProperties
ReadS [DescribeClientProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeClientProperties]
$creadListPrec :: ReadPrec [DescribeClientProperties]
readPrec :: ReadPrec DescribeClientProperties
$creadPrec :: ReadPrec DescribeClientProperties
readList :: ReadS [DescribeClientProperties]
$creadList :: ReadS [DescribeClientProperties]
readsPrec :: Int -> ReadS DescribeClientProperties
$creadsPrec :: Int -> ReadS DescribeClientProperties
Prelude.Read, Int -> DescribeClientProperties -> ShowS
[DescribeClientProperties] -> ShowS
DescribeClientProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeClientProperties] -> ShowS
$cshowList :: [DescribeClientProperties] -> ShowS
show :: DescribeClientProperties -> String
$cshow :: DescribeClientProperties -> String
showsPrec :: Int -> DescribeClientProperties -> ShowS
$cshowsPrec :: Int -> DescribeClientProperties -> ShowS
Prelude.Show, forall x.
Rep DescribeClientProperties x -> DescribeClientProperties
forall x.
DescribeClientProperties -> Rep DescribeClientProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeClientProperties x -> DescribeClientProperties
$cfrom :: forall x.
DescribeClientProperties -> Rep DescribeClientProperties x
Prelude.Generic)

-- |
-- Create a value of 'DescribeClientProperties' 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:
--
-- 'resourceIds', 'describeClientProperties_resourceIds' - The resource identifier, in the form of directory IDs.
newDescribeClientProperties ::
  -- | 'resourceIds'
  Prelude.NonEmpty Prelude.Text ->
  DescribeClientProperties
newDescribeClientProperties :: NonEmpty Text -> DescribeClientProperties
newDescribeClientProperties NonEmpty Text
pResourceIds_ =
  DescribeClientProperties'
    { $sel:resourceIds:DescribeClientProperties' :: NonEmpty Text
resourceIds =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pResourceIds_
    }

-- | The resource identifier, in the form of directory IDs.
describeClientProperties_resourceIds :: Lens.Lens' DescribeClientProperties (Prelude.NonEmpty Prelude.Text)
describeClientProperties_resourceIds :: Lens' DescribeClientProperties (NonEmpty Text)
describeClientProperties_resourceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientProperties' {NonEmpty Text
resourceIds :: NonEmpty Text
$sel:resourceIds:DescribeClientProperties' :: DescribeClientProperties -> NonEmpty Text
resourceIds} -> NonEmpty Text
resourceIds) (\s :: DescribeClientProperties
s@DescribeClientProperties' {} NonEmpty Text
a -> DescribeClientProperties
s {$sel:resourceIds:DescribeClientProperties' :: NonEmpty Text
resourceIds = NonEmpty Text
a} :: DescribeClientProperties) 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 DescribeClientProperties where
  type
    AWSResponse DescribeClientProperties =
      DescribeClientPropertiesResponse
  request :: (Service -> Service)
-> DescribeClientProperties -> Request DescribeClientProperties
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 DescribeClientProperties
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeClientProperties)))
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 [ClientPropertiesResult]
-> Int -> DescribeClientPropertiesResponse
DescribeClientPropertiesResponse'
            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
"ClientPropertiesList"
                            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 DescribeClientProperties where
  hashWithSalt :: Int -> DescribeClientProperties -> Int
hashWithSalt Int
_salt DescribeClientProperties' {NonEmpty Text
resourceIds :: NonEmpty Text
$sel:resourceIds:DescribeClientProperties' :: DescribeClientProperties -> NonEmpty Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
resourceIds

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

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

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

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

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

-- |
-- Create a value of 'DescribeClientPropertiesResponse' 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:
--
-- 'clientPropertiesList', 'describeClientPropertiesResponse_clientPropertiesList' - Information about the specified Amazon WorkSpaces clients.
--
-- 'httpStatus', 'describeClientPropertiesResponse_httpStatus' - The response's http status code.
newDescribeClientPropertiesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeClientPropertiesResponse
newDescribeClientPropertiesResponse :: Int -> DescribeClientPropertiesResponse
newDescribeClientPropertiesResponse Int
pHttpStatus_ =
  DescribeClientPropertiesResponse'
    { $sel:clientPropertiesList:DescribeClientPropertiesResponse' :: Maybe [ClientPropertiesResult]
clientPropertiesList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeClientPropertiesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the specified Amazon WorkSpaces clients.
describeClientPropertiesResponse_clientPropertiesList :: Lens.Lens' DescribeClientPropertiesResponse (Prelude.Maybe [ClientPropertiesResult])
describeClientPropertiesResponse_clientPropertiesList :: Lens'
  DescribeClientPropertiesResponse (Maybe [ClientPropertiesResult])
describeClientPropertiesResponse_clientPropertiesList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientPropertiesResponse' {Maybe [ClientPropertiesResult]
clientPropertiesList :: Maybe [ClientPropertiesResult]
$sel:clientPropertiesList:DescribeClientPropertiesResponse' :: DescribeClientPropertiesResponse -> Maybe [ClientPropertiesResult]
clientPropertiesList} -> Maybe [ClientPropertiesResult]
clientPropertiesList) (\s :: DescribeClientPropertiesResponse
s@DescribeClientPropertiesResponse' {} Maybe [ClientPropertiesResult]
a -> DescribeClientPropertiesResponse
s {$sel:clientPropertiesList:DescribeClientPropertiesResponse' :: Maybe [ClientPropertiesResult]
clientPropertiesList = Maybe [ClientPropertiesResult]
a} :: DescribeClientPropertiesResponse) 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.
describeClientPropertiesResponse_httpStatus :: Lens.Lens' DescribeClientPropertiesResponse Prelude.Int
describeClientPropertiesResponse_httpStatus :: Lens' DescribeClientPropertiesResponse Int
describeClientPropertiesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClientPropertiesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeClientPropertiesResponse' :: DescribeClientPropertiesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeClientPropertiesResponse
s@DescribeClientPropertiesResponse' {} Int
a -> DescribeClientPropertiesResponse
s {$sel:httpStatus:DescribeClientPropertiesResponse' :: Int
httpStatus = Int
a} :: DescribeClientPropertiesResponse)

instance
  Prelude.NFData
    DescribeClientPropertiesResponse
  where
  rnf :: DescribeClientPropertiesResponse -> ()
rnf DescribeClientPropertiesResponse' {Int
Maybe [ClientPropertiesResult]
httpStatus :: Int
clientPropertiesList :: Maybe [ClientPropertiesResult]
$sel:httpStatus:DescribeClientPropertiesResponse' :: DescribeClientPropertiesResponse -> Int
$sel:clientPropertiesList:DescribeClientPropertiesResponse' :: DescribeClientPropertiesResponse -> Maybe [ClientPropertiesResult]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ClientPropertiesResult]
clientPropertiesList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus