{-# 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.EnableDirectory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables the specified directory. Only disabled directories can be
-- enabled. Once enabled, the directory can then be read and written to.
module Amazonka.CloudDirectory.EnableDirectory
  ( -- * Creating a Request
    EnableDirectory (..),
    newEnableDirectory,

    -- * Request Lenses
    enableDirectory_directoryArn,

    -- * Destructuring the Response
    EnableDirectoryResponse (..),
    newEnableDirectoryResponse,

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

-- |
-- Create a value of 'EnableDirectory' 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:
--
-- 'directoryArn', 'enableDirectory_directoryArn' - The ARN of the directory to enable.
newEnableDirectory ::
  -- | 'directoryArn'
  Prelude.Text ->
  EnableDirectory
newEnableDirectory :: Text -> EnableDirectory
newEnableDirectory Text
pDirectoryArn_ =
  EnableDirectory' {$sel:directoryArn:EnableDirectory' :: Text
directoryArn = Text
pDirectoryArn_}

-- | The ARN of the directory to enable.
enableDirectory_directoryArn :: Lens.Lens' EnableDirectory Prelude.Text
enableDirectory_directoryArn :: Lens' EnableDirectory Text
enableDirectory_directoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableDirectory' {Text
directoryArn :: Text
$sel:directoryArn:EnableDirectory' :: EnableDirectory -> Text
directoryArn} -> Text
directoryArn) (\s :: EnableDirectory
s@EnableDirectory' {} Text
a -> EnableDirectory
s {$sel:directoryArn:EnableDirectory' :: Text
directoryArn = Text
a} :: EnableDirectory)

instance Core.AWSRequest EnableDirectory where
  type
    AWSResponse EnableDirectory =
      EnableDirectoryResponse
  request :: (Service -> Service) -> EnableDirectory -> Request EnableDirectory
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy EnableDirectory
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse EnableDirectory)))
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 ->
          Int -> Text -> EnableDirectoryResponse
EnableDirectoryResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"DirectoryArn")
      )

instance Prelude.Hashable EnableDirectory where
  hashWithSalt :: Int -> EnableDirectory -> Int
hashWithSalt Int
_salt EnableDirectory' {Text
directoryArn :: Text
$sel:directoryArn:EnableDirectory' :: EnableDirectory -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryArn

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

instance Data.ToHeaders EnableDirectory where
  toHeaders :: EnableDirectory -> ResponseHeaders
toHeaders EnableDirectory' {Text
directoryArn :: Text
$sel:directoryArn:EnableDirectory' :: EnableDirectory -> Text
..} =
    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 EnableDirectory where
  toJSON :: EnableDirectory -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath EnableDirectory where
  toPath :: EnableDirectory -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/directory/enable"

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

-- | /See:/ 'newEnableDirectoryResponse' smart constructor.
data EnableDirectoryResponse = EnableDirectoryResponse'
  { -- | The response's http status code.
    EnableDirectoryResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ARN of the enabled directory.
    EnableDirectoryResponse -> Text
directoryArn :: Prelude.Text
  }
  deriving (EnableDirectoryResponse -> EnableDirectoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableDirectoryResponse -> EnableDirectoryResponse -> Bool
$c/= :: EnableDirectoryResponse -> EnableDirectoryResponse -> Bool
== :: EnableDirectoryResponse -> EnableDirectoryResponse -> Bool
$c== :: EnableDirectoryResponse -> EnableDirectoryResponse -> Bool
Prelude.Eq, ReadPrec [EnableDirectoryResponse]
ReadPrec EnableDirectoryResponse
Int -> ReadS EnableDirectoryResponse
ReadS [EnableDirectoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableDirectoryResponse]
$creadListPrec :: ReadPrec [EnableDirectoryResponse]
readPrec :: ReadPrec EnableDirectoryResponse
$creadPrec :: ReadPrec EnableDirectoryResponse
readList :: ReadS [EnableDirectoryResponse]
$creadList :: ReadS [EnableDirectoryResponse]
readsPrec :: Int -> ReadS EnableDirectoryResponse
$creadsPrec :: Int -> ReadS EnableDirectoryResponse
Prelude.Read, Int -> EnableDirectoryResponse -> ShowS
[EnableDirectoryResponse] -> ShowS
EnableDirectoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableDirectoryResponse] -> ShowS
$cshowList :: [EnableDirectoryResponse] -> ShowS
show :: EnableDirectoryResponse -> String
$cshow :: EnableDirectoryResponse -> String
showsPrec :: Int -> EnableDirectoryResponse -> ShowS
$cshowsPrec :: Int -> EnableDirectoryResponse -> ShowS
Prelude.Show, forall x. Rep EnableDirectoryResponse x -> EnableDirectoryResponse
forall x. EnableDirectoryResponse -> Rep EnableDirectoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableDirectoryResponse x -> EnableDirectoryResponse
$cfrom :: forall x. EnableDirectoryResponse -> Rep EnableDirectoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableDirectoryResponse' 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:
--
-- 'httpStatus', 'enableDirectoryResponse_httpStatus' - The response's http status code.
--
-- 'directoryArn', 'enableDirectoryResponse_directoryArn' - The ARN of the enabled directory.
newEnableDirectoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'directoryArn'
  Prelude.Text ->
  EnableDirectoryResponse
newEnableDirectoryResponse :: Int -> Text -> EnableDirectoryResponse
newEnableDirectoryResponse
  Int
pHttpStatus_
  Text
pDirectoryArn_ =
    EnableDirectoryResponse'
      { $sel:httpStatus:EnableDirectoryResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:directoryArn:EnableDirectoryResponse' :: Text
directoryArn = Text
pDirectoryArn_
      }

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

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

instance Prelude.NFData EnableDirectoryResponse where
  rnf :: EnableDirectoryResponse -> ()
rnf EnableDirectoryResponse' {Int
Text
directoryArn :: Text
httpStatus :: Int
$sel:directoryArn:EnableDirectoryResponse' :: EnableDirectoryResponse -> Text
$sel:httpStatus:EnableDirectoryResponse' :: EnableDirectoryResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryArn