{-# 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.AssociateDefaultView
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets the specified view as the default for the Amazon Web Services
-- Region in which you call this operation. When a user performs a Search
-- that doesn\'t explicitly specify which view to use, then Amazon Web
-- Services Resource Explorer automatically chooses this default view for
-- searches performed in this Amazon Web Services Region.
--
-- If an Amazon Web Services Region doesn\'t have a default view
-- configured, then users must explicitly specify a view with every
-- @Search@ operation performed in that Region.
module Amazonka.ResourceExplorer2.AssociateDefaultView
  ( -- * Creating a Request
    AssociateDefaultView (..),
    newAssociateDefaultView,

    -- * Request Lenses
    associateDefaultView_viewArn,

    -- * Destructuring the Response
    AssociateDefaultViewResponse (..),
    newAssociateDefaultViewResponse,

    -- * Response Lenses
    associateDefaultViewResponse_viewArn,
    associateDefaultViewResponse_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:/ 'newAssociateDefaultView' smart constructor.
data AssociateDefaultView = AssociateDefaultView'
  { -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
    -- of the view to set as the default for the Amazon Web Services Region and
    -- Amazon Web Services account in which you call this operation. The
    -- specified view must already exist in the called Region.
    AssociateDefaultView -> Text
viewArn :: Prelude.Text
  }
  deriving (AssociateDefaultView -> AssociateDefaultView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateDefaultView -> AssociateDefaultView -> Bool
$c/= :: AssociateDefaultView -> AssociateDefaultView -> Bool
== :: AssociateDefaultView -> AssociateDefaultView -> Bool
$c== :: AssociateDefaultView -> AssociateDefaultView -> Bool
Prelude.Eq, ReadPrec [AssociateDefaultView]
ReadPrec AssociateDefaultView
Int -> ReadS AssociateDefaultView
ReadS [AssociateDefaultView]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateDefaultView]
$creadListPrec :: ReadPrec [AssociateDefaultView]
readPrec :: ReadPrec AssociateDefaultView
$creadPrec :: ReadPrec AssociateDefaultView
readList :: ReadS [AssociateDefaultView]
$creadList :: ReadS [AssociateDefaultView]
readsPrec :: Int -> ReadS AssociateDefaultView
$creadsPrec :: Int -> ReadS AssociateDefaultView
Prelude.Read, Int -> AssociateDefaultView -> ShowS
[AssociateDefaultView] -> ShowS
AssociateDefaultView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateDefaultView] -> ShowS
$cshowList :: [AssociateDefaultView] -> ShowS
show :: AssociateDefaultView -> String
$cshow :: AssociateDefaultView -> String
showsPrec :: Int -> AssociateDefaultView -> ShowS
$cshowsPrec :: Int -> AssociateDefaultView -> ShowS
Prelude.Show, forall x. Rep AssociateDefaultView x -> AssociateDefaultView
forall x. AssociateDefaultView -> Rep AssociateDefaultView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateDefaultView x -> AssociateDefaultView
$cfrom :: forall x. AssociateDefaultView -> Rep AssociateDefaultView x
Prelude.Generic)

-- |
-- Create a value of 'AssociateDefaultView' 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:
--
-- 'viewArn', 'associateDefaultView_viewArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view to set as the default for the Amazon Web Services Region and
-- Amazon Web Services account in which you call this operation. The
-- specified view must already exist in the called Region.
newAssociateDefaultView ::
  -- | 'viewArn'
  Prelude.Text ->
  AssociateDefaultView
newAssociateDefaultView :: Text -> AssociateDefaultView
newAssociateDefaultView Text
pViewArn_ =
  AssociateDefaultView' {$sel:viewArn:AssociateDefaultView' :: Text
viewArn = Text
pViewArn_}

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view to set as the default for the Amazon Web Services Region and
-- Amazon Web Services account in which you call this operation. The
-- specified view must already exist in the called Region.
associateDefaultView_viewArn :: Lens.Lens' AssociateDefaultView Prelude.Text
associateDefaultView_viewArn :: Lens' AssociateDefaultView Text
associateDefaultView_viewArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateDefaultView' {Text
viewArn :: Text
$sel:viewArn:AssociateDefaultView' :: AssociateDefaultView -> Text
viewArn} -> Text
viewArn) (\s :: AssociateDefaultView
s@AssociateDefaultView' {} Text
a -> AssociateDefaultView
s {$sel:viewArn:AssociateDefaultView' :: Text
viewArn = Text
a} :: AssociateDefaultView)

instance Core.AWSRequest AssociateDefaultView where
  type
    AWSResponse AssociateDefaultView =
      AssociateDefaultViewResponse
  request :: (Service -> Service)
-> AssociateDefaultView -> Request AssociateDefaultView
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 AssociateDefaultView
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateDefaultView)))
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 Text -> Int -> AssociateDefaultViewResponse
AssociateDefaultViewResponse'
            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
"ViewArn")
            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 AssociateDefaultView where
  hashWithSalt :: Int -> AssociateDefaultView -> Int
hashWithSalt Int
_salt AssociateDefaultView' {Text
viewArn :: Text
$sel:viewArn:AssociateDefaultView' :: AssociateDefaultView -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
viewArn

instance Prelude.NFData AssociateDefaultView where
  rnf :: AssociateDefaultView -> ()
rnf AssociateDefaultView' {Text
viewArn :: Text
$sel:viewArn:AssociateDefaultView' :: AssociateDefaultView -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
viewArn

instance Data.ToHeaders AssociateDefaultView where
  toHeaders :: AssociateDefaultView -> 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 AssociateDefaultView where
  toJSON :: AssociateDefaultView -> Value
toJSON AssociateDefaultView' {Text
viewArn :: Text
$sel:viewArn:AssociateDefaultView' :: AssociateDefaultView -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [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 AssociateDefaultView where
  toPath :: AssociateDefaultView -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/AssociateDefaultView"

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

-- | /See:/ 'newAssociateDefaultViewResponse' smart constructor.
data AssociateDefaultViewResponse = AssociateDefaultViewResponse'
  { -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
    -- of the view that the operation set as the default for queries made in
    -- the Amazon Web Services Region and Amazon Web Services account in which
    -- you called this operation.
    AssociateDefaultViewResponse -> Maybe Text
viewArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AssociateDefaultViewResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AssociateDefaultViewResponse
-> AssociateDefaultViewResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateDefaultViewResponse
-> AssociateDefaultViewResponse -> Bool
$c/= :: AssociateDefaultViewResponse
-> AssociateDefaultViewResponse -> Bool
== :: AssociateDefaultViewResponse
-> AssociateDefaultViewResponse -> Bool
$c== :: AssociateDefaultViewResponse
-> AssociateDefaultViewResponse -> Bool
Prelude.Eq, ReadPrec [AssociateDefaultViewResponse]
ReadPrec AssociateDefaultViewResponse
Int -> ReadS AssociateDefaultViewResponse
ReadS [AssociateDefaultViewResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateDefaultViewResponse]
$creadListPrec :: ReadPrec [AssociateDefaultViewResponse]
readPrec :: ReadPrec AssociateDefaultViewResponse
$creadPrec :: ReadPrec AssociateDefaultViewResponse
readList :: ReadS [AssociateDefaultViewResponse]
$creadList :: ReadS [AssociateDefaultViewResponse]
readsPrec :: Int -> ReadS AssociateDefaultViewResponse
$creadsPrec :: Int -> ReadS AssociateDefaultViewResponse
Prelude.Read, Int -> AssociateDefaultViewResponse -> ShowS
[AssociateDefaultViewResponse] -> ShowS
AssociateDefaultViewResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateDefaultViewResponse] -> ShowS
$cshowList :: [AssociateDefaultViewResponse] -> ShowS
show :: AssociateDefaultViewResponse -> String
$cshow :: AssociateDefaultViewResponse -> String
showsPrec :: Int -> AssociateDefaultViewResponse -> ShowS
$cshowsPrec :: Int -> AssociateDefaultViewResponse -> ShowS
Prelude.Show, forall x.
Rep AssociateDefaultViewResponse x -> AssociateDefaultViewResponse
forall x.
AssociateDefaultViewResponse -> Rep AssociateDefaultViewResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateDefaultViewResponse x -> AssociateDefaultViewResponse
$cfrom :: forall x.
AssociateDefaultViewResponse -> Rep AssociateDefaultViewResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssociateDefaultViewResponse' 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:
--
-- 'viewArn', 'associateDefaultViewResponse_viewArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view that the operation set as the default for queries made in
-- the Amazon Web Services Region and Amazon Web Services account in which
-- you called this operation.
--
-- 'httpStatus', 'associateDefaultViewResponse_httpStatus' - The response's http status code.
newAssociateDefaultViewResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateDefaultViewResponse
newAssociateDefaultViewResponse :: Int -> AssociateDefaultViewResponse
newAssociateDefaultViewResponse Int
pHttpStatus_ =
  AssociateDefaultViewResponse'
    { $sel:viewArn:AssociateDefaultViewResponse' :: Maybe Text
viewArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociateDefaultViewResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view that the operation set as the default for queries made in
-- the Amazon Web Services Region and Amazon Web Services account in which
-- you called this operation.
associateDefaultViewResponse_viewArn :: Lens.Lens' AssociateDefaultViewResponse (Prelude.Maybe Prelude.Text)
associateDefaultViewResponse_viewArn :: Lens' AssociateDefaultViewResponse (Maybe Text)
associateDefaultViewResponse_viewArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateDefaultViewResponse' {Maybe Text
viewArn :: Maybe Text
$sel:viewArn:AssociateDefaultViewResponse' :: AssociateDefaultViewResponse -> Maybe Text
viewArn} -> Maybe Text
viewArn) (\s :: AssociateDefaultViewResponse
s@AssociateDefaultViewResponse' {} Maybe Text
a -> AssociateDefaultViewResponse
s {$sel:viewArn:AssociateDefaultViewResponse' :: Maybe Text
viewArn = Maybe Text
a} :: AssociateDefaultViewResponse)

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

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