{-# 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.MwAA.CreateCliToken
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a CLI token for the Airflow CLI. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/call-mwaa-apis-cli.html Creating an Apache Airflow CLI token>.
module Amazonka.MwAA.CreateCliToken
  ( -- * Creating a Request
    CreateCliToken (..),
    newCreateCliToken,

    -- * Request Lenses
    createCliToken_name,

    -- * Destructuring the Response
    CreateCliTokenResponse (..),
    newCreateCliTokenResponse,

    -- * Response Lenses
    createCliTokenResponse_cliToken,
    createCliTokenResponse_webServerHostname,
    createCliTokenResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MwAA.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateCliToken' smart constructor.
data CreateCliToken = CreateCliToken'
  { -- | The name of the Amazon MWAA environment. For example,
    -- @MyMWAAEnvironment@.
    CreateCliToken -> Text
name :: Prelude.Text
  }
  deriving (CreateCliToken -> CreateCliToken -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCliToken -> CreateCliToken -> Bool
$c/= :: CreateCliToken -> CreateCliToken -> Bool
== :: CreateCliToken -> CreateCliToken -> Bool
$c== :: CreateCliToken -> CreateCliToken -> Bool
Prelude.Eq, ReadPrec [CreateCliToken]
ReadPrec CreateCliToken
Int -> ReadS CreateCliToken
ReadS [CreateCliToken]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCliToken]
$creadListPrec :: ReadPrec [CreateCliToken]
readPrec :: ReadPrec CreateCliToken
$creadPrec :: ReadPrec CreateCliToken
readList :: ReadS [CreateCliToken]
$creadList :: ReadS [CreateCliToken]
readsPrec :: Int -> ReadS CreateCliToken
$creadsPrec :: Int -> ReadS CreateCliToken
Prelude.Read, Int -> CreateCliToken -> ShowS
[CreateCliToken] -> ShowS
CreateCliToken -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCliToken] -> ShowS
$cshowList :: [CreateCliToken] -> ShowS
show :: CreateCliToken -> String
$cshow :: CreateCliToken -> String
showsPrec :: Int -> CreateCliToken -> ShowS
$cshowsPrec :: Int -> CreateCliToken -> ShowS
Prelude.Show, forall x. Rep CreateCliToken x -> CreateCliToken
forall x. CreateCliToken -> Rep CreateCliToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCliToken x -> CreateCliToken
$cfrom :: forall x. CreateCliToken -> Rep CreateCliToken x
Prelude.Generic)

-- |
-- Create a value of 'CreateCliToken' 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:
--
-- 'name', 'createCliToken_name' - The name of the Amazon MWAA environment. For example,
-- @MyMWAAEnvironment@.
newCreateCliToken ::
  -- | 'name'
  Prelude.Text ->
  CreateCliToken
newCreateCliToken :: Text -> CreateCliToken
newCreateCliToken Text
pName_ =
  CreateCliToken' {$sel:name:CreateCliToken' :: Text
name = Text
pName_}

-- | The name of the Amazon MWAA environment. For example,
-- @MyMWAAEnvironment@.
createCliToken_name :: Lens.Lens' CreateCliToken Prelude.Text
createCliToken_name :: Lens' CreateCliToken Text
createCliToken_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCliToken' {Text
name :: Text
$sel:name:CreateCliToken' :: CreateCliToken -> Text
name} -> Text
name) (\s :: CreateCliToken
s@CreateCliToken' {} Text
a -> CreateCliToken
s {$sel:name:CreateCliToken' :: Text
name = Text
a} :: CreateCliToken)

instance Core.AWSRequest CreateCliToken where
  type
    AWSResponse CreateCliToken =
      CreateCliTokenResponse
  request :: (Service -> Service) -> CreateCliToken -> Request CreateCliToken
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 CreateCliToken
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateCliToken)))
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 (Sensitive Text)
-> Maybe Text -> Int -> CreateCliTokenResponse
CreateCliTokenResponse'
            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
"CliToken")
            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
"WebServerHostname")
            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 CreateCliToken where
  hashWithSalt :: Int -> CreateCliToken -> Int
hashWithSalt Int
_salt CreateCliToken' {Text
name :: Text
$sel:name:CreateCliToken' :: CreateCliToken -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders CreateCliToken where
  toHeaders :: CreateCliToken -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateCliToken where
  toJSON :: CreateCliToken -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath CreateCliToken where
  toPath :: CreateCliToken -> ByteString
toPath CreateCliToken' {Text
name :: Text
$sel:name:CreateCliToken' :: CreateCliToken -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/clitoken/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /See:/ 'newCreateCliTokenResponse' smart constructor.
data CreateCliTokenResponse = CreateCliTokenResponse'
  { -- | An Airflow CLI login token.
    CreateCliTokenResponse -> Maybe (Sensitive Text)
cliToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The Airflow web server hostname for the environment.
    CreateCliTokenResponse -> Maybe Text
webServerHostname :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateCliTokenResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCliTokenResponse -> CreateCliTokenResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCliTokenResponse -> CreateCliTokenResponse -> Bool
$c/= :: CreateCliTokenResponse -> CreateCliTokenResponse -> Bool
== :: CreateCliTokenResponse -> CreateCliTokenResponse -> Bool
$c== :: CreateCliTokenResponse -> CreateCliTokenResponse -> Bool
Prelude.Eq, Int -> CreateCliTokenResponse -> ShowS
[CreateCliTokenResponse] -> ShowS
CreateCliTokenResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCliTokenResponse] -> ShowS
$cshowList :: [CreateCliTokenResponse] -> ShowS
show :: CreateCliTokenResponse -> String
$cshow :: CreateCliTokenResponse -> String
showsPrec :: Int -> CreateCliTokenResponse -> ShowS
$cshowsPrec :: Int -> CreateCliTokenResponse -> ShowS
Prelude.Show, forall x. Rep CreateCliTokenResponse x -> CreateCliTokenResponse
forall x. CreateCliTokenResponse -> Rep CreateCliTokenResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCliTokenResponse x -> CreateCliTokenResponse
$cfrom :: forall x. CreateCliTokenResponse -> Rep CreateCliTokenResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCliTokenResponse' 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:
--
-- 'cliToken', 'createCliTokenResponse_cliToken' - An Airflow CLI login token.
--
-- 'webServerHostname', 'createCliTokenResponse_webServerHostname' - The Airflow web server hostname for the environment.
--
-- 'httpStatus', 'createCliTokenResponse_httpStatus' - The response's http status code.
newCreateCliTokenResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCliTokenResponse
newCreateCliTokenResponse :: Int -> CreateCliTokenResponse
newCreateCliTokenResponse Int
pHttpStatus_ =
  CreateCliTokenResponse'
    { $sel:cliToken:CreateCliTokenResponse' :: Maybe (Sensitive Text)
cliToken = forall a. Maybe a
Prelude.Nothing,
      $sel:webServerHostname:CreateCliTokenResponse' :: Maybe Text
webServerHostname = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCliTokenResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An Airflow CLI login token.
createCliTokenResponse_cliToken :: Lens.Lens' CreateCliTokenResponse (Prelude.Maybe Prelude.Text)
createCliTokenResponse_cliToken :: Lens' CreateCliTokenResponse (Maybe Text)
createCliTokenResponse_cliToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCliTokenResponse' {Maybe (Sensitive Text)
cliToken :: Maybe (Sensitive Text)
$sel:cliToken:CreateCliTokenResponse' :: CreateCliTokenResponse -> Maybe (Sensitive Text)
cliToken} -> Maybe (Sensitive Text)
cliToken) (\s :: CreateCliTokenResponse
s@CreateCliTokenResponse' {} Maybe (Sensitive Text)
a -> CreateCliTokenResponse
s {$sel:cliToken:CreateCliTokenResponse' :: Maybe (Sensitive Text)
cliToken = Maybe (Sensitive Text)
a} :: CreateCliTokenResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The Airflow web server hostname for the environment.
createCliTokenResponse_webServerHostname :: Lens.Lens' CreateCliTokenResponse (Prelude.Maybe Prelude.Text)
createCliTokenResponse_webServerHostname :: Lens' CreateCliTokenResponse (Maybe Text)
createCliTokenResponse_webServerHostname = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCliTokenResponse' {Maybe Text
webServerHostname :: Maybe Text
$sel:webServerHostname:CreateCliTokenResponse' :: CreateCliTokenResponse -> Maybe Text
webServerHostname} -> Maybe Text
webServerHostname) (\s :: CreateCliTokenResponse
s@CreateCliTokenResponse' {} Maybe Text
a -> CreateCliTokenResponse
s {$sel:webServerHostname:CreateCliTokenResponse' :: Maybe Text
webServerHostname = Maybe Text
a} :: CreateCliTokenResponse)

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

instance Prelude.NFData CreateCliTokenResponse where
  rnf :: CreateCliTokenResponse -> ()
rnf CreateCliTokenResponse' {Int
Maybe Text
Maybe (Sensitive Text)
httpStatus :: Int
webServerHostname :: Maybe Text
cliToken :: Maybe (Sensitive Text)
$sel:httpStatus:CreateCliTokenResponse' :: CreateCliTokenResponse -> Int
$sel:webServerHostname:CreateCliTokenResponse' :: CreateCliTokenResponse -> Maybe Text
$sel:cliToken:CreateCliTokenResponse' :: CreateCliTokenResponse -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
cliToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
webServerHostname
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus