{-# 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.GetDefaultView
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the Amazon Resource Name (ARN) of the view that is the default
-- for the Amazon Web Services Region in which you call this operation. You
-- can then call GetView to retrieve the details of that view.
module Amazonka.ResourceExplorer2.GetDefaultView
  ( -- * Creating a Request
    GetDefaultView (..),
    newGetDefaultView,

    -- * Destructuring the Response
    GetDefaultViewResponse (..),
    newGetDefaultViewResponse,

    -- * Response Lenses
    getDefaultViewResponse_viewArn,
    getDefaultViewResponse_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:/ 'newGetDefaultView' smart constructor.
data GetDefaultView = GetDefaultView'
  {
  }
  deriving (GetDefaultView -> GetDefaultView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDefaultView -> GetDefaultView -> Bool
$c/= :: GetDefaultView -> GetDefaultView -> Bool
== :: GetDefaultView -> GetDefaultView -> Bool
$c== :: GetDefaultView -> GetDefaultView -> Bool
Prelude.Eq, ReadPrec [GetDefaultView]
ReadPrec GetDefaultView
Int -> ReadS GetDefaultView
ReadS [GetDefaultView]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDefaultView]
$creadListPrec :: ReadPrec [GetDefaultView]
readPrec :: ReadPrec GetDefaultView
$creadPrec :: ReadPrec GetDefaultView
readList :: ReadS [GetDefaultView]
$creadList :: ReadS [GetDefaultView]
readsPrec :: Int -> ReadS GetDefaultView
$creadsPrec :: Int -> ReadS GetDefaultView
Prelude.Read, Int -> GetDefaultView -> ShowS
[GetDefaultView] -> ShowS
GetDefaultView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDefaultView] -> ShowS
$cshowList :: [GetDefaultView] -> ShowS
show :: GetDefaultView -> String
$cshow :: GetDefaultView -> String
showsPrec :: Int -> GetDefaultView -> ShowS
$cshowsPrec :: Int -> GetDefaultView -> ShowS
Prelude.Show, forall x. Rep GetDefaultView x -> GetDefaultView
forall x. GetDefaultView -> Rep GetDefaultView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDefaultView x -> GetDefaultView
$cfrom :: forall x. GetDefaultView -> Rep GetDefaultView x
Prelude.Generic)

-- |
-- Create a value of 'GetDefaultView' 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.
newGetDefaultView ::
  GetDefaultView
newGetDefaultView :: GetDefaultView
newGetDefaultView = GetDefaultView
GetDefaultView'

instance Core.AWSRequest GetDefaultView where
  type
    AWSResponse GetDefaultView =
      GetDefaultViewResponse
  request :: (Service -> Service) -> GetDefaultView -> Request GetDefaultView
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 GetDefaultView
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDefaultView)))
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 -> GetDefaultViewResponse
GetDefaultViewResponse'
            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 GetDefaultView where
  hashWithSalt :: Int -> GetDefaultView -> Int
hashWithSalt Int
_salt GetDefaultView
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData GetDefaultView where
  rnf :: GetDefaultView -> ()
rnf GetDefaultView
_ = ()

instance Data.ToHeaders GetDefaultView where
  toHeaders :: GetDefaultView -> 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 GetDefaultView where
  toJSON :: GetDefaultView -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'GetDefaultViewResponse' 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', 'getDefaultViewResponse_viewArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon resource name (ARN)>
-- of the view that is the current default for the Amazon Web Services
-- Region in which you called this operation.
--
-- 'httpStatus', 'getDefaultViewResponse_httpStatus' - The response's http status code.
newGetDefaultViewResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDefaultViewResponse
newGetDefaultViewResponse :: Int -> GetDefaultViewResponse
newGetDefaultViewResponse Int
pHttpStatus_ =
  GetDefaultViewResponse'
    { $sel:viewArn:GetDefaultViewResponse' :: Maybe Text
viewArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDefaultViewResponse' :: 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 is the current default for the Amazon Web Services
-- Region in which you called this operation.
getDefaultViewResponse_viewArn :: Lens.Lens' GetDefaultViewResponse (Prelude.Maybe Prelude.Text)
getDefaultViewResponse_viewArn :: Lens' GetDefaultViewResponse (Maybe Text)
getDefaultViewResponse_viewArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultViewResponse' {Maybe Text
viewArn :: Maybe Text
$sel:viewArn:GetDefaultViewResponse' :: GetDefaultViewResponse -> Maybe Text
viewArn} -> Maybe Text
viewArn) (\s :: GetDefaultViewResponse
s@GetDefaultViewResponse' {} Maybe Text
a -> GetDefaultViewResponse
s {$sel:viewArn:GetDefaultViewResponse' :: Maybe Text
viewArn = Maybe Text
a} :: GetDefaultViewResponse)

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

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