{-# 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.OpsWorks.DescribeCommands
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the results of specified commands.
--
-- This call accepts only one resource-identifying parameter.
--
-- __Required Permissions__: To use this action, an IAM user must have a
-- Show, Deploy, or Manage permissions level for the stack, or an attached
-- policy that explicitly grants permissions. For more information about
-- user permissions, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/opsworks-security-users.html Managing User Permissions>.
module Amazonka.OpsWorks.DescribeCommands
  ( -- * Creating a Request
    DescribeCommands (..),
    newDescribeCommands,

    -- * Request Lenses
    describeCommands_commandIds,
    describeCommands_deploymentId,
    describeCommands_instanceId,

    -- * Destructuring the Response
    DescribeCommandsResponse (..),
    newDescribeCommandsResponse,

    -- * Response Lenses
    describeCommandsResponse_commands,
    describeCommandsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeCommands' smart constructor.
data DescribeCommands = DescribeCommands'
  { -- | An array of command IDs. If you include this parameter,
    -- @DescribeCommands@ returns a description of the specified commands.
    -- Otherwise, it returns a description of every command.
    DescribeCommands -> Maybe [Text]
commandIds :: Prelude.Maybe [Prelude.Text],
    -- | The deployment ID. If you include this parameter, @DescribeCommands@
    -- returns a description of the commands associated with the specified
    -- deployment.
    DescribeCommands -> Maybe Text
deploymentId :: Prelude.Maybe Prelude.Text,
    -- | The instance ID. If you include this parameter, @DescribeCommands@
    -- returns a description of the commands associated with the specified
    -- instance.
    DescribeCommands -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeCommands -> DescribeCommands -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCommands -> DescribeCommands -> Bool
$c/= :: DescribeCommands -> DescribeCommands -> Bool
== :: DescribeCommands -> DescribeCommands -> Bool
$c== :: DescribeCommands -> DescribeCommands -> Bool
Prelude.Eq, ReadPrec [DescribeCommands]
ReadPrec DescribeCommands
Int -> ReadS DescribeCommands
ReadS [DescribeCommands]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCommands]
$creadListPrec :: ReadPrec [DescribeCommands]
readPrec :: ReadPrec DescribeCommands
$creadPrec :: ReadPrec DescribeCommands
readList :: ReadS [DescribeCommands]
$creadList :: ReadS [DescribeCommands]
readsPrec :: Int -> ReadS DescribeCommands
$creadsPrec :: Int -> ReadS DescribeCommands
Prelude.Read, Int -> DescribeCommands -> ShowS
[DescribeCommands] -> ShowS
DescribeCommands -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCommands] -> ShowS
$cshowList :: [DescribeCommands] -> ShowS
show :: DescribeCommands -> String
$cshow :: DescribeCommands -> String
showsPrec :: Int -> DescribeCommands -> ShowS
$cshowsPrec :: Int -> DescribeCommands -> ShowS
Prelude.Show, forall x. Rep DescribeCommands x -> DescribeCommands
forall x. DescribeCommands -> Rep DescribeCommands x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeCommands x -> DescribeCommands
$cfrom :: forall x. DescribeCommands -> Rep DescribeCommands x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCommands' 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:
--
-- 'commandIds', 'describeCommands_commandIds' - An array of command IDs. If you include this parameter,
-- @DescribeCommands@ returns a description of the specified commands.
-- Otherwise, it returns a description of every command.
--
-- 'deploymentId', 'describeCommands_deploymentId' - The deployment ID. If you include this parameter, @DescribeCommands@
-- returns a description of the commands associated with the specified
-- deployment.
--
-- 'instanceId', 'describeCommands_instanceId' - The instance ID. If you include this parameter, @DescribeCommands@
-- returns a description of the commands associated with the specified
-- instance.
newDescribeCommands ::
  DescribeCommands
newDescribeCommands :: DescribeCommands
newDescribeCommands =
  DescribeCommands'
    { $sel:commandIds:DescribeCommands' :: Maybe [Text]
commandIds = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentId:DescribeCommands' :: Maybe Text
deploymentId = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:DescribeCommands' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing
    }

-- | An array of command IDs. If you include this parameter,
-- @DescribeCommands@ returns a description of the specified commands.
-- Otherwise, it returns a description of every command.
describeCommands_commandIds :: Lens.Lens' DescribeCommands (Prelude.Maybe [Prelude.Text])
describeCommands_commandIds :: Lens' DescribeCommands (Maybe [Text])
describeCommands_commandIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCommands' {Maybe [Text]
commandIds :: Maybe [Text]
$sel:commandIds:DescribeCommands' :: DescribeCommands -> Maybe [Text]
commandIds} -> Maybe [Text]
commandIds) (\s :: DescribeCommands
s@DescribeCommands' {} Maybe [Text]
a -> DescribeCommands
s {$sel:commandIds:DescribeCommands' :: Maybe [Text]
commandIds = Maybe [Text]
a} :: DescribeCommands) 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 deployment ID. If you include this parameter, @DescribeCommands@
-- returns a description of the commands associated with the specified
-- deployment.
describeCommands_deploymentId :: Lens.Lens' DescribeCommands (Prelude.Maybe Prelude.Text)
describeCommands_deploymentId :: Lens' DescribeCommands (Maybe Text)
describeCommands_deploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCommands' {Maybe Text
deploymentId :: Maybe Text
$sel:deploymentId:DescribeCommands' :: DescribeCommands -> Maybe Text
deploymentId} -> Maybe Text
deploymentId) (\s :: DescribeCommands
s@DescribeCommands' {} Maybe Text
a -> DescribeCommands
s {$sel:deploymentId:DescribeCommands' :: Maybe Text
deploymentId = Maybe Text
a} :: DescribeCommands)

-- | The instance ID. If you include this parameter, @DescribeCommands@
-- returns a description of the commands associated with the specified
-- instance.
describeCommands_instanceId :: Lens.Lens' DescribeCommands (Prelude.Maybe Prelude.Text)
describeCommands_instanceId :: Lens' DescribeCommands (Maybe Text)
describeCommands_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCommands' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:DescribeCommands' :: DescribeCommands -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: DescribeCommands
s@DescribeCommands' {} Maybe Text
a -> DescribeCommands
s {$sel:instanceId:DescribeCommands' :: Maybe Text
instanceId = Maybe Text
a} :: DescribeCommands)

instance Core.AWSRequest DescribeCommands where
  type
    AWSResponse DescribeCommands =
      DescribeCommandsResponse
  request :: (Service -> Service)
-> DescribeCommands -> Request DescribeCommands
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 DescribeCommands
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeCommands)))
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 [Command] -> Int -> DescribeCommandsResponse
DescribeCommandsResponse'
            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
"Commands" 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 DescribeCommands where
  hashWithSalt :: Int -> DescribeCommands -> Int
hashWithSalt Int
_salt DescribeCommands' {Maybe [Text]
Maybe Text
instanceId :: Maybe Text
deploymentId :: Maybe Text
commandIds :: Maybe [Text]
$sel:instanceId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:deploymentId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:commandIds:DescribeCommands' :: DescribeCommands -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
commandIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId

instance Prelude.NFData DescribeCommands where
  rnf :: DescribeCommands -> ()
rnf DescribeCommands' {Maybe [Text]
Maybe Text
instanceId :: Maybe Text
deploymentId :: Maybe Text
commandIds :: Maybe [Text]
$sel:instanceId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:deploymentId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:commandIds:DescribeCommands' :: DescribeCommands -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
commandIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId

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

instance Data.ToJSON DescribeCommands where
  toJSON :: DescribeCommands -> Value
toJSON DescribeCommands' {Maybe [Text]
Maybe Text
instanceId :: Maybe Text
deploymentId :: Maybe Text
commandIds :: Maybe [Text]
$sel:instanceId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:deploymentId:DescribeCommands' :: DescribeCommands -> Maybe Text
$sel:commandIds:DescribeCommands' :: DescribeCommands -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CommandIds" 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]
commandIds,
            (Key
"DeploymentId" 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
deploymentId,
            (Key
"InstanceId" 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
instanceId
          ]
      )

instance Data.ToPath DescribeCommands where
  toPath :: DescribeCommands -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | Contains the response to a @DescribeCommands@ request.
--
-- /See:/ 'newDescribeCommandsResponse' smart constructor.
data DescribeCommandsResponse = DescribeCommandsResponse'
  { -- | An array of @Command@ objects that describe each of the specified
    -- commands.
    DescribeCommandsResponse -> Maybe [Command]
commands :: Prelude.Maybe [Command],
    -- | The response's http status code.
    DescribeCommandsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeCommandsResponse -> DescribeCommandsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCommandsResponse -> DescribeCommandsResponse -> Bool
$c/= :: DescribeCommandsResponse -> DescribeCommandsResponse -> Bool
== :: DescribeCommandsResponse -> DescribeCommandsResponse -> Bool
$c== :: DescribeCommandsResponse -> DescribeCommandsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCommandsResponse]
ReadPrec DescribeCommandsResponse
Int -> ReadS DescribeCommandsResponse
ReadS [DescribeCommandsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCommandsResponse]
$creadListPrec :: ReadPrec [DescribeCommandsResponse]
readPrec :: ReadPrec DescribeCommandsResponse
$creadPrec :: ReadPrec DescribeCommandsResponse
readList :: ReadS [DescribeCommandsResponse]
$creadList :: ReadS [DescribeCommandsResponse]
readsPrec :: Int -> ReadS DescribeCommandsResponse
$creadsPrec :: Int -> ReadS DescribeCommandsResponse
Prelude.Read, Int -> DescribeCommandsResponse -> ShowS
[DescribeCommandsResponse] -> ShowS
DescribeCommandsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCommandsResponse] -> ShowS
$cshowList :: [DescribeCommandsResponse] -> ShowS
show :: DescribeCommandsResponse -> String
$cshow :: DescribeCommandsResponse -> String
showsPrec :: Int -> DescribeCommandsResponse -> ShowS
$cshowsPrec :: Int -> DescribeCommandsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCommandsResponse x -> DescribeCommandsResponse
forall x.
DescribeCommandsResponse -> Rep DescribeCommandsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCommandsResponse x -> DescribeCommandsResponse
$cfrom :: forall x.
DescribeCommandsResponse -> Rep DescribeCommandsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCommandsResponse' 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:
--
-- 'commands', 'describeCommandsResponse_commands' - An array of @Command@ objects that describe each of the specified
-- commands.
--
-- 'httpStatus', 'describeCommandsResponse_httpStatus' - The response's http status code.
newDescribeCommandsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeCommandsResponse
newDescribeCommandsResponse :: Int -> DescribeCommandsResponse
newDescribeCommandsResponse Int
pHttpStatus_ =
  DescribeCommandsResponse'
    { $sel:commands:DescribeCommandsResponse' :: Maybe [Command]
commands =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeCommandsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @Command@ objects that describe each of the specified
-- commands.
describeCommandsResponse_commands :: Lens.Lens' DescribeCommandsResponse (Prelude.Maybe [Command])
describeCommandsResponse_commands :: Lens' DescribeCommandsResponse (Maybe [Command])
describeCommandsResponse_commands = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCommandsResponse' {Maybe [Command]
commands :: Maybe [Command]
$sel:commands:DescribeCommandsResponse' :: DescribeCommandsResponse -> Maybe [Command]
commands} -> Maybe [Command]
commands) (\s :: DescribeCommandsResponse
s@DescribeCommandsResponse' {} Maybe [Command]
a -> DescribeCommandsResponse
s {$sel:commands:DescribeCommandsResponse' :: Maybe [Command]
commands = Maybe [Command]
a} :: DescribeCommandsResponse) 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.
describeCommandsResponse_httpStatus :: Lens.Lens' DescribeCommandsResponse Prelude.Int
describeCommandsResponse_httpStatus :: Lens' DescribeCommandsResponse Int
describeCommandsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCommandsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeCommandsResponse' :: DescribeCommandsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeCommandsResponse
s@DescribeCommandsResponse' {} Int
a -> DescribeCommandsResponse
s {$sel:httpStatus:DescribeCommandsResponse' :: Int
httpStatus = Int
a} :: DescribeCommandsResponse)

instance Prelude.NFData DescribeCommandsResponse where
  rnf :: DescribeCommandsResponse -> ()
rnf DescribeCommandsResponse' {Int
Maybe [Command]
httpStatus :: Int
commands :: Maybe [Command]
$sel:httpStatus:DescribeCommandsResponse' :: DescribeCommandsResponse -> Int
$sel:commands:DescribeCommandsResponse' :: DescribeCommandsResponse -> Maybe [Command]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Command]
commands
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus