{-# 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.CreateView
-- 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 view that users can query by using the Search operation.
-- Results from queries that you make using this view include only
-- resources that match the view\'s @Filters@. For more information about
-- Amazon Web Services Resource Explorer views, see
-- <https://docs.aws.amazon.com/resource-explorer/latest/userguide/manage-views.html Managing views>
-- in the /Amazon Web Services Resource Explorer User Guide/.
--
-- Only the principals with an IAM identity-based policy that grants
-- @Allow@ to the @Search@ action on a @Resource@ with the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of this view can Search using views you create with this operation.
module Amazonka.ResourceExplorer2.CreateView
  ( -- * Creating a Request
    CreateView (..),
    newCreateView,

    -- * Request Lenses
    createView_clientToken,
    createView_filters,
    createView_includedProperties,
    createView_tags,
    createView_viewName,

    -- * Destructuring the Response
    CreateViewResponse (..),
    newCreateViewResponse,

    -- * Response Lenses
    createViewResponse_view,
    createViewResponse_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:/ 'newCreateView' smart constructor.
data CreateView = CreateView'
  { -- | This value helps ensure idempotency. Resource Explorer uses this value
    -- to prevent the accidental creation of duplicate versions. We recommend
    -- that you generate a
    -- <https://wikipedia.org/wiki/Universally_unique_identifier UUID-type value>
    -- to ensure the uniqueness of your views.
    CreateView -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    CreateView -> 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.
    CreateView -> Maybe [IncludedProperty]
includedProperties :: Prelude.Maybe [IncludedProperty],
    -- | Tag key and value pairs that are attached to the view.
    CreateView -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the new view. This name appears in the list of views in
    -- Resource Explorer.
    --
    -- The name must be no more than 64 characters long, and can include
    -- letters, digits, and the dash (-) character. The name must be unique
    -- within its Amazon Web Services Region.
    CreateView -> Text
viewName :: Prelude.Text
  }
  deriving (CreateView -> CreateView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateView -> CreateView -> Bool
$c/= :: CreateView -> CreateView -> Bool
== :: CreateView -> CreateView -> Bool
$c== :: CreateView -> CreateView -> Bool
Prelude.Eq, Int -> CreateView -> ShowS
[CreateView] -> ShowS
CreateView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateView] -> ShowS
$cshowList :: [CreateView] -> ShowS
show :: CreateView -> String
$cshow :: CreateView -> String
showsPrec :: Int -> CreateView -> ShowS
$cshowsPrec :: Int -> CreateView -> ShowS
Prelude.Show, forall x. Rep CreateView x -> CreateView
forall x. CreateView -> Rep CreateView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateView x -> CreateView
$cfrom :: forall x. CreateView -> Rep CreateView x
Prelude.Generic)

-- |
-- Create a value of 'CreateView' 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:
--
-- 'clientToken', 'createView_clientToken' - This value helps ensure idempotency. Resource Explorer uses this value
-- to prevent the accidental creation of duplicate versions. We recommend
-- that you generate a
-- <https://wikipedia.org/wiki/Universally_unique_identifier UUID-type value>
-- to ensure the uniqueness of your views.
--
-- 'filters', 'createView_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', 'createView_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.
--
-- 'tags', 'createView_tags' - Tag key and value pairs that are attached to the view.
--
-- 'viewName', 'createView_viewName' - The name of the new view. This name appears in the list of views in
-- Resource Explorer.
--
-- The name must be no more than 64 characters long, and can include
-- letters, digits, and the dash (-) character. The name must be unique
-- within its Amazon Web Services Region.
newCreateView ::
  -- | 'viewName'
  Prelude.Text ->
  CreateView
newCreateView :: Text -> CreateView
newCreateView Text
pViewName_ =
  CreateView'
    { $sel:clientToken:CreateView' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:CreateView' :: Maybe (Sensitive SearchFilter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:includedProperties:CreateView' :: Maybe [IncludedProperty]
includedProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateView' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:viewName:CreateView' :: Text
viewName = Text
pViewName_
    }

-- | This value helps ensure idempotency. Resource Explorer uses this value
-- to prevent the accidental creation of duplicate versions. We recommend
-- that you generate a
-- <https://wikipedia.org/wiki/Universally_unique_identifier UUID-type value>
-- to ensure the uniqueness of your views.
createView_clientToken :: Lens.Lens' CreateView (Prelude.Maybe Prelude.Text)
createView_clientToken :: Lens' CreateView (Maybe Text)
createView_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateView' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateView' :: CreateView -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateView
s@CreateView' {} Maybe Text
a -> CreateView
s {$sel:clientToken:CreateView' :: Maybe Text
clientToken = Maybe Text
a} :: CreateView)

-- | 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@.
createView_filters :: Lens.Lens' CreateView (Prelude.Maybe SearchFilter)
createView_filters :: Lens' CreateView (Maybe SearchFilter)
createView_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateView' {Maybe (Sensitive SearchFilter)
filters :: Maybe (Sensitive SearchFilter)
$sel:filters:CreateView' :: CreateView -> Maybe (Sensitive SearchFilter)
filters} -> Maybe (Sensitive SearchFilter)
filters) (\s :: CreateView
s@CreateView' {} Maybe (Sensitive SearchFilter)
a -> CreateView
s {$sel:filters:CreateView' :: Maybe (Sensitive SearchFilter)
filters = Maybe (Sensitive SearchFilter)
a} :: CreateView) 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.
createView_includedProperties :: Lens.Lens' CreateView (Prelude.Maybe [IncludedProperty])
createView_includedProperties :: Lens' CreateView (Maybe [IncludedProperty])
createView_includedProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateView' {Maybe [IncludedProperty]
includedProperties :: Maybe [IncludedProperty]
$sel:includedProperties:CreateView' :: CreateView -> Maybe [IncludedProperty]
includedProperties} -> Maybe [IncludedProperty]
includedProperties) (\s :: CreateView
s@CreateView' {} Maybe [IncludedProperty]
a -> CreateView
s {$sel:includedProperties:CreateView' :: Maybe [IncludedProperty]
includedProperties = Maybe [IncludedProperty]
a} :: CreateView) 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

-- | Tag key and value pairs that are attached to the view.
createView_tags :: Lens.Lens' CreateView (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createView_tags :: Lens' CreateView (Maybe (HashMap Text Text))
createView_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateView' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateView' :: CreateView -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateView
s@CreateView' {} Maybe (HashMap Text Text)
a -> CreateView
s {$sel:tags:CreateView' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateView) 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 name of the new view. This name appears in the list of views in
-- Resource Explorer.
--
-- The name must be no more than 64 characters long, and can include
-- letters, digits, and the dash (-) character. The name must be unique
-- within its Amazon Web Services Region.
createView_viewName :: Lens.Lens' CreateView Prelude.Text
createView_viewName :: Lens' CreateView Text
createView_viewName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateView' {Text
viewName :: Text
$sel:viewName:CreateView' :: CreateView -> Text
viewName} -> Text
viewName) (\s :: CreateView
s@CreateView' {} Text
a -> CreateView
s {$sel:viewName:CreateView' :: Text
viewName = Text
a} :: CreateView)

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

instance Prelude.NFData CreateView where
  rnf :: CreateView -> ()
rnf CreateView' {Maybe [IncludedProperty]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive SearchFilter)
Text
viewName :: Text
tags :: Maybe (HashMap Text Text)
includedProperties :: Maybe [IncludedProperty]
filters :: Maybe (Sensitive SearchFilter)
clientToken :: Maybe Text
$sel:viewName:CreateView' :: CreateView -> Text
$sel:tags:CreateView' :: CreateView -> Maybe (HashMap Text Text)
$sel:includedProperties:CreateView' :: CreateView -> Maybe [IncludedProperty]
$sel:filters:CreateView' :: CreateView -> Maybe (Sensitive SearchFilter)
$sel:clientToken:CreateView' :: CreateView -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
viewName

instance Data.ToHeaders CreateView where
  toHeaders :: CreateView -> 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 CreateView where
  toJSON :: CreateView -> Value
toJSON CreateView' {Maybe [IncludedProperty]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive SearchFilter)
Text
viewName :: Text
tags :: Maybe (HashMap Text Text)
includedProperties :: Maybe [IncludedProperty]
filters :: Maybe (Sensitive SearchFilter)
clientToken :: Maybe Text
$sel:viewName:CreateView' :: CreateView -> Text
$sel:tags:CreateView' :: CreateView -> Maybe (HashMap Text Text)
$sel:includedProperties:CreateView' :: CreateView -> Maybe [IncludedProperty]
$sel:filters:CreateView' :: CreateView -> Maybe (Sensitive SearchFilter)
$sel:clientToken:CreateView' :: CreateView -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientToken" 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
clientToken,
            (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,
            (Key
"Tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"ViewName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
viewName)
          ]
      )

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

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

-- | /See:/ 'newCreateViewResponse' smart constructor.
data CreateViewResponse = CreateViewResponse'
  { -- | A structure that contains the details about the new view.
    CreateViewResponse -> Maybe View
view :: Prelude.Maybe View,
    -- | The response's http status code.
    CreateViewResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateViewResponse -> CreateViewResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateViewResponse -> CreateViewResponse -> Bool
$c/= :: CreateViewResponse -> CreateViewResponse -> Bool
== :: CreateViewResponse -> CreateViewResponse -> Bool
$c== :: CreateViewResponse -> CreateViewResponse -> Bool
Prelude.Eq, Int -> CreateViewResponse -> ShowS
[CreateViewResponse] -> ShowS
CreateViewResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateViewResponse] -> ShowS
$cshowList :: [CreateViewResponse] -> ShowS
show :: CreateViewResponse -> String
$cshow :: CreateViewResponse -> String
showsPrec :: Int -> CreateViewResponse -> ShowS
$cshowsPrec :: Int -> CreateViewResponse -> ShowS
Prelude.Show, forall x. Rep CreateViewResponse x -> CreateViewResponse
forall x. CreateViewResponse -> Rep CreateViewResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateViewResponse x -> CreateViewResponse
$cfrom :: forall x. CreateViewResponse -> Rep CreateViewResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateViewResponse' 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', 'createViewResponse_view' - A structure that contains the details about the new view.
--
-- 'httpStatus', 'createViewResponse_httpStatus' - The response's http status code.
newCreateViewResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateViewResponse
newCreateViewResponse :: Int -> CreateViewResponse
newCreateViewResponse Int
pHttpStatus_ =
  CreateViewResponse'
    { $sel:view:CreateViewResponse' :: Maybe View
view = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateViewResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A structure that contains the details about the new view.
createViewResponse_view :: Lens.Lens' CreateViewResponse (Prelude.Maybe View)
createViewResponse_view :: Lens' CreateViewResponse (Maybe View)
createViewResponse_view = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateViewResponse' {Maybe View
view :: Maybe View
$sel:view:CreateViewResponse' :: CreateViewResponse -> Maybe View
view} -> Maybe View
view) (\s :: CreateViewResponse
s@CreateViewResponse' {} Maybe View
a -> CreateViewResponse
s {$sel:view:CreateViewResponse' :: Maybe View
view = Maybe View
a} :: CreateViewResponse)

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

instance Prelude.NFData CreateViewResponse where
  rnf :: CreateViewResponse -> ()
rnf CreateViewResponse' {Int
Maybe View
httpStatus :: Int
view :: Maybe View
$sel:httpStatus:CreateViewResponse' :: CreateViewResponse -> Int
$sel:view:CreateViewResponse' :: CreateViewResponse -> 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