{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SSM.Types.CommandFilter
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SSM.Types.CommandFilter where

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 Amazonka.SSM.Types.CommandFilterKey

-- | Describes a command filter.
--
-- A managed node ID can\'t be specified when a command status is @Pending@
-- because the command hasn\'t run on the node yet.
--
-- /See:/ 'newCommandFilter' smart constructor.
data CommandFilter = CommandFilter'
  { -- | The name of the filter.
    --
    -- The @ExecutionStage@ filter can\'t be used with the
    -- @ListCommandInvocations@ operation, only with @ListCommands@.
    CommandFilter -> CommandFilterKey
key :: CommandFilterKey,
    -- | The filter value. Valid values for each filter key are as follows:
    --
    -- -   __InvokedAfter__: Specify a timestamp to limit your results. For
    --     example, specify @2021-07-07T00:00:00Z@ to see a list of command
    --     executions occurring July 7, 2021, and later.
    --
    -- -   __InvokedBefore__: Specify a timestamp to limit your results. For
    --     example, specify @2021-07-07T00:00:00Z@ to see a list of command
    --     executions from before July 7, 2021.
    --
    -- -   __Status__: Specify a valid command status to see a list of all
    --     command executions with that status. The status choices depend on
    --     the API you call.
    --
    --     The status values you can specify for @ListCommands@ are:
    --
    --     -   @Pending@
    --
    --     -   @InProgress@
    --
    --     -   @Success@
    --
    --     -   @Cancelled@
    --
    --     -   @Failed@
    --
    --     -   @TimedOut@ (this includes both Delivery and Execution time outs)
    --
    --     -   @AccessDenied@
    --
    --     -   @DeliveryTimedOut@
    --
    --     -   @ExecutionTimedOut@
    --
    --     -   @Incomplete@
    --
    --     -   @NoInstancesInTag@
    --
    --     -   @LimitExceeded@
    --
    --     The status values you can specify for @ListCommandInvocations@ are:
    --
    --     -   @Pending@
    --
    --     -   @InProgress@
    --
    --     -   @Delayed@
    --
    --     -   @Success@
    --
    --     -   @Cancelled@
    --
    --     -   @Failed@
    --
    --     -   @TimedOut@ (this includes both Delivery and Execution time outs)
    --
    --     -   @AccessDenied@
    --
    --     -   @DeliveryTimedOut@
    --
    --     -   @ExecutionTimedOut@
    --
    --     -   @Undeliverable@
    --
    --     -   @InvalidPlatform@
    --
    --     -   @Terminated@
    --
    -- -   __DocumentName__: Specify name of the Amazon Web Services Systems
    --     Manager document (SSM document) for which you want to see command
    --     execution results. For example, specify @AWS-RunPatchBaseline@ to
    --     see command executions that used this SSM document to perform
    --     security patching operations on managed nodes.
    --
    -- -   __ExecutionStage__: Specify one of the following values
    --     (@ListCommands@ operations only):
    --
    --     -   @Executing@: Returns a list of command executions that are
    --         currently still running.
    --
    --     -   @Complete@: Returns a list of command executions that have
    --         already completed.
    CommandFilter -> Text
value :: Prelude.Text
  }
  deriving (CommandFilter -> CommandFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandFilter -> CommandFilter -> Bool
$c/= :: CommandFilter -> CommandFilter -> Bool
== :: CommandFilter -> CommandFilter -> Bool
$c== :: CommandFilter -> CommandFilter -> Bool
Prelude.Eq, ReadPrec [CommandFilter]
ReadPrec CommandFilter
Int -> ReadS CommandFilter
ReadS [CommandFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommandFilter]
$creadListPrec :: ReadPrec [CommandFilter]
readPrec :: ReadPrec CommandFilter
$creadPrec :: ReadPrec CommandFilter
readList :: ReadS [CommandFilter]
$creadList :: ReadS [CommandFilter]
readsPrec :: Int -> ReadS CommandFilter
$creadsPrec :: Int -> ReadS CommandFilter
Prelude.Read, Int -> CommandFilter -> ShowS
[CommandFilter] -> ShowS
CommandFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandFilter] -> ShowS
$cshowList :: [CommandFilter] -> ShowS
show :: CommandFilter -> String
$cshow :: CommandFilter -> String
showsPrec :: Int -> CommandFilter -> ShowS
$cshowsPrec :: Int -> CommandFilter -> ShowS
Prelude.Show, forall x. Rep CommandFilter x -> CommandFilter
forall x. CommandFilter -> Rep CommandFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommandFilter x -> CommandFilter
$cfrom :: forall x. CommandFilter -> Rep CommandFilter x
Prelude.Generic)

-- |
-- Create a value of 'CommandFilter' 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:
--
-- 'key', 'commandFilter_key' - The name of the filter.
--
-- The @ExecutionStage@ filter can\'t be used with the
-- @ListCommandInvocations@ operation, only with @ListCommands@.
--
-- 'value', 'commandFilter_value' - The filter value. Valid values for each filter key are as follows:
--
-- -   __InvokedAfter__: Specify a timestamp to limit your results. For
--     example, specify @2021-07-07T00:00:00Z@ to see a list of command
--     executions occurring July 7, 2021, and later.
--
-- -   __InvokedBefore__: Specify a timestamp to limit your results. For
--     example, specify @2021-07-07T00:00:00Z@ to see a list of command
--     executions from before July 7, 2021.
--
-- -   __Status__: Specify a valid command status to see a list of all
--     command executions with that status. The status choices depend on
--     the API you call.
--
--     The status values you can specify for @ListCommands@ are:
--
--     -   @Pending@
--
--     -   @InProgress@
--
--     -   @Success@
--
--     -   @Cancelled@
--
--     -   @Failed@
--
--     -   @TimedOut@ (this includes both Delivery and Execution time outs)
--
--     -   @AccessDenied@
--
--     -   @DeliveryTimedOut@
--
--     -   @ExecutionTimedOut@
--
--     -   @Incomplete@
--
--     -   @NoInstancesInTag@
--
--     -   @LimitExceeded@
--
--     The status values you can specify for @ListCommandInvocations@ are:
--
--     -   @Pending@
--
--     -   @InProgress@
--
--     -   @Delayed@
--
--     -   @Success@
--
--     -   @Cancelled@
--
--     -   @Failed@
--
--     -   @TimedOut@ (this includes both Delivery and Execution time outs)
--
--     -   @AccessDenied@
--
--     -   @DeliveryTimedOut@
--
--     -   @ExecutionTimedOut@
--
--     -   @Undeliverable@
--
--     -   @InvalidPlatform@
--
--     -   @Terminated@
--
-- -   __DocumentName__: Specify name of the Amazon Web Services Systems
--     Manager document (SSM document) for which you want to see command
--     execution results. For example, specify @AWS-RunPatchBaseline@ to
--     see command executions that used this SSM document to perform
--     security patching operations on managed nodes.
--
-- -   __ExecutionStage__: Specify one of the following values
--     (@ListCommands@ operations only):
--
--     -   @Executing@: Returns a list of command executions that are
--         currently still running.
--
--     -   @Complete@: Returns a list of command executions that have
--         already completed.
newCommandFilter ::
  -- | 'key'
  CommandFilterKey ->
  -- | 'value'
  Prelude.Text ->
  CommandFilter
newCommandFilter :: CommandFilterKey -> Text -> CommandFilter
newCommandFilter CommandFilterKey
pKey_ Text
pValue_ =
  CommandFilter' {$sel:key:CommandFilter' :: CommandFilterKey
key = CommandFilterKey
pKey_, $sel:value:CommandFilter' :: Text
value = Text
pValue_}

-- | The name of the filter.
--
-- The @ExecutionStage@ filter can\'t be used with the
-- @ListCommandInvocations@ operation, only with @ListCommands@.
commandFilter_key :: Lens.Lens' CommandFilter CommandFilterKey
commandFilter_key :: Lens' CommandFilter CommandFilterKey
commandFilter_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CommandFilter' {CommandFilterKey
key :: CommandFilterKey
$sel:key:CommandFilter' :: CommandFilter -> CommandFilterKey
key} -> CommandFilterKey
key) (\s :: CommandFilter
s@CommandFilter' {} CommandFilterKey
a -> CommandFilter
s {$sel:key:CommandFilter' :: CommandFilterKey
key = CommandFilterKey
a} :: CommandFilter)

-- | The filter value. Valid values for each filter key are as follows:
--
-- -   __InvokedAfter__: Specify a timestamp to limit your results. For
--     example, specify @2021-07-07T00:00:00Z@ to see a list of command
--     executions occurring July 7, 2021, and later.
--
-- -   __InvokedBefore__: Specify a timestamp to limit your results. For
--     example, specify @2021-07-07T00:00:00Z@ to see a list of command
--     executions from before July 7, 2021.
--
-- -   __Status__: Specify a valid command status to see a list of all
--     command executions with that status. The status choices depend on
--     the API you call.
--
--     The status values you can specify for @ListCommands@ are:
--
--     -   @Pending@
--
--     -   @InProgress@
--
--     -   @Success@
--
--     -   @Cancelled@
--
--     -   @Failed@
--
--     -   @TimedOut@ (this includes both Delivery and Execution time outs)
--
--     -   @AccessDenied@
--
--     -   @DeliveryTimedOut@
--
--     -   @ExecutionTimedOut@
--
--     -   @Incomplete@
--
--     -   @NoInstancesInTag@
--
--     -   @LimitExceeded@
--
--     The status values you can specify for @ListCommandInvocations@ are:
--
--     -   @Pending@
--
--     -   @InProgress@
--
--     -   @Delayed@
--
--     -   @Success@
--
--     -   @Cancelled@
--
--     -   @Failed@
--
--     -   @TimedOut@ (this includes both Delivery and Execution time outs)
--
--     -   @AccessDenied@
--
--     -   @DeliveryTimedOut@
--
--     -   @ExecutionTimedOut@
--
--     -   @Undeliverable@
--
--     -   @InvalidPlatform@
--
--     -   @Terminated@
--
-- -   __DocumentName__: Specify name of the Amazon Web Services Systems
--     Manager document (SSM document) for which you want to see command
--     execution results. For example, specify @AWS-RunPatchBaseline@ to
--     see command executions that used this SSM document to perform
--     security patching operations on managed nodes.
--
-- -   __ExecutionStage__: Specify one of the following values
--     (@ListCommands@ operations only):
--
--     -   @Executing@: Returns a list of command executions that are
--         currently still running.
--
--     -   @Complete@: Returns a list of command executions that have
--         already completed.
commandFilter_value :: Lens.Lens' CommandFilter Prelude.Text
commandFilter_value :: Lens' CommandFilter Text
commandFilter_value = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CommandFilter' {Text
value :: Text
$sel:value:CommandFilter' :: CommandFilter -> Text
value} -> Text
value) (\s :: CommandFilter
s@CommandFilter' {} Text
a -> CommandFilter
s {$sel:value:CommandFilter' :: Text
value = Text
a} :: CommandFilter)

instance Prelude.Hashable CommandFilter where
  hashWithSalt :: Int -> CommandFilter -> Int
hashWithSalt Int
_salt CommandFilter' {Text
CommandFilterKey
value :: Text
key :: CommandFilterKey
$sel:value:CommandFilter' :: CommandFilter -> Text
$sel:key:CommandFilter' :: CommandFilter -> CommandFilterKey
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CommandFilterKey
key
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
value

instance Prelude.NFData CommandFilter where
  rnf :: CommandFilter -> ()
rnf CommandFilter' {Text
CommandFilterKey
value :: Text
key :: CommandFilterKey
$sel:value:CommandFilter' :: CommandFilter -> Text
$sel:key:CommandFilter' :: CommandFilter -> CommandFilterKey
..} =
    forall a. NFData a => a -> ()
Prelude.rnf CommandFilterKey
key seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
value

instance Data.ToJSON CommandFilter where
  toJSON :: CommandFilter -> Value
toJSON CommandFilter' {Text
CommandFilterKey
value :: Text
key :: CommandFilterKey
$sel:value:CommandFilter' :: CommandFilter -> Text
$sel:key:CommandFilter' :: CommandFilter -> CommandFilterKey
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= CommandFilterKey
key),
            forall a. a -> Maybe a
Prelude.Just (Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
value)
          ]
      )