{-# 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.ListOutgoingTypedLinks
-- 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 outgoing 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.ListOutgoingTypedLinks
  ( -- * Creating a Request
    ListOutgoingTypedLinks (..),
    newListOutgoingTypedLinks,

    -- * Request Lenses
    listOutgoingTypedLinks_consistencyLevel,
    listOutgoingTypedLinks_filterAttributeRanges,
    listOutgoingTypedLinks_filterTypedLink,
    listOutgoingTypedLinks_maxResults,
    listOutgoingTypedLinks_nextToken,
    listOutgoingTypedLinks_directoryArn,
    listOutgoingTypedLinks_objectReference,

    -- * Destructuring the Response
    ListOutgoingTypedLinksResponse (..),
    newListOutgoingTypedLinksResponse,

    -- * Response Lenses
    listOutgoingTypedLinksResponse_nextToken,
    listOutgoingTypedLinksResponse_typedLinkSpecifiers,
    listOutgoingTypedLinksResponse_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:/ 'newListOutgoingTypedLinks' smart constructor.
data ListOutgoingTypedLinks = ListOutgoingTypedLinks'
  { -- | The consistency level to execute the request at.
    ListOutgoingTypedLinks -> 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.
    ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges :: Prelude.Maybe [TypedLinkAttributeRange],
    -- | Filters are interpreted in the order of the attributes defined on the
    -- typed link facet, not the order they are supplied to any API calls.
    ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink :: Prelude.Maybe TypedLinkSchemaAndFacetName,
    -- | The maximum number of results to retrieve.
    ListOutgoingTypedLinks -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token.
    ListOutgoingTypedLinks -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the directory where you want to list
    -- the typed links.
    ListOutgoingTypedLinks -> Text
directoryArn :: Prelude.Text,
    -- | A reference that identifies the object whose attributes will be listed.
    ListOutgoingTypedLinks -> ObjectReference
objectReference :: ObjectReference
  }
  deriving (ListOutgoingTypedLinks -> ListOutgoingTypedLinks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListOutgoingTypedLinks -> ListOutgoingTypedLinks -> Bool
$c/= :: ListOutgoingTypedLinks -> ListOutgoingTypedLinks -> Bool
== :: ListOutgoingTypedLinks -> ListOutgoingTypedLinks -> Bool
$c== :: ListOutgoingTypedLinks -> ListOutgoingTypedLinks -> Bool
Prelude.Eq, ReadPrec [ListOutgoingTypedLinks]
ReadPrec ListOutgoingTypedLinks
Int -> ReadS ListOutgoingTypedLinks
ReadS [ListOutgoingTypedLinks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListOutgoingTypedLinks]
$creadListPrec :: ReadPrec [ListOutgoingTypedLinks]
readPrec :: ReadPrec ListOutgoingTypedLinks
$creadPrec :: ReadPrec ListOutgoingTypedLinks
readList :: ReadS [ListOutgoingTypedLinks]
$creadList :: ReadS [ListOutgoingTypedLinks]
readsPrec :: Int -> ReadS ListOutgoingTypedLinks
$creadsPrec :: Int -> ReadS ListOutgoingTypedLinks
Prelude.Read, Int -> ListOutgoingTypedLinks -> ShowS
[ListOutgoingTypedLinks] -> ShowS
ListOutgoingTypedLinks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListOutgoingTypedLinks] -> ShowS
$cshowList :: [ListOutgoingTypedLinks] -> ShowS
show :: ListOutgoingTypedLinks -> String
$cshow :: ListOutgoingTypedLinks -> String
showsPrec :: Int -> ListOutgoingTypedLinks -> ShowS
$cshowsPrec :: Int -> ListOutgoingTypedLinks -> ShowS
Prelude.Show, forall x. Rep ListOutgoingTypedLinks x -> ListOutgoingTypedLinks
forall x. ListOutgoingTypedLinks -> Rep ListOutgoingTypedLinks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListOutgoingTypedLinks x -> ListOutgoingTypedLinks
$cfrom :: forall x. ListOutgoingTypedLinks -> Rep ListOutgoingTypedLinks x
Prelude.Generic)

-- |
-- Create a value of 'ListOutgoingTypedLinks' 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', 'listOutgoingTypedLinks_consistencyLevel' - The consistency level to execute the request at.
--
-- 'filterAttributeRanges', 'listOutgoingTypedLinks_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', 'listOutgoingTypedLinks_filterTypedLink' - Filters are interpreted in the order of the attributes defined on the
-- typed link facet, not the order they are supplied to any API calls.
--
-- 'maxResults', 'listOutgoingTypedLinks_maxResults' - The maximum number of results to retrieve.
--
-- 'nextToken', 'listOutgoingTypedLinks_nextToken' - The pagination token.
--
-- 'directoryArn', 'listOutgoingTypedLinks_directoryArn' - The Amazon Resource Name (ARN) of the directory where you want to list
-- the typed links.
--
-- 'objectReference', 'listOutgoingTypedLinks_objectReference' - A reference that identifies the object whose attributes will be listed.
newListOutgoingTypedLinks ::
  -- | 'directoryArn'
  Prelude.Text ->
  -- | 'objectReference'
  ObjectReference ->
  ListOutgoingTypedLinks
newListOutgoingTypedLinks :: Text -> ObjectReference -> ListOutgoingTypedLinks
newListOutgoingTypedLinks
  Text
pDirectoryArn_
  ObjectReference
pObjectReference_ =
    ListOutgoingTypedLinks'
      { $sel:consistencyLevel:ListOutgoingTypedLinks' :: Maybe ConsistencyLevel
consistencyLevel =
          forall a. Maybe a
Prelude.Nothing,
        $sel:filterAttributeRanges:ListOutgoingTypedLinks' :: Maybe [TypedLinkAttributeRange]
filterAttributeRanges = forall a. Maybe a
Prelude.Nothing,
        $sel:filterTypedLink:ListOutgoingTypedLinks' :: Maybe TypedLinkSchemaAndFacetName
filterTypedLink = forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListOutgoingTypedLinks' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListOutgoingTypedLinks' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:directoryArn:ListOutgoingTypedLinks' :: Text
directoryArn = Text
pDirectoryArn_,
        $sel:objectReference:ListOutgoingTypedLinks' :: ObjectReference
objectReference = ObjectReference
pObjectReference_
      }

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

-- | 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.
listOutgoingTypedLinks_filterAttributeRanges :: Lens.Lens' ListOutgoingTypedLinks (Prelude.Maybe [TypedLinkAttributeRange])
listOutgoingTypedLinks_filterAttributeRanges :: Lens' ListOutgoingTypedLinks (Maybe [TypedLinkAttributeRange])
listOutgoingTypedLinks_filterAttributeRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOutgoingTypedLinks' {Maybe [TypedLinkAttributeRange]
filterAttributeRanges :: Maybe [TypedLinkAttributeRange]
$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges} -> Maybe [TypedLinkAttributeRange]
filterAttributeRanges) (\s :: ListOutgoingTypedLinks
s@ListOutgoingTypedLinks' {} Maybe [TypedLinkAttributeRange]
a -> ListOutgoingTypedLinks
s {$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: Maybe [TypedLinkAttributeRange]
filterAttributeRanges = Maybe [TypedLinkAttributeRange]
a} :: ListOutgoingTypedLinks) 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 defined on the
-- typed link facet, not the order they are supplied to any API calls.
listOutgoingTypedLinks_filterTypedLink :: Lens.Lens' ListOutgoingTypedLinks (Prelude.Maybe TypedLinkSchemaAndFacetName)
listOutgoingTypedLinks_filterTypedLink :: Lens' ListOutgoingTypedLinks (Maybe TypedLinkSchemaAndFacetName)
listOutgoingTypedLinks_filterTypedLink = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOutgoingTypedLinks' {Maybe TypedLinkSchemaAndFacetName
filterTypedLink :: Maybe TypedLinkSchemaAndFacetName
$sel:filterTypedLink:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink} -> Maybe TypedLinkSchemaAndFacetName
filterTypedLink) (\s :: ListOutgoingTypedLinks
s@ListOutgoingTypedLinks' {} Maybe TypedLinkSchemaAndFacetName
a -> ListOutgoingTypedLinks
s {$sel:filterTypedLink:ListOutgoingTypedLinks' :: Maybe TypedLinkSchemaAndFacetName
filterTypedLink = Maybe TypedLinkSchemaAndFacetName
a} :: ListOutgoingTypedLinks)

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

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

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

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

instance Core.AWSPager ListOutgoingTypedLinks where
  page :: ListOutgoingTypedLinks
-> AWSResponse ListOutgoingTypedLinks
-> Maybe ListOutgoingTypedLinks
page ListOutgoingTypedLinks
rq AWSResponse ListOutgoingTypedLinks
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListOutgoingTypedLinks
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOutgoingTypedLinksResponse (Maybe Text)
listOutgoingTypedLinksResponse_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 ListOutgoingTypedLinks
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOutgoingTypedLinksResponse (Maybe [TypedLinkSpecifier])
listOutgoingTypedLinksResponse_typedLinkSpecifiers
            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.$ ListOutgoingTypedLinks
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListOutgoingTypedLinks (Maybe Text)
listOutgoingTypedLinks_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListOutgoingTypedLinks
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOutgoingTypedLinksResponse (Maybe Text)
listOutgoingTypedLinksResponse_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 ListOutgoingTypedLinks where
  type
    AWSResponse ListOutgoingTypedLinks =
      ListOutgoingTypedLinksResponse
  request :: (Service -> Service)
-> ListOutgoingTypedLinks -> Request ListOutgoingTypedLinks
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 ListOutgoingTypedLinks
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListOutgoingTypedLinks)))
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
-> Maybe [TypedLinkSpecifier]
-> Int
-> ListOutgoingTypedLinksResponse
ListOutgoingTypedLinksResponse'
            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
