{-# 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.GetTrustStore
-- 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 the trust store.
module Amazonka.WorkSpacesWeb.GetTrustStore
  ( -- * Creating a Request
    GetTrustStore (..),
    newGetTrustStore,

    -- * Request Lenses
    getTrustStore_trustStoreArn,

    -- * Destructuring the Response
    GetTrustStoreResponse (..),
    newGetTrustStoreResponse,

    -- * Response Lenses
    getTrustStoreResponse_trustStore,
    getTrustStoreResponse_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:/ 'newGetTrustStore' smart constructor.
data GetTrustStore = GetTrustStore'
  { -- | The ARN of the trust store.
    GetTrustStore -> Text
trustStoreArn :: Prelude.Text
  }
  deriving (GetTrustStore -> GetTrustStore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTrustStore -> GetTrustStore -> Bool
$c/= :: GetTrustStore -> GetTrustStore -> Bool
== :: GetTrustStore -> GetTrustStore -> Bool
$c== :: GetTrustStore -> GetTrustStore -> Bool
Prelude.Eq, ReadPrec [GetTrustStore]
ReadPrec GetTrustStore
Int -> ReadS GetTrustStore
ReadS [GetTrustStore]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTrustStore]
$creadListPrec :: ReadPrec [GetTrustStore]
readPrec :: ReadPrec GetTrustStore
$creadPrec :: ReadPrec GetTrustStore
readList :: ReadS [GetTrustStore]
$creadList :: ReadS [GetTrustStore]
readsPrec :: Int -> ReadS GetTrustStore
$creadsPrec :: Int -> ReadS GetTrustStore
Prelude.Read, Int -> GetTrustStore -> ShowS
[GetTrustStore] -> ShowS
GetTrustStore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTrustStore] -> ShowS
$cshowList :: [GetTrustStore] -> ShowS
show :: GetTrustStore -> String
$cshow :: GetTrustStore -> String
showsPrec :: Int -> GetTrustStore -> ShowS
$cshowsPrec :: Int -> GetTrustStore -> ShowS
Prelude.Show, forall x. Rep GetTrustStore x -> GetTrustStore
forall x. GetTrustStore -> Rep GetTrustStore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTrustStore x -> GetTrustStore
$cfrom :: forall x. GetTrustStore -> Rep GetTrustStore x
Prelude.Generic)

-- |
-- Create a value of 'GetTrustStore' 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:
--
-- 'trustStoreArn', 'getTrustStore_trustStoreArn' - The ARN of the trust store.
newGetTrustStore ::
  -- | 'trustStoreArn'
  Prelude.Text ->
  GetTrustStore
newGetTrustStore :: Text -> GetTrustStore
newGetTrustStore Text
pTrustStoreArn_ =
  GetTrustStore' {$sel:trustStoreArn:GetTrustStore' :: Text
trustStoreArn = Text
pTrustStoreArn_}

-- | The ARN of the trust store.
getTrustStore_trustStoreArn :: Lens.Lens' GetTrustStore Prelude.Text
getTrustStore_trustStoreArn :: Lens' GetTrustStore Text
getTrustStore_trustStoreArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTrustStore' {Text
trustStoreArn :: Text
$sel:trustStoreArn:GetTrustStore' :: GetTrustStore -> Text
trustStoreArn} -> Text
trustStoreArn) (\s :: GetTrustStore
s@GetTrustStore' {} Text
a -> GetTrustStore
s {$sel:trustStoreArn:GetTrustStore' :: Text
trustStoreArn = Text
a} :: GetTrustStore)

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

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

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

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

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

-- |
-- Create a value of 'GetTrustStoreResponse' 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:
--
-- 'trustStore', 'getTrustStoreResponse_trustStore' - The trust store.
--
-- 'httpStatus', 'getTrustStoreResponse_httpStatus' - The response's http status code.
newGetTrustStoreResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTrustStoreResponse
newGetTrustStoreResponse :: Int -> GetTrustStoreResponse
newGetTrustStoreResponse Int
pHttpStatus_ =
  GetTrustStoreResponse'
    { $sel:trustStore:GetTrustStoreResponse' :: Maybe TrustStore
trustStore =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTrustStoreResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The trust store.
getTrustStoreResponse_trustStore :: Lens.Lens' GetTrustStoreResponse (Prelude.Maybe TrustStore)
getTrustStoreResponse_trustStore :: Lens' GetTrustStoreResponse (Maybe TrustStore)
getTrustStoreResponse_trustStore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTrustStoreResponse' {Maybe TrustStore
trustStore :: Maybe TrustStore
$sel:trustStore:GetTrustStoreResponse' :: GetTrustStoreResponse -> Maybe TrustStore
trustStore} -> Maybe TrustStore
trustStore) (\s :: GetTrustStoreResponse
s@GetTrustStoreResponse' {} Maybe TrustStore
a -> GetTrustStoreResponse
s {$sel:trustStore:GetTrustStoreResponse' :: Maybe TrustStore
trustStore = Maybe TrustStore
a} :: GetTrustStoreResponse)

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

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