{-# 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.CloudDirectory.GetTypedLinkFacetInformation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the identity attribute order for a specific TypedLinkFacet. For
-- more information, see
-- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
module Amazonka.CloudDirectory.GetTypedLinkFacetInformation
  ( -- * Creating a Request
    GetTypedLinkFacetInformation (..),
    newGetTypedLinkFacetInformation,

    -- * Request Lenses
    getTypedLinkFacetInformation_schemaArn,
    getTypedLinkFacetInformation_name,

    -- * Destructuring the Response
    GetTypedLinkFacetInformationResponse (..),
    newGetTypedLinkFacetInformationResponse,

    -- * Response Lenses
    getTypedLinkFacetInformationResponse_identityAttributeOrder,
    getTypedLinkFacetInformationResponse_httpStatus,
  )
where

import Amazonka.CloudDirectory.Types
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

-- | /See:/ 'newGetTypedLinkFacetInformation' smart constructor.
data GetTypedLinkFacetInformation = GetTypedLinkFacetInformation'
  { -- | The Amazon Resource Name (ARN) that is associated with the schema. For
    -- more information, see arns.
    GetTypedLinkFacetInformation -> Text
schemaArn :: Prelude.Text,
    -- | The unique name of the typed link facet.
    GetTypedLinkFacetInformation -> Text
name :: Prelude.Text
  }
  deriving (GetTypedLinkFacetInformation
-> GetTypedLinkFacetInformation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTypedLinkFacetInformation
-> GetTypedLinkFacetInformation -> Bool
$c/= :: GetTypedLinkFacetInformation
-> GetTypedLinkFacetInformation -> Bool
== :: GetTypedLinkFacetInformation
-> GetTypedLinkFacetInformation -> Bool
$c== :: GetTypedLinkFacetInformation
-> GetTypedLinkFacetInformation -> Bool
Prelude.Eq, ReadPrec [GetTypedLinkFacetInformation]
ReadPrec GetTypedLinkFacetInformation
Int -> ReadS GetTypedLinkFacetInformation
ReadS [GetTypedLinkFacetInformation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTypedLinkFacetInformation]
$creadListPrec :: ReadPrec [GetTypedLinkFacetInformation]
readPrec :: ReadPrec GetTypedLinkFacetInformation
$creadPrec :: ReadPrec GetTypedLinkFacetInformation
readList :: ReadS [GetTypedLinkFacetInformation]
$creadList :: ReadS [GetTypedLinkFacetInformation]
readsPrec :: Int -> ReadS GetTypedLinkFacetInformation
$creadsPrec :: Int -> ReadS GetTypedLinkFacetInformation
Prelude.Read, Int -> GetTypedLinkFacetInformation -> ShowS
[GetTypedLinkFacetInformation] -> ShowS
GetTypedLinkFacetInformation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTypedLinkFacetInformation] -> ShowS
$cshowList :: [GetTypedLinkFacetInformation] -> ShowS
show :: GetTypedLinkFacetInformation -> String
$cshow :: GetTypedLinkFacetInformation -> String
showsPrec :: Int -> GetTypedLinkFacetInformation -> ShowS
$cshowsPrec :: Int -> GetTypedLinkFacetInformation -> ShowS
Prelude.Show, forall x.
Rep GetTypedLinkFacetInformation x -> GetTypedLinkFacetInformation
forall x.
GetTypedLinkFacetInformation -> Rep GetTypedLinkFacetInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTypedLinkFacetInformation x -> GetTypedLinkFacetInformation
$cfrom :: forall x.
GetTypedLinkFacetInformation -> Rep GetTypedLinkFacetInformation x
Prelude.Generic)

-- |
-- Create a value of 'GetTypedLinkFacetInformation' 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:
--
-- 'schemaArn', 'getTypedLinkFacetInformation_schemaArn' - The Amazon Resource Name (ARN) that is associated with the schema. For
-- more information, see arns.
--
-- 'name', 'getTypedLinkFacetInformation_name' - The unique name of the typed link facet.
newGetTypedLinkFacetInformation ::
  -- | 'schemaArn'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  GetTypedLinkFacetInformation
newGetTypedLinkFacetInformation :: Text -> Text -> GetTypedLinkFacetInformation
newGetTypedLinkFacetInformation Text
pSchemaArn_ Text
pName_ =
  GetTypedLinkFacetInformation'
    { $sel:schemaArn:GetTypedLinkFacetInformation' :: Text
schemaArn =
        Text
pSchemaArn_,
      $sel:name:GetTypedLinkFacetInformation' :: Text
name = Text
pName_
    }

-- | The Amazon Resource Name (ARN) that is associated with the schema. For
-- more information, see arns.
getTypedLinkFacetInformation_schemaArn :: Lens.Lens' GetTypedLinkFacetInformation Prelude.Text
getTypedLinkFacetInformation_schemaArn :: Lens' GetTypedLinkFacetInformation Text
getTypedLinkFacetInformation_schemaArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTypedLinkFacetInformation' {Text
schemaArn :: Text
$sel:schemaArn:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
schemaArn} -> Text
schemaArn) (\s :: GetTypedLinkFacetInformation
s@GetTypedLinkFacetInformation' {} Text
a -> GetTypedLinkFacetInformation
s {$sel:schemaArn:GetTypedLinkFacetInformation' :: Text
schemaArn = Text
a} :: GetTypedLinkFacetInformation)

-- | The unique name of the typed link facet.
getTypedLinkFacetInformation_name :: Lens.Lens' GetTypedLinkFacetInformation Prelude.Text
getTypedLinkFacetInformation_name :: Lens' GetTypedLinkFacetInformation Text
getTypedLinkFacetInformation_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTypedLinkFacetInformation' {Text
name :: Text
$sel:name:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
name} -> Text
name) (\s :: GetTypedLinkFacetInformation
s@GetTypedLinkFacetInformation' {} Text
a -> GetTypedLinkFacetInformation
s {$sel:name:GetTypedLinkFacetInformation' :: Text
name = Text
a} :: GetTypedLinkFacetInformation)

instance Core.AWSRequest GetTypedLinkFacetInformation where
  type
    AWSResponse GetTypedLinkFacetInformation =
      GetTypedLinkFacetInformationResponse
  request :: (Service -> Service)
-> GetTypedLinkFacetInformation
-> Request GetTypedLinkFacetInformation
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 GetTypedLinkFacetInformation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetTypedLinkFacetInformation)))
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 [Text] -> Int -> GetTypedLinkFacetInformationResponse
GetTypedLinkFacetInformationResponse'
            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
"IdentityAttributeOrder"
                            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
    GetTypedLinkFacetInformation
  where
  hashWithSalt :: Int -> GetTypedLinkFacetInformation -> Int
hashWithSalt Int
_salt GetTypedLinkFacetInformation' {Text
name :: Text
schemaArn :: Text
$sel:name:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
$sel:schemaArn:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
schemaArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData GetTypedLinkFacetInformation where
  rnf :: GetTypedLinkFacetInformation -> ()
rnf GetTypedLinkFacetInformation' {Text
name :: Text
schemaArn :: Text
$sel:name:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
$sel:schemaArn:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
schemaArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders GetTypedLinkFacetInformation where
  toHeaders :: GetTypedLinkFacetInformation -> ResponseHeaders
toHeaders GetTypedLinkFacetInformation' {Text
name :: Text
schemaArn :: Text
$sel:name:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
$sel:schemaArn:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amz-data-partition" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
schemaArn]

instance Data.ToJSON GetTypedLinkFacetInformation where
  toJSON :: GetTypedLinkFacetInformation -> Value
toJSON GetTypedLinkFacetInformation' {Text
name :: Text
schemaArn :: Text
$sel:name:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
$sel:schemaArn:GetTypedLinkFacetInformation' :: GetTypedLinkFacetInformation -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

instance Data.ToPath GetTypedLinkFacetInformation where
  toPath :: GetTypedLinkFacetInformation -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/typedlink/facet/get"

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

-- | /See:/ 'newGetTypedLinkFacetInformationResponse' smart constructor.
data GetTypedLinkFacetInformationResponse = GetTypedLinkFacetInformationResponse'
  { -- | The order of identity attributes for the facet, from most significant to
    -- least significant. The ability to filter typed links considers the order
    -- that the attributes are defined on the typed link facet. When providing
    -- ranges to typed link selection, any inexact ranges must be specified at
    -- the end. Any attributes that do not have a range specified are presumed
    -- to match the entire range. Filters are interpreted in the order of the
    -- attributes on the typed link facet, not the order in which they are
    -- supplied to any API calls. For more information about identity
    -- attributes, see
    -- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
    GetTypedLinkFacetInformationResponse -> Maybe [Text]
identityAttributeOrder :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    GetTypedLinkFacetInformationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetTypedLinkFacetInformationResponse
-> GetTypedLinkFacetInformationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTypedLinkFacetInformationResponse
-> GetTypedLinkFacetInformationResponse -> Bool
$c/= :: GetTypedLinkFacetInformationResponse
-> GetTypedLinkFacetInformationResponse -> Bool
== :: GetTypedLinkFacetInformationResponse
-> GetTypedLinkFacetInformationResponse -> Bool
$c== :: GetTypedLinkFacetInformationResponse
-> GetTypedLinkFacetInformationResponse -> Bool
Prelude.Eq, ReadPrec [GetTypedLinkFacetInformationResponse]
ReadPrec GetTypedLinkFacetInformationResponse
Int -> ReadS GetTypedLinkFacetInformationResponse
ReadS [GetTypedLinkFacetInformationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTypedLinkFacetInformationResponse]
$creadListPrec :: ReadPrec [GetTypedLinkFacetInformationResponse]
readPrec :: ReadPrec GetTypedLinkFacetInformationResponse
$creadPrec :: ReadPrec GetTypedLinkFacetInformationResponse
readList :: ReadS [GetTypedLinkFacetInformationResponse]
$creadList :: ReadS [GetTypedLinkFacetInformationResponse]
readsPrec :: Int -> ReadS GetTypedLinkFacetInformationResponse
$creadsPrec :: Int -> ReadS GetTypedLinkFacetInformationResponse
Prelude.Read, Int -> GetTypedLinkFacetInformationResponse -> ShowS
[GetTypedLinkFacetInformationResponse] -> ShowS
GetTypedLinkFacetInformationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTypedLinkFacetInformationResponse] -> ShowS
$cshowList :: [GetTypedLinkFacetInformationResponse] -> ShowS
show :: GetTypedLinkFacetInformationResponse -> String
$cshow :: GetTypedLinkFacetInformationResponse -> String
showsPrec :: Int -> GetTypedLinkFacetInformationResponse -> ShowS
$cshowsPrec :: Int -> GetTypedLinkFacetInformationResponse -> ShowS
Prelude.Show, forall x.
Rep GetTypedLinkFacetInformationResponse x
-> GetTypedLinkFacetInformationResponse
forall x.
GetTypedLinkFacetInformationResponse
-> Rep GetTypedLinkFacetInformationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTypedLinkFacetInformationResponse x
-> GetTypedLinkFacetInformationResponse
$cfrom :: forall x.
GetTypedLinkFacetInformationResponse
-> Rep GetTypedLinkFacetInformationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTypedLinkFacetInformationResponse' 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:
--
-- 'identityAttributeOrder', 'getTypedLinkFacetInformationResponse_identityAttributeOrder' - The order of identity attributes for the facet, from most significant to
-- least significant. The ability to filter typed links considers the order
-- that the attributes are defined on the typed link facet. When providing
-- ranges to typed link selection, any inexact ranges must be specified at
-- the end. Any attributes that do not have a range specified are presumed
-- to match the entire range. Filters are interpreted in the order of the
-- attributes on the typed link facet, not the order in which they are
-- supplied to any API calls. For more information about identity
-- attributes, see
-- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
--
-- 'httpStatus', 'getTypedLinkFacetInformationResponse_httpStatus' - The response's http status code.
newGetTypedLinkFacetInformationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTypedLinkFacetInformationResponse
newGetTypedLinkFacetInformationResponse :: Int -> GetTypedLinkFacetInformationResponse
newGetTypedLinkFacetInformationResponse Int
pHttpStatus_ =
  GetTypedLinkFacetInformationResponse'
    { $sel:identityAttributeOrder:GetTypedLinkFacetInformationResponse' :: Maybe [Text]
identityAttributeOrder =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTypedLinkFacetInformationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The order of identity attributes for the facet, from most significant to
-- least significant. The ability to filter typed links considers the order
-- that the attributes are defined on the typed link facet. When providing
-- ranges to typed link selection, any inexact ranges must be specified at
-- the end. Any attributes that do not have a range specified are presumed
-- to match the entire range. Filters are interpreted in the order of the
-- attributes on the typed link facet, not the order in which they are
-- supplied to any API calls. For more information about identity
-- attributes, see
-- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
getTypedLinkFacetInformationResponse_identityAttributeOrder :: Lens.Lens' GetTypedLinkFacetInformationResponse (Prelude.Maybe [Prelude.Text])
getTypedLinkFacetInformationResponse_identityAttributeOrder :: Lens' GetTypedLinkFacetInformationResponse (Maybe [Text])
getTypedLinkFacetInformationResponse_identityAttributeOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTypedLinkFacetInformationResponse' {Maybe [Text]
identityAttributeOrder :: Maybe [Text]
$sel:identityAttributeOrder:GetTypedLinkFacetInformationResponse' :: GetTypedLinkFacetInformationResponse -> Maybe [Text]
identityAttributeOrder} -> Maybe [Text]
identityAttributeOrder) (\s :: GetTypedLinkFacetInformationResponse
s@GetTypedLinkFacetInformationResponse' {} Maybe [Text]
a -> GetTypedLinkFacetInformationResponse
s {$sel:identityAttributeOrder:GetTypedLinkFacetInformationResponse' :: Maybe [Text]
identityAttributeOrder = Maybe [Text]
a} :: GetTypedLinkFacetInformationResponse) 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.
getTypedLinkFacetInformationResponse_httpStatus :: Lens.Lens' GetTypedLinkFacetInformationResponse Prelude.Int
getTypedLinkFacetInformationResponse_httpStatus :: Lens' GetTypedLinkFacetInformationResponse Int
getTypedLinkFacetInformationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTypedLinkFacetInformationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetTypedLinkFacetInformationResponse' :: GetTypedLinkFacetInformationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetTypedLinkFacetInformationResponse
s@GetTypedLinkFacetInformationResponse' {} Int
a -> GetTypedLinkFacetInformationResponse
s {$sel:httpStatus:GetTypedLinkFacetInformationResponse' :: Int
httpStatus = Int
a} :: GetTypedLinkFacetInformationResponse)

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