"NextToken")
            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
"TypedLinkSpecifiers"
                            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 ListOutgoingTypedLinks where
  hashWithSalt :: Int -> ListOutgoingTypedLinks -> Int
hashWithSalt Int
_salt ListOutgoingTypedLinks' {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:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> ObjectReference
$sel:directoryArn:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Text
$sel:nextToken:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Text
$sel:maxResults:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> 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 ListOutgoingTypedLinks where
  rnf :: ListOutgoingTypedLinks -> ()
rnf ListOutgoingTypedLinks' {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:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> ObjectReference
$sel:directoryArn:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Text
$sel:nextToken:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Text
$sel:maxResults:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> 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 ListOutgoingTypedLinks where
  toHeaders :: ListOutgoingTypedLinks -> ResponseHeaders
toHeaders ListOutgoingTypedLinks' {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:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> ObjectReference
$sel:directoryArn:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Text
$sel:nextToken:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Text
$sel:maxResults:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> 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 ListOutgoingTypedLinks where
  toJSON :: ListOutgoingTypedLinks -> Value
toJSON ListOutgoingTypedLinks' {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:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> ObjectReference
$sel:directoryArn:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Text
$sel:nextToken:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Text
$sel:maxResults:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe Natural
$sel:filterTypedLink:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe TypedLinkSchemaAndFacetName
$sel:filterAttributeRanges:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> Maybe [TypedLinkAttributeRange]
$sel:consistencyLevel:ListOutgoingTypedLinks' :: ListOutgoingTypedLinks -> 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 ListOutgoingTypedLinks where
  toPath :: ListOutgoingTypedLinks -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/typedlink/outgoing"

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

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

-- |
-- Create a value of 'ListOutgoingTypedLinksResponse' 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:
--
-- 'nextToken', 'listOutgoingTypedLinksResponse_nextToken' - The pagination token.
--
-- 'typedLinkSpecifiers', 'listOutgoingTypedLinksResponse_typedLinkSpecifiers' - Returns a typed link specifier as output.
--
-- 'httpStatus', 'listOutgoingTypedLinksResponse_httpStatus' - The response's http status code.
newListOutgoingTypedLinksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListOutgoingTypedLinksResponse
newListOutgoingTypedLinksResponse :: Int -> ListOutgoingTypedLinksResponse
newListOutgoingTypedLinksResponse Int
pHttpStatus_ =
  ListOutgoingTypedLinksResponse'
    { $sel:nextToken:ListOutgoingTypedLinksResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:typedLinkSpecifiers:ListOutgoingTypedLinksResponse' :: Maybe [TypedLinkSpecifier]
typedLinkSpecifiers = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListOutgoingTypedLinksResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Returns a typed link specifier as output.
listOutgoingTypedLinksResponse_typedLinkSpecifiers :: Lens.Lens' ListOutgoingTypedLinksResponse (Prelude.Maybe [TypedLinkSpecifier])
listOutgoingTypedLinksResponse_typedLinkSpecifiers :: Lens' ListOutgoingTypedLinksResponse (Maybe [TypedLinkSpecifier])
listOutgoingTypedLinksResponse_typedLinkSpecifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOutgoingTypedLinksResponse' {Maybe [TypedLinkSpecifier]
typedLinkSpecifiers :: Maybe [TypedLinkSpecifier]
$sel:typedLinkSpecifiers:ListOutgoingTypedLinksResponse' :: ListOutgoingTypedLinksResponse -> Maybe [TypedLinkSpecifier]
typedLinkSpecifiers} -> Maybe [TypedLinkSpecifier]
typedLinkSpecifiers) (\s :: ListOutgoingTypedLinksResponse
s@ListOutgoingTypedLinksResponse' {} Maybe [TypedLinkSpecifier]
a -> ListOutgoingTypedLinksResponse
s {$sel:typedLinkSpecifiers:ListOutgoingTypedLinksResponse' :: Maybe [TypedLinkSpecifier]
typedLinkSpecifiers = Maybe [TypedLinkSpecifier]
a} :: ListOutgoingTypedLinksResponse) 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.
listOutgoingTypedLinksResponse_httpStatus :: Lens.Lens' ListOutgoingTypedLinksResponse Prelude.Int
listOutgoingTypedLinksResponse_httpStatus :: Lens' ListOutgoingTypedLinksResponse Int
listOutgoingTypedLinksResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOutgoingTypedLinksResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListOutgoingTypedLinksResponse' :: ListOutgoingTypedLinksResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListOutgoingTypedLinksResponse
s@ListOutgoingTypedLinksResponse' {} Int
a -> ListOutgoingTypedLinksResponse
s {$sel:httpStatus:ListOutgoingTypedLinksResponse' :: Int
httpStatus = Int
a} :: ListOutgoingTypedLinksResponse)

instance
  Prelude.NFData
    ListOutgoingTypedLinksResponse
  where
  rnf :: ListOutgoingTypedLinksResponse -> ()
rnf ListOutgoingTypedLinksResponse' {Int
Maybe [TypedLinkSpecifier]
Maybe Text
httpStatus :: Int
typedLinkSpecifiers :: Maybe [TypedLinkSpecifier]
nextToken :: Maybe Text
$sel:httpStatus:ListOutgoingTypedLinksResponse' :: ListOutgoingTypedLinksResponse -> Int
$sel:typedLinkSpecifiers:ListOutgoingTypedLinksResponse' :: ListOutgoingTypedLinksResponse -> Maybe [TypedLinkSpecifier]
$sel:nextToken:ListOutgoingTypedLinksResponse' :: ListOutgoingTypedLinksResponse -> Maybe Text
..} =
    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 Maybe [TypedLinkSpecifier]
typedLinkSpecifiers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus