{-# 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.ListIncomingTypedLinks
-- 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 a paginated list of all the incoming TypedLinkSpecifier
-- information for an object. It also supports filtering by typed link
-- facet and identity attributes. For more information, see
-- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
--
-- This operation returns paginated results.
module Amazonka.CloudDirectory.ListIncomingTypedLinks
  ( -- * Creating a Request
    ListIncomingTypedLinks (..),
    newListIncomingTypedLinks,

    -- * Request Lenses
    listIncomingTypedLinks_consistencyLevel,
    listIncomingTypedLinks_filterAttributeRanges,
    listIncomingTypedLinks_filterTypedLink,
    listIncomingTypedLinks_maxResults,
    listIncomingTypedLinks_nextToken,
    listIncomingTypedLinks_directoryArn,
    listIncomingTypedLinks_objectReference,

    -- * Destructuring the Response
    ListIncomingTypedLinksResponse (..),
    newListIncomingTypedLinksResponse,

    -- * Response Lenses
    listIncomingTypedLinksResponse_linkSpecifiers,
    listIncomingTypedLinksResponse_nextToken,
    listIncomingTypedLinksResponse_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:/ 'newListIncomingTypedLinks' smart constructor.
data ListIncomingTypedLinks = ListIncomingTypedLinks'
  { -- | The consistency level to execute the request at.
    ListIncomingTypedLinks -> Maybe ConsistencyLevel
consistencyLevel :: Prelude.Maybe ConsistencyLevel,
    -- | Provides range filters for multiple attributes. 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.
    ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges :: Prelude.Maybe [TypedLinkAttributeRange],
    -- | 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.
    ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink :: Prelude.Maybe TypedLinkSchemaAndFacetName,
    -- | The maximum number of results to retrieve.
    ListIncomingTypedLinks -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token.
    ListIncomingTypedLinks -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the directory where you want to list
    -- the typed links.
    ListIncomingTypedLinks -> Text
directoryArn :: Prelude.Text,
    -- | Reference that identifies the object whose attributes will be listed.
    ListIncomingTypedLinks -> ObjectReference
objectReference :: ObjectReference
  }
  deriving (ListIncomingTypedLinks -> ListIncomingTypedLinks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIncomingTypedLinks -> ListIncomingTypedLinks -> Bool
$c/= :: ListIncomingTypedLinks -> ListIncomingTypedLinks -> Bool
== :: ListIncomingTypedLinks -> ListIncomingTypedLinks -> Bool
$c== :: ListIncomingTypedLinks -> ListIncomingTypedLinks -> Bool
Prelude.Eq, ReadPrec [ListIncomingTypedLinks]
ReadPrec ListIncomingTypedLinks
Int -> ReadS ListIncomingTypedLinks
ReadS [ListIncomingTypedLinks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIncomingTypedLinks]
$creadListPrec :: ReadPrec [ListIncomingTypedLinks]
readPrec :: ReadPrec ListIncomingTypedLinks
$creadPrec :: ReadPrec ListIncomingTypedLinks
readList :: ReadS [ListIncomingTypedLinks]
$creadList :: ReadS [ListIncomingTypedLinks]
readsPrec :: Int -> ReadS ListIncomingTypedLinks
$creadsPrec :: Int -> ReadS ListIncomingTypedLinks
Prelude.Read, Int -> ListIncomingTypedLinks -> ShowS
[ListIncomingTypedLinks] -> ShowS
ListIncomingTypedLinks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIncomingTypedLinks] -> ShowS
$cshowList :: [ListIncomingTypedLinks] -> ShowS
show :: ListIncomingTypedLinks -> String
$cshow :: ListIncomingTypedLinks -> String
showsPrec :: Int -> ListIncomingTypedLinks -> ShowS
$cshowsPrec :: Int -> ListIncomingTypedLinks -> ShowS
Prelude.Show, forall x. Rep ListIncomingTypedLinks x -> ListIncomingTypedLinks
forall x. ListIncomingTypedLinks -> Rep ListIncomingTypedLinks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListIncomingTypedLinks x -> ListIncomingTypedLinks
$cfrom :: forall x. ListIncomingTypedLinks -> Rep ListIncomingTypedLinks x
Prelude.Generic)

-- |
-- Create a value of 'ListIncomingTypedLinks' 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:
--
-- 'consistencyLevel', 'listIncomingTypedLinks_consistencyLevel' - The consistency level to execute the request at.
--
-- 'filterAttributeRanges', 'listIncomingTypedLinks_filterAttributeRanges' - Provides range filters for multiple attributes. 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.
--
-- 'filterTypedLink', 'listIncomingTypedLinks_filterTypedLink' - 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.
--
-- 'maxResults', 'listIncomingTypedLinks_maxResults' - The maximum number of results to retrieve.
--
-- 'nextToken', 'listIncomingTypedLinks_nextToken' - The pagination token.
--
-- 'directoryArn', 'listIncomingTypedLinks_directoryArn' - The Amazon Resource Name (ARN) of the directory where you want to list
-- the typed links.
--
-- 'objectReference', 'listIncomingTypedLinks_objectReference' - Reference that identifies the object whose attributes will be listed.
newListIncomingTypedLinks ::
  -- | 'directoryArn'
  Prelude.Text ->
  -- | 'objectReference'
  ObjectReference ->
  ListIncomingTypedLinks
newListIncomingTypedLinks :: Text -> ObjectReference -> ListIncomingTypedLinks
newListIncomingTypedLinks
  Text
pDirectoryArn_
  ObjectReference
pObjectReference_ =
    ListIncomingTypedLinks'
      { $sel:consistencyLevel:ListIncomingTypedLinks' :: Maybe ConsistencyLevel
consistencyLevel =
          forall a. Maybe a
Prelude.Nothing,
        $sel:filterAttributeRanges:ListIncomingTypedLinks' :: Maybe [TypedLinkAttributeRange]
filterAttributeRanges = forall a. Maybe a
Prelude.Nothing,
        $sel:filterTypedLink:ListIncomingTypedLinks' :: Maybe TypedLinkSchemaAndFacetName
filterTypedLink = forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListIncomingTypedLinks' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListIncomingTypedLinks' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:directoryArn:ListIncomingTypedLinks' :: Text
directoryArn = Text
pDirectoryArn_,
        $sel:objectReference:ListIncomingTypedLinks' :: ObjectReference
objectReference = ObjectReference
pObjectReference_
      }

-- | The consistency level to execute the request at.
listIncomingTypedLinks_consistencyLevel :: Lens.Lens' ListIncomingTypedLinks (Prelude.Maybe ConsistencyLevel)
listIncomingTypedLinks_consistencyLevel :: Lens' ListIncomingTypedLinks (Maybe ConsistencyLevel)
listIncomingTypedLinks_consistencyLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Maybe ConsistencyLevel
consistencyLevel :: Maybe ConsistencyLevel
$sel:consistencyLevel:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe ConsistencyLevel
consistencyLevel} -> Maybe ConsistencyLevel
consistencyLevel) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Maybe ConsistencyLevel
a -> ListIncomingTypedLinks
s {$sel:consistencyLevel:ListIncomingTypedLinks' :: Maybe ConsistencyLevel
consistencyLevel = Maybe ConsistencyLevel
a} :: ListIncomingTypedLinks)

-- | Provides range filters for multiple attributes. 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.
listIncomingTypedLinks_filterAttributeRanges :: Lens.Lens' ListIncomingTypedLinks (Prelude.Maybe [TypedLinkAttributeRange])
listIncomingTypedLinks_filterAttributeRanges :: Lens' ListIncomingTypedLinks (Maybe [TypedLinkAttributeRange])
listIncomingTypedLinks_filterAttributeRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Maybe [TypedLinkAttributeRange]
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
$sel:filterAttributeRanges:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges} -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Maybe [TypedLinkAttributeRange]
a -> ListIncomingTypedLinks
s {$sel:filterAttributeRanges:ListIncomingTypedLinks' :: Maybe [TypedLinkAttributeRange]
filterAttributeRanges = Maybe [TypedLinkAttributeRange]
a} :: ListIncomingTypedLinks) 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

-- | 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.
listIncomingTypedLinks_filterTypedLink :: Lens.Lens' ListIncomingTypedLinks (Prelude.Maybe TypedLinkSchemaAndFacetName)
listIncomingTypedLinks_filterTypedLink :: Lens' ListIncomingTypedLinks (Maybe TypedLinkSchemaAndFacetName)
listIncomingTypedLinks_filterTypedLink = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Maybe TypedLinkSchemaAndFacetName
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
$sel:filterTypedLink:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink} -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Maybe TypedLinkSchemaAndFacetName
a -> ListIncomingTypedLinks
s {$sel:filterTypedLink:ListIncomingTypedLinks' :: Maybe TypedLinkSchemaAndFacetName
filterTypedLink = Maybe TypedLinkSchemaAndFacetName
a} :: ListIncomingTypedLinks)

-- | The maximum number of results to retrieve.
listIncomingTypedLinks_maxResults :: Lens.Lens' ListIncomingTypedLinks (Prelude.Maybe Prelude.Natural)
listIncomingTypedLinks_maxResults :: Lens' ListIncomingTypedLinks (Maybe Natural)
listIncomingTypedLinks_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Maybe Natural
a -> ListIncomingTypedLinks
s {$sel:maxResults:ListIncomingTypedLinks' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListIncomingTypedLinks)

-- | The pagination token.
listIncomingTypedLinks_nextToken :: Lens.Lens' ListIncomingTypedLinks (Prelude.Maybe Prelude.Text)
listIncomingTypedLinks_nextToken :: Lens' ListIncomingTypedLinks (Maybe Text)
listIncomingTypedLinks_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Maybe Text
a -> ListIncomingTypedLinks
s {$sel:nextToken:ListIncomingTypedLinks' :: Maybe Text
nextToken = Maybe Text
a} :: ListIncomingTypedLinks)

-- | The Amazon Resource Name (ARN) of the directory where you want to list
-- the typed links.
listIncomingTypedLinks_directoryArn :: Lens.Lens' ListIncomingTypedLinks Prelude.Text
listIncomingTypedLinks_directoryArn :: Lens' ListIncomingTypedLinks Text
listIncomingTypedLinks_directoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {Text
directoryArn :: Text
$sel:directoryArn:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Text
directoryArn} -> Text
directoryArn) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} Text
a -> ListIncomingTypedLinks
s {$sel:directoryArn:ListIncomingTypedLinks' :: Text
directoryArn = Text
a} :: ListIncomingTypedLinks)

-- | Reference that identifies the object whose attributes will be listed.
listIncomingTypedLinks_objectReference :: Lens.Lens' ListIncomingTypedLinks ObjectReference
listIncomingTypedLinks_objectReference :: Lens' ListIncomingTypedLinks ObjectReference
listIncomingTypedLinks_objectReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinks' {ObjectReference
objectReference :: ObjectReference
$sel:objectReference:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> ObjectReference
objectReference} -> ObjectReference
objectReference) (\s :: ListIncomingTypedLinks
s@ListIncomingTypedLinks' {} ObjectReference
a -> ListIncomingTypedLinks
s {$sel:objectReference:ListIncomingTypedLinks' :: ObjectReference
objectReference = ObjectReference
a} :: ListIncomingTypedLinks)

instance Core.AWSPager ListIncomingTypedLinks where
  page :: ListIncomingTypedLinks
-> AWSResponse ListIncomingTypedLinks
-> Maybe ListIncomingTypedLinks
page ListIncomingTypedLinks
rq AWSResponse ListIncomingTypedLinks
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListIncomingTypedLinks
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIncomingTypedLinksResponse (Maybe Text)
listIncomingTypedLinksResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListIncomingTypedLinks
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIncomingTypedLinksResponse (Maybe [TypedLinkSpecifier])
listIncomingTypedLinksResponse_linkSpecifiers
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListIncomingTypedLinks
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListIncomingTypedLinks (Maybe Text)
listIncomingTypedLinks_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListIncomingTypedLinks
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIncomingTypedLinksResponse (Maybe Text)
listIncomingTypedLinksResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListIncomingTypedLinks where
  type
    AWSResponse ListIncomingTypedLinks =
      ListIncomingTypedLinksResponse
  request :: (Service -> Service)
-> ListIncomingTypedLinks -> Request ListIncomingTypedLinks
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 ListIncomingTypedLinks
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListIncomingTypedLinks)))
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 [TypedLinkSpecifier]
-> Maybe Text -> Int -> ListIncomingTypedLinksResponse
ListIncomingTypedLinksResponse'
            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
"LinkSpecifiers" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            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 ListIncomingTypedLinks where
  hashWithSalt :: Int -> ListIncomingTypedLinks -> Int
hashWithSalt Int
_salt ListIncomingTypedLinks' {Maybe Natural
Maybe [TypedLinkAttributeRange]
Maybe Text
Maybe ConsistencyLevel
Maybe TypedLinkSchemaAndFacetName
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> ObjectReference
$sel:directoryArn:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Text
$sel:nextToken:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Text
$sel:maxResults:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe ConsistencyLevel
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConsistencyLevel
consistencyLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TypedLinkAttributeRange]
filterAttributeRanges
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TypedLinkSchemaAndFacetName
filterTypedLink
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectReference
objectReference

instance Prelude.NFData ListIncomingTypedLinks where
  rnf :: ListIncomingTypedLinks -> ()
rnf ListIncomingTypedLinks' {Maybe Natural
Maybe [TypedLinkAttributeRange]
Maybe Text
Maybe ConsistencyLevel
Maybe TypedLinkSchemaAndFacetName
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> ObjectReference
$sel:directoryArn:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Text
$sel:nextToken:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Text
$sel:maxResults:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe ConsistencyLevel
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConsistencyLevel
consistencyLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TypedLinkAttributeRange]
filterAttributeRanges
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TypedLinkSchemaAndFacetName
filterTypedLink
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectReference
objectReference

instance Data.ToHeaders ListIncomingTypedLinks where
  toHeaders :: ListIncomingTypedLinks -> ResponseHeaders
toHeaders ListIncomingTypedLinks' {Maybe Natural
Maybe [TypedLinkAttributeRange]
Maybe Text
Maybe ConsistencyLevel
Maybe TypedLinkSchemaAndFacetName
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> ObjectReference
$sel:directoryArn:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Text
$sel:nextToken:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Text
$sel:maxResults:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe ConsistencyLevel
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amz-data-partition" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
directoryArn]

instance Data.ToJSON ListIncomingTypedLinks where
  toJSON :: ListIncomingTypedLinks -> Value
toJSON ListIncomingTypedLinks' {Maybe Natural
Maybe [TypedLinkAttributeRange]
Maybe Text
Maybe ConsistencyLevel
Maybe TypedLinkSchemaAndFacetName
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> ObjectReference
$sel:directoryArn:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Text
$sel:nextToken:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Text
$sel:maxResults:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListIncomingTypedLinks' :: ListIncomingTypedLinks -> Maybe ConsistencyLevel
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConsistencyLevel" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConsistencyLevel
consistencyLevel,
            (Key
"FilterAttributeRanges" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TypedLinkAttributeRange]
filterAttributeRanges,
            (Key
"FilterTypedLink" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TypedLinkSchemaAndFacetName
filterTypedLink,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ObjectReference" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ObjectReference
objectReference)
          ]
      )

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

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

-- | /See:/ 'newListIncomingTypedLinksResponse' smart constructor.
data ListIncomingTypedLinksResponse = ListIncomingTypedLinksResponse'
  { -- | Returns one or more typed link specifiers as output.
    ListIncomingTypedLinksResponse -> Maybe [TypedLinkSpecifier]
linkSpecifiers :: Prelude.Maybe [TypedLinkSpecifier],
    -- | The pagination token.
    ListIncomingTypedLinksResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListIncomingTypedLinksResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListIncomingTypedLinksResponse
-> ListIncomingTypedLinksResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIncomingTypedLinksResponse
-> ListIncomingTypedLinksResponse -> Bool
$c/= :: ListIncomingTypedLinksResponse
-> ListIncomingTypedLinksResponse -> Bool
== :: ListIncomingTypedLinksResponse
-> ListIncomingTypedLinksResponse -> Bool
$c== :: ListIncomingTypedLinksResponse
-> ListIncomingTypedLinksResponse -> Bool
Prelude.Eq, ReadPrec [ListIncomingTypedLinksResponse]
ReadPrec ListIncomingTypedLinksResponse
Int -> ReadS ListIncomingTypedLinksResponse
ReadS [ListIncomingTypedLinksResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIncomingTypedLinksResponse]
$creadListPrec :: ReadPrec [ListIncomingTypedLinksResponse]
readPrec :: ReadPrec ListIncomingTypedLinksResponse
$creadPrec :: ReadPrec ListIncomingTypedLinksResponse
readList :: ReadS [ListIncomingTypedLinksResponse]
$creadList :: ReadS [ListIncomingTypedLinksResponse]
readsPrec :: Int -> ReadS ListIncomingTypedLinksResponse
$creadsPrec :: Int -> ReadS ListIncomingTypedLinksResponse
Prelude.Read, Int -> ListIncomingTypedLinksResponse -> ShowS
[ListIncomingTypedLinksResponse] -> ShowS
ListIncomingTypedLinksResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIncomingTypedLinksResponse] -> ShowS
$cshowList :: [ListIncomingTypedLinksResponse] -> ShowS
show :: ListIncomingTypedLinksResponse -> String
$cshow :: ListIncomingTypedLinksResponse -> String
showsPrec :: Int -> ListIncomingTypedLinksResponse -> ShowS
$cshowsPrec :: Int -> ListIncomingTypedLinksResponse -> ShowS
Prelude.Show, forall x.
Rep ListIncomingTypedLinksResponse x
-> ListIncomingTypedLinksResponse
forall x.
ListIncomingTypedLinksResponse
-> Rep ListIncomingTypedLinksResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListIncomingTypedLinksResponse x
-> ListIncomingTypedLinksResponse
$cfrom :: forall x.
ListIncomingTypedLinksResponse
-> Rep ListIncomingTypedLinksResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListIncomingTypedLinksResponse' 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:
--
-- 'linkSpecifiers', 'listIncomingTypedLinksResponse_linkSpecifiers' - Returns one or more typed link specifiers as output.
--
-- 'nextToken', 'listIncomingTypedLinksResponse_nextToken' - The pagination token.
--
-- 'httpStatus', 'listIncomingTypedLinksResponse_httpStatus' - The response's http status code.
newListIncomingTypedLinksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListIncomingTypedLinksResponse
newListIncomingTypedLinksResponse :: Int -> ListIncomingTypedLinksResponse
newListIncomingTypedLinksResponse Int
pHttpStatus_ =
  ListIncomingTypedLinksResponse'
    { $sel:linkSpecifiers:ListIncomingTypedLinksResponse' :: Maybe [TypedLinkSpecifier]
linkSpecifiers =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIncomingTypedLinksResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListIncomingTypedLinksResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns one or more typed link specifiers as output.
listIncomingTypedLinksResponse_linkSpecifiers :: Lens.Lens' ListIncomingTypedLinksResponse (Prelude.Maybe [TypedLinkSpecifier])
listIncomingTypedLinksResponse_linkSpecifiers :: Lens' ListIncomingTypedLinksResponse (Maybe [TypedLinkSpecifier])
listIncomingTypedLinksResponse_linkSpecifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinksResponse' {Maybe [TypedLinkSpecifier]
linkSpecifiers :: Maybe [TypedLinkSpecifier]
$sel:linkSpecifiers:ListIncomingTypedLinksResponse' :: ListIncomingTypedLinksResponse -> Maybe [TypedLinkSpecifier]
linkSpecifiers} -> Maybe [TypedLinkSpecifier]
linkSpecifiers) (\s :: ListIncomingTypedLinksResponse
s@ListIncomingTypedLinksResponse' {} Maybe [TypedLinkSpecifier]
a -> ListIncomingTypedLinksResponse
s {$sel:linkSpecifiers:ListIncomingTypedLinksResponse' :: Maybe [TypedLinkSpecifier]
linkSpecifiers = Maybe [TypedLinkSpecifier]
a} :: ListIncomingTypedLinksResponse) 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 pagination token.
listIncomingTypedLinksResponse_nextToken :: Lens.Lens' ListIncomingTypedLinksResponse (Prelude.Maybe Prelude.Text)
listIncomingTypedLinksResponse_nextToken :: Lens' ListIncomingTypedLinksResponse (Maybe Text)
listIncomingTypedLinksResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIncomingTypedLinksResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIncomingTypedLinksResponse' :: ListIncomingTypedLinksResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIncomingTypedLinksResponse
s@ListIncomingTypedLinksResponse' {} Maybe Text
a -> ListIncomingTypedLinksResponse
s {$sel:nextToken:ListIncomingTypedLinksResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListIncomingTypedLinksResponse)

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

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