{-# 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.SageMaker.Types.NestedFilters
-- 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.SageMaker.Types.NestedFilters 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.SageMaker.Types.Filter

-- | A list of nested Filter objects. A resource must satisfy the conditions
-- of all filters to be included in the results returned from the Search
-- API.
--
-- For example, to filter on a training job\'s @InputDataConfig@ property
-- with a specific channel name and @S3Uri@ prefix, define the following
-- filters:
--
-- -   @\'{Name:\"InputDataConfig.ChannelName\", \"Operator\":\"Equals\", \"Value\":\"train\"}\',@
--
-- -   @\'{Name:\"InputDataConfig.DataSource.S3DataSource.S3Uri\", \"Operator\":\"Contains\", \"Value\":\"mybucket\/catdata\"}\'@
--
-- /See:/ 'newNestedFilters' smart constructor.
data NestedFilters = NestedFilters'
  { -- | The name of the property to use in the nested filters. The value must
    -- match a listed property name, such as @InputDataConfig@.
    NestedFilters -> Text
nestedPropertyName :: Prelude.Text,
    -- | A list of filters. Each filter acts on a property. Filters must contain
    -- at least one @Filters@ value. For example, a @NestedFilters@ call might
    -- include a filter on the @PropertyName@ parameter of the
    -- @InputDataConfig@ property:
    -- @InputDataConfig.DataSource.S3DataSource.S3Uri@.
    NestedFilters -> NonEmpty Filter
filters :: Prelude.NonEmpty Filter
  }
  deriving (NestedFilters -> NestedFilters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NestedFilters -> NestedFilters -> Bool
$c/= :: NestedFilters -> NestedFilters -> Bool
== :: NestedFilters -> NestedFilters -> Bool
$c== :: NestedFilters -> NestedFilters -> Bool
Prelude.Eq, ReadPrec [NestedFilters]
ReadPrec NestedFilters
Int -> ReadS NestedFilters
ReadS [NestedFilters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NestedFilters]
$creadListPrec :: ReadPrec [NestedFilters]
readPrec :: ReadPrec NestedFilters
$creadPrec :: ReadPrec NestedFilters
readList :: ReadS [NestedFilters]
$creadList :: ReadS [NestedFilters]
readsPrec :: Int -> ReadS NestedFilters
$creadsPrec :: Int -> ReadS NestedFilters
Prelude.Read, Int -> NestedFilters -> ShowS
[NestedFilters] -> ShowS
NestedFilters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NestedFilters] -> ShowS
$cshowList :: [NestedFilters] -> ShowS
show :: NestedFilters -> String
$cshow :: NestedFilters -> String
showsPrec :: Int -> NestedFilters -> ShowS
$cshowsPrec :: Int -> NestedFilters -> ShowS
Prelude.Show, forall x. Rep NestedFilters x -> NestedFilters
forall x. NestedFilters -> Rep NestedFilters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NestedFilters x -> NestedFilters
$cfrom :: forall x. NestedFilters -> Rep NestedFilters x
Prelude.Generic)

-- |
-- Create a value of 'NestedFilters' 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:
--
-- 'nestedPropertyName', 'nestedFilters_nestedPropertyName' - The name of the property to use in the nested filters. The value must
-- match a listed property name, such as @InputDataConfig@.
--
-- 'filters', 'nestedFilters_filters' - A list of filters. Each filter acts on a property. Filters must contain
-- at least one @Filters@ value. For example, a @NestedFilters@ call might
-- include a filter on the @PropertyName@ parameter of the
-- @InputDataConfig@ property:
-- @InputDataConfig.DataSource.S3DataSource.S3Uri@.
newNestedFilters ::
  -- | 'nestedPropertyName'
  Prelude.Text ->
  -- | 'filters'
  Prelude.NonEmpty Filter ->
  NestedFilters
newNestedFilters :: Text -> NonEmpty Filter -> NestedFilters
newNestedFilters Text
pNestedPropertyName_ NonEmpty Filter
pFilters_ =
  NestedFilters'
    { $sel:nestedPropertyName:NestedFilters' :: Text
nestedPropertyName =
        Text
pNestedPropertyName_,
      $sel:filters:NestedFilters' :: NonEmpty Filter
filters = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Filter
pFilters_
    }

-- | The name of the property to use in the nested filters. The value must
-- match a listed property name, such as @InputDataConfig@.
nestedFilters_nestedPropertyName :: Lens.Lens' NestedFilters Prelude.Text
nestedFilters_nestedPropertyName :: Lens' NestedFilters Text
nestedFilters_nestedPropertyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NestedFilters' {Text
nestedPropertyName :: Text
$sel:nestedPropertyName:NestedFilters' :: NestedFilters -> Text
nestedPropertyName} -> Text
nestedPropertyName) (\s :: NestedFilters
s@NestedFilters' {} Text
a -> NestedFilters
s {$sel:nestedPropertyName:NestedFilters' :: Text
nestedPropertyName = Text
a} :: NestedFilters)

-- | A list of filters. Each filter acts on a property. Filters must contain
-- at least one @Filters@ value. For example, a @NestedFilters@ call might
-- include a filter on the @PropertyName@ parameter of the
-- @InputDataConfig@ property:
-- @InputDataConfig.DataSource.S3DataSource.S3Uri@.
nestedFilters_filters :: Lens.Lens' NestedFilters (Prelude.NonEmpty Filter)
nestedFilters_filters :: Lens' NestedFilters (NonEmpty Filter)
nestedFilters_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NestedFilters' {NonEmpty Filter
filters :: NonEmpty Filter
$sel:filters:NestedFilters' :: NestedFilters -> NonEmpty Filter
filters} -> NonEmpty Filter
filters) (\s :: NestedFilters
s@NestedFilters' {} NonEmpty Filter
a -> NestedFilters
s {$sel:filters:NestedFilters' :: NonEmpty Filter
filters = NonEmpty Filter
a} :: NestedFilters) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.Hashable NestedFilters where
  hashWithSalt :: Int -> NestedFilters -> Int
hashWithSalt Int
_salt NestedFilters' {NonEmpty Filter
Text
filters :: NonEmpty Filter
nestedPropertyName :: Text
$sel:filters:NestedFilters' :: NestedFilters -> NonEmpty Filter
$sel:nestedPropertyName:NestedFilters' :: NestedFilters -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
nestedPropertyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Filter
filters

instance Prelude.NFData NestedFilters where
  rnf :: NestedFilters -> ()
rnf NestedFilters' {NonEmpty Filter
Text
filters :: NonEmpty Filter
nestedPropertyName :: Text
$sel:filters:NestedFilters' :: NestedFilters -> NonEmpty Filter
$sel:nestedPropertyName:NestedFilters' :: NestedFilters -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
nestedPropertyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Filter
filters

instance Data.ToJSON NestedFilters where
  toJSON :: NestedFilters -> Value
toJSON NestedFilters' {NonEmpty Filter
Text
filters :: NonEmpty Filter
nestedPropertyName :: Text
$sel:filters:NestedFilters' :: NestedFilters -> NonEmpty Filter
$sel:nestedPropertyName:NestedFilters' :: NestedFilters -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"NestedPropertyName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
nestedPropertyName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Filter
filters)
          ]
      )