{-# 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.ResourceExplorer2.UpdateView
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies some of the details of a view. You can change the filter string
-- and the list of included properties. You can\'t change the name of the
-- view.
module Amazonka.ResourceExplorer2.UpdateView
  ( -- * Creating a Request
    UpdateView (..),
    newUpdateView,

    -- * Request Lenses
    updateView_filters,
    updateView_includedProperties,
    updateView_viewArn,

    -- * Destructuring the Response
    UpdateViewResponse (..),
    newUpdateViewResponse,

    -- * Response Lenses
    updateViewResponse_view,
    updateViewResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import Amazonka.ResourceExplorer2.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateView' smart constructor.
data UpdateView = UpdateView'
  { -- | An array of strings that specify which resources are included in the
    -- results of queries made using this view. When you use this view in a
    -- Search operation, the filter string is combined with the search\'s
    -- @QueryString@ parameter using a logical @AND@ operator.
    --
    -- For information about the supported syntax, see
    -- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html Search query reference for Resource Explorer>
    -- in the /Amazon Web Services Resource Explorer User Guide/.
    --
    -- This query string in the context of this operation supports only
    -- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-filters filter prefixes>
    -- with optional
    -- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-operators operators>.
    -- It doesn\'t support free-form text. For example, the string
    -- @region:us* service:ec2 -tag:stage=prod@ includes all Amazon EC2
    -- resources in any Amazon Web Services Region that begins with the letters
    -- @us@ and is /not/ tagged with a key @Stage@ that has the value @prod@.
    UpdateView -> Maybe (Sensitive SearchFilter)
filters :: Prelude.Maybe (Data.Sensitive SearchFilter),
    -- | Specifies optional fields that you want included in search results from
    -- this view. It is a list of objects that each describe a field to
    -- include.
    --
    -- The default is an empty list, with no optional fields included in the
    -- results.
    UpdateView -> Maybe [IncludedProperty]
includedProperties :: Prelude.Maybe [IncludedProperty],
    -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
    -- of the view that you want to modify.
    UpdateView -> Text
viewArn :: Prelude.Text
  }
  deriving (UpdateView -> UpdateView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateView -> UpdateView -> Bool
$c/= :: UpdateView -> UpdateView -> Bool
== :: UpdateView -> UpdateView -> Bool
$c== :: UpdateView -> UpdateView -> Bool
Prelude.Eq, Int -> UpdateView -> ShowS
[UpdateView] -> ShowS
UpdateView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateView] -> ShowS
$cshowList :: [UpdateView] -> ShowS
show :: UpdateView -> String
$cshow :: UpdateView -> String
showsPrec :: Int -> UpdateView -> ShowS
$cshowsPrec :: Int -> UpdateView -> ShowS
Prelude.Show, forall x. Rep UpdateView x -> UpdateView
forall x. UpdateView -> Rep UpdateView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateView x -> UpdateView
$cfrom :: forall x. UpdateView -> Rep UpdateView x
Prelude.Generic)

-- |
-- Create a value of 'UpdateView' 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:
--
-- 'filters', 'updateView_filters' - An array of strings that specify which resources are included in the
-- results of queries made using this view. When you use this view in a
-- Search operation, the filter string is combined with the search\'s
-- @QueryString@ parameter using a logical @AND@ operator.
--
-- For information about the supported syntax, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html Search query reference for Resource Explorer>
-- in the /Amazon Web Services Resource Explorer User Guide/.
--
-- This query string in the context of this operation supports only
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-filters filter prefixes>
-- with optional
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-operators operators>.
-- It doesn\'t support free-form text. For example, the string
-- @region:us* service:ec2 -tag:stage=prod@ includes all Amazon EC2
-- resources in any Amazon Web Services Region that begins with the letters
-- @us@ and is /not/ tagged with a key @Stage@ that has the value @prod@.
--
-- 'includedProperties', 'updateView_includedProperties' - Specifies optional fields that you want included in search results from
-- this view. It is a list of objects that each describe a field to
-- include.
--
-- The default is an empty list, with no optional fields included in the
-- results.
--
-- 'viewArn', 'updateView_viewArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view that you want to modify.
newUpdateView ::
  -- | 'viewArn'
  Prelude.Text ->
  UpdateView
newUpdateView :: Text -> UpdateView
newUpdateView Text
pViewArn_ =
  UpdateView'
    { $sel:filters:UpdateView' :: Maybe (Sensitive SearchFilter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:includedProperties:UpdateView' :: Maybe [IncludedProperty]
includedProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:viewArn:UpdateView' :: Text
viewArn = Text
pViewArn_
    }

-- | An array of strings that specify which resources are included in the
-- results of queries made using this view. When you use this view in a
-- Search operation, the filter string is combined with the search\'s
-- @QueryString@ parameter using a logical @AND@ operator.
--
-- For information about the supported syntax, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html Search query reference for Resource Explorer>
-- in the /Amazon Web Services Resource Explorer User Guide/.
--
-- This query string in the context of this operation supports only
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-filters filter prefixes>
-- with optional
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/using-search-query-syntax.html#query-syntax-operators operators>.
-- It doesn\'t support free-form text. For example, the string
-- @region:us* service:ec2 -tag:stage=prod@ includes all Amazon EC2
-- resources in any Amazon Web Services Region that begins with the letters
-- @us@ and is /not/ tagged with a key @Stage@ that has the value @prod@.
updateView_filters :: Lens.Lens' UpdateView (Prelude.Maybe SearchFilter)
updateView_filters :: Lens' UpdateView (Maybe SearchFilter)
updateView_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateView' {Maybe (Sensitive SearchFilter)
filters :: Maybe (Sensitive SearchFilter)
$sel:filters:UpdateView' :: UpdateView -> Maybe (Sensitive SearchFilter)
filters} -> Maybe (Sensitive SearchFilter)
filters) (\s :: UpdateView
s@UpdateView' {} Maybe (Sensitive SearchFilter)
a -> UpdateView
s {$sel:filters:UpdateView' :: Maybe (Sensitive SearchFilter)
filters = Maybe (Sensitive SearchFilter)
a} :: UpdateView) 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

-- | Specifies optional fields that you want included in search results from
-- this view. It is a list of objects that each describe a field to
-- include.
--
-- The default is an empty list, with no optional fields included in the
-- results.
updateView_includedProperties :: Lens.Lens' UpdateView (Prelude.Maybe [IncludedProperty])
updateView_includedProperties :: Lens' UpdateView (Maybe [IncludedProperty])
updateView_includedProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateView' {Maybe [IncludedProperty]
includedProperties :: Maybe [IncludedProperty]
$sel:includedProperties:UpdateView' :: UpdateView -> Maybe [IncludedProperty]
includedProperties} -> Maybe [IncludedProperty]
includedProperties) (\s :: UpdateView
s@UpdateView' {} Maybe [IncludedProperty]
a -> UpdateView
s {$sel:includedProperties:UpdateView' :: Maybe [IncludedProperty]
includedProperties = Maybe [IncludedProperty]
a} :: UpdateView) 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
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view that you want to modify.
updateView_viewArn :: Lens.Lens' UpdateView Prelude.Text
updateView_viewArn :: Lens' UpdateView Text
updateView_viewArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateView' {Text
viewArn :: Text
$sel:viewArn:UpdateView' :: UpdateView -> Text
viewArn} -> Text
viewArn) (\s :: UpdateView
s@UpdateView' {} Text
a -> UpdateView
s {$sel:viewArn:UpdateView' :: Text
viewArn = Text
a} :: UpdateView)

instance Core.AWSRequest UpdateView where
  type AWSResponse UpdateView = UpdateViewResponse
  request :: (Service -> Service) -> UpdateView -> Request UpdateView
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 UpdateView
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateView)))
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 View -> Int -> UpdateViewResponse
UpdateViewResponse'
            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
"View")
            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 UpdateView where
  hashWithSalt :: Int -> UpdateView -> Int
hashWithSalt Int
_salt UpdateView' {Maybe [IncludedProperty]
Maybe (Sensitive SearchFilter)
Text
viewArn :: Text
includedProperties :: Maybe [IncludedProperty]
filters :: Maybe (Sensitive SearchFilter)
$sel:viewArn:UpdateView' :: UpdateView -> Text
$sel:includedProperties:UpdateView' :: UpdateView -> Maybe [IncludedProperty]
$sel:filters:UpdateView' :: UpdateView -> Maybe (Sensitive SearchFilter)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive SearchFilter)
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [IncludedProperty]
includedProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
viewArn

instance Prelude.NFData UpdateView where
  rnf :: UpdateView -> ()
rnf UpdateView' {Maybe [IncludedProperty]
Maybe (Sensitive SearchFilter)
Text
viewArn :: Text
includedProperties :: Maybe [IncludedProperty]
filters :: Maybe (Sensitive SearchFilter)
$sel:viewArn:UpdateView' :: UpdateView -> Text
$sel:includedProperties:UpdateView' :: UpdateView -> Maybe [IncludedProperty]
$sel:filters:UpdateView' :: UpdateView -> Maybe (Sensitive SearchFilter)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive SearchFilter)
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [IncludedProperty]
includedProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
viewArn

instance Data.ToHeaders UpdateView where
  toHeaders :: UpdateView -> 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 UpdateView where
  toJSON :: UpdateView -> Value
toJSON UpdateView' {Maybe [IncludedProperty]
Maybe (Sensitive SearchFilter)
Text
viewArn :: Text
includedProperties :: Maybe [IncludedProperty]
filters :: Maybe (Sensitive SearchFilter)
$sel:viewArn:UpdateView' :: UpdateView -> Text
$sel:includedProperties:UpdateView' :: UpdateView -> Maybe [IncludedProperty]
$sel:filters:UpdateView' :: UpdateView -> Maybe (Sensitive SearchFilter)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 (Sensitive SearchFilter)
filters,
            (Key
"IncludedProperties" 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 [IncludedProperty]
includedProperties,
            forall a. a -> Maybe a
Prelude.Just (Key
"ViewArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
viewArn)
          ]
      )

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

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

-- | /See:/ 'newUpdateViewResponse' smart constructor.
data UpdateViewResponse = UpdateViewResponse'
  { -- | Details about the view that you changed with this operation.
    UpdateViewResponse -> Maybe View
view :: Prelude.Maybe View,
    -- | The response's http status code.
    UpdateViewResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateViewResponse -> UpdateViewResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateViewResponse -> UpdateViewResponse -> Bool
$c/= :: UpdateViewResponse -> UpdateViewResponse -> Bool
== :: UpdateViewResponse -> UpdateViewResponse -> Bool
$c== :: UpdateViewResponse -> UpdateViewResponse -> Bool
Prelude.Eq, Int -> UpdateViewResponse -> ShowS
[UpdateViewResponse] -> ShowS
UpdateViewResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateViewResponse] -> ShowS
$cshowList :: [UpdateViewResponse] -> ShowS
show :: UpdateViewResponse -> String
$cshow :: UpdateViewResponse -> String
showsPrec :: Int -> UpdateViewResponse -> ShowS
$cshowsPrec :: Int -> UpdateViewResponse -> ShowS
Prelude.Show, forall x. Rep UpdateViewResponse x -> UpdateViewResponse
forall x. UpdateViewResponse -> Rep UpdateViewResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateViewResponse x -> UpdateViewResponse
$cfrom :: forall x. UpdateViewResponse -> Rep UpdateViewResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateViewResponse' 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:
--
-- 'view', 'updateViewResponse_view' - Details about the view that you changed with this operation.
--
-- 'httpStatus', 'updateViewResponse_httpStatus' - The response's http status code.
newUpdateViewResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateViewResponse
newUpdateViewResponse :: Int -> UpdateViewResponse
newUpdateViewResponse Int
pHttpStatus_ =
  UpdateViewResponse'
    { $sel:view:UpdateViewResponse' :: Maybe View
view = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateViewResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about the view that you changed with this operation.
updateViewResponse_view :: Lens.Lens' UpdateViewResponse (Prelude.Maybe View)
updateViewResponse_view :: Lens' UpdateViewResponse (Maybe View)
updateViewResponse_view = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateViewResponse' {Maybe View
view :: Maybe View
$sel:view:UpdateViewResponse' :: UpdateViewResponse -> Maybe View
view} -> Maybe View
view) (\s :: UpdateViewResponse
s@UpdateViewResponse' {} Maybe View
a -> UpdateViewResponse
s {$sel:view:UpdateViewResponse' :: Maybe View
view = Maybe View
a} :: UpdateViewResponse)

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

instance Prelude.NFData UpdateViewResponse where
  rnf :: UpdateViewResponse -> ()
rnf UpdateViewResponse' {Int
Maybe View
httpStatus :: Int
view :: Maybe View
$sel:httpStatus:UpdateViewResponse' :: UpdateViewResponse -> Int
$sel:view:UpdateViewResponse' :: UpdateViewResponse -> Maybe View
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe View
view
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus