{-# 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.GetObjectInformation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves metadata about an object.
module Amazonka.CloudDirectory.GetObjectInformation
  ( -- * Creating a Request
    GetObjectInformation (..),
    newGetObjectInformation,

    -- * Request Lenses
    getObjectInformation_consistencyLevel,
    getObjectInformation_directoryArn,
    getObjectInformation_objectReference,

    -- * Destructuring the Response
    GetObjectInformationResponse (..),
    newGetObjectInformationResponse,

    -- * Response Lenses
    getObjectInformationResponse_objectIdentifier,
    getObjectInformationResponse_schemaFacets,
    getObjectInformationResponse_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:/ 'newGetObjectInformation' smart constructor.
data GetObjectInformation = GetObjectInformation'
  { -- | The consistency level at which to retrieve the object information.
    GetObjectInformation -> Maybe ConsistencyLevel
consistencyLevel :: Prelude.Maybe ConsistencyLevel,
    -- | The ARN of the directory being retrieved.
    GetObjectInformation -> Text
directoryArn :: Prelude.Text,
    -- | A reference to the object.
    GetObjectInformation -> ObjectReference
objectReference :: ObjectReference
  }
  deriving (GetObjectInformation -> GetObjectInformation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetObjectInformation -> GetObjectInformation -> Bool
$c/= :: GetObjectInformation -> GetObjectInformation -> Bool
== :: GetObjectInformation -> GetObjectInformation -> Bool
$c== :: GetObjectInformation -> GetObjectInformation -> Bool
Prelude.Eq, ReadPrec [GetObjectInformation]
ReadPrec GetObjectInformation
Int -> ReadS GetObjectInformation
ReadS [GetObjectInformation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetObjectInformation]
$creadListPrec :: ReadPrec [GetObjectInformation]
readPrec :: ReadPrec GetObjectInformation
$creadPrec :: ReadPrec GetObjectInformation
readList :: ReadS [GetObjectInformation]
$creadList :: ReadS [GetObjectInformation]
readsPrec :: Int -> ReadS GetObjectInformation
$creadsPrec :: Int -> ReadS GetObjectInformation
Prelude.Read, Int -> GetObjectInformation -> ShowS
[GetObjectInformation] -> ShowS
GetObjectInformation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectInformation] -> ShowS
$cshowList :: [GetObjectInformation] -> ShowS
show :: GetObjectInformation -> String
$cshow :: GetObjectInformation -> String
showsPrec :: Int -> GetObjectInformation -> ShowS
$cshowsPrec :: Int -> GetObjectInformation -> ShowS
Prelude.Show, forall x. Rep GetObjectInformation x -> GetObjectInformation
forall x. GetObjectInformation -> Rep GetObjectInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetObjectInformation x -> GetObjectInformation
$cfrom :: forall x. GetObjectInformation -> Rep GetObjectInformation x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectInformation' 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', 'getObjectInformation_consistencyLevel' - The consistency level at which to retrieve the object information.
--
-- 'directoryArn', 'getObjectInformation_directoryArn' - The ARN of the directory being retrieved.
--
-- 'objectReference', 'getObjectInformation_objectReference' - A reference to the object.
newGetObjectInformation ::
  -- | 'directoryArn'
  Prelude.Text ->
  -- | 'objectReference'
  ObjectReference ->
  GetObjectInformation
newGetObjectInformation :: Text -> ObjectReference -> GetObjectInformation
newGetObjectInformation
  Text
pDirectoryArn_
  ObjectReference
pObjectReference_ =
    GetObjectInformation'
      { $sel:consistencyLevel:GetObjectInformation' :: Maybe ConsistencyLevel
consistencyLevel =
          forall a. Maybe a
Prelude.Nothing,
        $sel:directoryArn:GetObjectInformation' :: Text
directoryArn = Text
pDirectoryArn_,
        $sel:objectReference:GetObjectInformation' :: ObjectReference
objectReference = ObjectReference
pObjectReference_
      }

-- | The consistency level at which to retrieve the object information.
getObjectInformation_consistencyLevel :: Lens.Lens' GetObjectInformation (Prelude.Maybe ConsistencyLevel)
getObjectInformation_consistencyLevel :: Lens' GetObjectInformation (Maybe ConsistencyLevel)
getObjectInformation_consistencyLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformation' {Maybe ConsistencyLevel
consistencyLevel :: Maybe ConsistencyLevel
$sel:consistencyLevel:GetObjectInformation' :: GetObjectInformation -> Maybe ConsistencyLevel
consistencyLevel} -> Maybe ConsistencyLevel
consistencyLevel) (\s :: GetObjectInformation
s@GetObjectInformation' {} Maybe ConsistencyLevel
a -> GetObjectInformation
s {$sel:consistencyLevel:GetObjectInformation' :: Maybe ConsistencyLevel
consistencyLevel = Maybe ConsistencyLevel
a} :: GetObjectInformation)

-- | The ARN of the directory being retrieved.
getObjectInformation_directoryArn :: Lens.Lens' GetObjectInformation Prelude.Text
getObjectInformation_directoryArn :: Lens' GetObjectInformation Text
getObjectInformation_directoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformation' {Text
directoryArn :: Text
$sel:directoryArn:GetObjectInformation' :: GetObjectInformation -> Text
directoryArn} -> Text
directoryArn) (\s :: GetObjectInformation
s@GetObjectInformation' {} Text
a -> GetObjectInformation
s {$sel:directoryArn:GetObjectInformation' :: Text
directoryArn = Text
a} :: GetObjectInformation)

-- | A reference to the object.
getObjectInformation_objectReference :: Lens.Lens' GetObjectInformation ObjectReference
getObjectInformation_objectReference :: Lens' GetObjectInformation ObjectReference
getObjectInformation_objectReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformation' {ObjectReference
objectReference :: ObjectReference
$sel:objectReference:GetObjectInformation' :: GetObjectInformation -> ObjectReference
objectReference} -> ObjectReference
objectReference) (\s :: GetObjectInformation
s@GetObjectInformation' {} ObjectReference
a -> GetObjectInformation
s {$sel:objectReference:GetObjectInformation' :: ObjectReference
objectReference = ObjectReference
a} :: GetObjectInformation)

instance Core.AWSRequest GetObjectInformation where
  type
    AWSResponse GetObjectInformation =
      GetObjectInformationResponse
  request :: (Service -> Service)
-> GetObjectInformation -> Request GetObjectInformation
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 GetObjectInformation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetObjectInformation)))
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 [SchemaFacet] -> Int -> GetObjectInformationResponse
GetObjectInformationResponse'
            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
"ObjectIdentifier")
            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
"SchemaFacets" 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 GetObjectInformation where
  hashWithSalt :: Int -> GetObjectInformation -> Int
hashWithSalt Int
_salt GetObjectInformation' {Maybe ConsistencyLevel
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:GetObjectInformation' :: GetObjectInformation -> ObjectReference
$sel:directoryArn:GetObjectInformation' :: GetObjectInformation -> Text
$sel:consistencyLevel:GetObjectInformation' :: GetObjectInformation -> 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` Text
directoryArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectReference
objectReference

instance Prelude.NFData GetObjectInformation where
  rnf :: GetObjectInformation -> ()
rnf GetObjectInformation' {Maybe ConsistencyLevel
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:GetObjectInformation' :: GetObjectInformation -> ObjectReference
$sel:directoryArn:GetObjectInformation' :: GetObjectInformation -> Text
$sel:consistencyLevel:GetObjectInformation' :: GetObjectInformation -> 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 Text
directoryArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectReference
objectReference

instance Data.ToHeaders GetObjectInformation where
  toHeaders :: GetObjectInformation -> ResponseHeaders
toHeaders GetObjectInformation' {Maybe ConsistencyLevel
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:GetObjectInformation' :: GetObjectInformation -> ObjectReference
$sel:directoryArn:GetObjectInformation' :: GetObjectInformation -> Text
$sel:consistencyLevel:GetObjectInformation' :: GetObjectInformation -> Maybe ConsistencyLevel
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-consistency-level" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ConsistencyLevel
consistencyLevel,
        HeaderName
"x-amz-data-partition" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
directoryArn
      ]

instance Data.ToJSON GetObjectInformation where
  toJSON :: GetObjectInformation -> Value
toJSON GetObjectInformation' {Maybe ConsistencyLevel
Text
ObjectReference
objectReference :: ObjectReference
directoryArn :: Text
consistencyLevel :: Maybe ConsistencyLevel
$sel:objectReference:GetObjectInformation' :: GetObjectInformation -> ObjectReference
$sel:directoryArn:GetObjectInformation' :: GetObjectInformation -> Text
$sel:consistencyLevel:GetObjectInformation' :: GetObjectInformation -> Maybe ConsistencyLevel
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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 GetObjectInformation where
  toPath :: GetObjectInformation -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/object/information"

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

-- | /See:/ 'newGetObjectInformationResponse' smart constructor.
data GetObjectInformationResponse = GetObjectInformationResponse'
  { -- | The @ObjectIdentifier@ of the specified object.
    GetObjectInformationResponse -> Maybe Text
objectIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The facets attached to the specified object. Although the response does
    -- not include minor version information, the most recently applied minor
    -- version of each Facet is in effect. See GetAppliedSchemaVersion for
    -- details.
    GetObjectInformationResponse -> Maybe [SchemaFacet]
schemaFacets :: Prelude.Maybe [SchemaFacet],
    -- | The response's http status code.
    GetObjectInformationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetObjectInformationResponse
-> GetObjectInformationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetObjectInformationResponse
-> GetObjectInformationResponse -> Bool
$c/= :: GetObjectInformationResponse
-> GetObjectInformationResponse -> Bool
== :: GetObjectInformationResponse
-> GetObjectInformationResponse -> Bool
$c== :: GetObjectInformationResponse
-> GetObjectInformationResponse -> Bool
Prelude.Eq, ReadPrec [GetObjectInformationResponse]
ReadPrec GetObjectInformationResponse
Int -> ReadS GetObjectInformationResponse
ReadS [GetObjectInformationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetObjectInformationResponse]
$creadListPrec :: ReadPrec [GetObjectInformationResponse]
readPrec :: ReadPrec GetObjectInformationResponse
$creadPrec :: ReadPrec GetObjectInformationResponse
readList :: ReadS [GetObjectInformationResponse]
$creadList :: ReadS [GetObjectInformationResponse]
readsPrec :: Int -> ReadS GetObjectInformationResponse
$creadsPrec :: Int -> ReadS GetObjectInformationResponse
Prelude.Read, Int -> GetObjectInformationResponse -> ShowS
[GetObjectInformationResponse] -> ShowS
GetObjectInformationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectInformationResponse] -> ShowS
$cshowList :: [GetObjectInformationResponse] -> ShowS
show :: GetObjectInformationResponse -> String
$cshow :: GetObjectInformationResponse -> String
showsPrec :: Int -> GetObjectInformationResponse -> ShowS
$cshowsPrec :: Int -> GetObjectInformationResponse -> ShowS
Prelude.Show, forall x.
Rep GetObjectInformationResponse x -> GetObjectInformationResponse
forall x.
GetObjectInformationResponse -> Rep GetObjectInformationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetObjectInformationResponse x -> GetObjectInformationResponse
$cfrom :: forall x.
GetObjectInformationResponse -> Rep GetObjectInformationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectInformationResponse' 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:
--
-- 'objectIdentifier', 'getObjectInformationResponse_objectIdentifier' - The @ObjectIdentifier@ of the specified object.
--
-- 'schemaFacets', 'getObjectInformationResponse_schemaFacets' - The facets attached to the specified object. Although the response does
-- not include minor version information, the most recently applied minor
-- version of each Facet is in effect. See GetAppliedSchemaVersion for
-- details.
--
-- 'httpStatus', 'getObjectInformationResponse_httpStatus' - The response's http status code.
newGetObjectInformationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetObjectInformationResponse
newGetObjectInformationResponse :: Int -> GetObjectInformationResponse
newGetObjectInformationResponse Int
pHttpStatus_ =
  GetObjectInformationResponse'
    { $sel:objectIdentifier:GetObjectInformationResponse' :: Maybe Text
objectIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:schemaFacets:GetObjectInformationResponse' :: Maybe [SchemaFacet]
schemaFacets = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetObjectInformationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @ObjectIdentifier@ of the specified object.
getObjectInformationResponse_objectIdentifier :: Lens.Lens' GetObjectInformationResponse (Prelude.Maybe Prelude.Text)
getObjectInformationResponse_objectIdentifier :: Lens' GetObjectInformationResponse (Maybe Text)
getObjectInformationResponse_objectIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformationResponse' {Maybe Text
objectIdentifier :: Maybe Text
$sel:objectIdentifier:GetObjectInformationResponse' :: GetObjectInformationResponse -> Maybe Text
objectIdentifier} -> Maybe Text
objectIdentifier) (\s :: GetObjectInformationResponse
s@GetObjectInformationResponse' {} Maybe Text
a -> GetObjectInformationResponse
s {$sel:objectIdentifier:GetObjectInformationResponse' :: Maybe Text
objectIdentifier = Maybe Text
a} :: GetObjectInformationResponse)

-- | The facets attached to the specified object. Although the response does
-- not include minor version information, the most recently applied minor
-- version of each Facet is in effect. See GetAppliedSchemaVersion for
-- details.
getObjectInformationResponse_schemaFacets :: Lens.Lens' GetObjectInformationResponse (Prelude.Maybe [SchemaFacet])
getObjectInformationResponse_schemaFacets :: Lens' GetObjectInformationResponse (Maybe [SchemaFacet])
getObjectInformationResponse_schemaFacets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformationResponse' {Maybe [SchemaFacet]
schemaFacets :: Maybe [SchemaFacet]
$sel:schemaFacets:GetObjectInformationResponse' :: GetObjectInformationResponse -> Maybe [SchemaFacet]
schemaFacets} -> Maybe [SchemaFacet]
schemaFacets) (\s :: GetObjectInformationResponse
s@GetObjectInformationResponse' {} Maybe [SchemaFacet]
a -> GetObjectInformationResponse
s {$sel:schemaFacets:GetObjectInformationResponse' :: Maybe [SchemaFacet]
schemaFacets = Maybe [SchemaFacet]
a} :: GetObjectInformationResponse) 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.
getObjectInformationResponse_httpStatus :: Lens.Lens' GetObjectInformationResponse Prelude.Int
getObjectInformationResponse_httpStatus :: Lens' GetObjectInformationResponse Int
getObjectInformationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectInformationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetObjectInformationResponse' :: GetObjectInformationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetObjectInformationResponse
s@GetObjectInformationResponse' {} Int
a -> GetObjectInformationResponse
s {$sel:httpStatus:GetObjectInformationResponse' :: Int
httpStatus = Int
a} :: GetObjectInformationResponse)

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