{-# 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.Nimble.GetEula
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get EULA.
module Amazonka.Nimble.GetEula
  ( -- * Creating a Request
    GetEula (..),
    newGetEula,

    -- * Request Lenses
    getEula_eulaId,

    -- * Destructuring the Response
    GetEulaResponse (..),
    newGetEulaResponse,

    -- * Response Lenses
    getEulaResponse_eula,
    getEulaResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Nimble.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetEula' smart constructor.
data GetEula = GetEula'
  { -- | The EULA ID.
    GetEula -> Text
eulaId :: Prelude.Text
  }
  deriving (GetEula -> GetEula -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEula -> GetEula -> Bool
$c/= :: GetEula -> GetEula -> Bool
== :: GetEula -> GetEula -> Bool
$c== :: GetEula -> GetEula -> Bool
Prelude.Eq, ReadPrec [GetEula]
ReadPrec GetEula
Int -> ReadS GetEula
ReadS [GetEula]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEula]
$creadListPrec :: ReadPrec [GetEula]
readPrec :: ReadPrec GetEula
$creadPrec :: ReadPrec GetEula
readList :: ReadS [GetEula]
$creadList :: ReadS [GetEula]
readsPrec :: Int -> ReadS GetEula
$creadsPrec :: Int -> ReadS GetEula
Prelude.Read, Int -> GetEula -> ShowS
[GetEula] -> ShowS
GetEula -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEula] -> ShowS
$cshowList :: [GetEula] -> ShowS
show :: GetEula -> String
$cshow :: GetEula -> String
showsPrec :: Int -> GetEula -> ShowS
$cshowsPrec :: Int -> GetEula -> ShowS
Prelude.Show, forall x. Rep GetEula x -> GetEula
forall x. GetEula -> Rep GetEula x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEula x -> GetEula
$cfrom :: forall x. GetEula -> Rep GetEula x
Prelude.Generic)

-- |
-- Create a value of 'GetEula' 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:
--
-- 'eulaId', 'getEula_eulaId' - The EULA ID.
newGetEula ::
  -- | 'eulaId'
  Prelude.Text ->
  GetEula
newGetEula :: Text -> GetEula
newGetEula Text
pEulaId_ = GetEula' {$sel:eulaId:GetEula' :: Text
eulaId = Text
pEulaId_}

-- | The EULA ID.
getEula_eulaId :: Lens.Lens' GetEula Prelude.Text
getEula_eulaId :: Lens' GetEula Text
getEula_eulaId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEula' {Text
eulaId :: Text
$sel:eulaId:GetEula' :: GetEula -> Text
eulaId} -> Text
eulaId) (\s :: GetEula
s@GetEula' {} Text
a -> GetEula
s {$sel:eulaId:GetEula' :: Text
eulaId = Text
a} :: GetEula)

instance Core.AWSRequest GetEula where
  type AWSResponse GetEula = GetEulaResponse
  request :: (Service -> Service) -> GetEula -> Request GetEula
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetEula
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetEula)))
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 Eula -> Int -> GetEulaResponse
GetEulaResponse'
            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
"eula")
            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 GetEula where
  hashWithSalt :: Int -> GetEula -> Int
hashWithSalt Int
_salt GetEula' {Text
eulaId :: Text
$sel:eulaId:GetEula' :: GetEula -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
eulaId

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

instance Data.ToHeaders GetEula where
  toHeaders :: GetEula -> 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.ToPath GetEula where
  toPath :: GetEula -> ByteString
toPath GetEula' {Text
eulaId :: Text
$sel:eulaId:GetEula' :: GetEula -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2020-08-01/eulas/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
eulaId]

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

-- | /See:/ 'newGetEulaResponse' smart constructor.
data GetEulaResponse = GetEulaResponse'
  { -- | The EULA.
    GetEulaResponse -> Maybe Eula
eula :: Prelude.Maybe Eula,
    -- | The response's http status code.
    GetEulaResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetEulaResponse -> GetEulaResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEulaResponse -> GetEulaResponse -> Bool
$c/= :: GetEulaResponse -> GetEulaResponse -> Bool
== :: GetEulaResponse -> GetEulaResponse -> Bool
$c== :: GetEulaResponse -> GetEulaResponse -> Bool
Prelude.Eq, ReadPrec [GetEulaResponse]
ReadPrec GetEulaResponse
Int -> ReadS GetEulaResponse
ReadS [GetEulaResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEulaResponse]
$creadListPrec :: ReadPrec [GetEulaResponse]
readPrec :: ReadPrec GetEulaResponse
$creadPrec :: ReadPrec GetEulaResponse
readList :: ReadS [GetEulaResponse]
$creadList :: ReadS [GetEulaResponse]
readsPrec :: Int -> ReadS GetEulaResponse
$creadsPrec :: Int -> ReadS GetEulaResponse
Prelude.Read, Int -> GetEulaResponse -> ShowS
[GetEulaResponse] -> ShowS
GetEulaResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEulaResponse] -> ShowS
$cshowList :: [GetEulaResponse] -> ShowS
show :: GetEulaResponse -> String
$cshow :: GetEulaResponse -> String
showsPrec :: Int -> GetEulaResponse -> ShowS
$cshowsPrec :: Int -> GetEulaResponse -> ShowS
Prelude.Show, forall x. Rep GetEulaResponse x -> GetEulaResponse
forall x. GetEulaResponse -> Rep GetEulaResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEulaResponse x -> GetEulaResponse
$cfrom :: forall x. GetEulaResponse -> Rep GetEulaResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetEulaResponse' 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:
--
-- 'eula', 'getEulaResponse_eula' - The EULA.
--
-- 'httpStatus', 'getEulaResponse_httpStatus' - The response's http status code.
newGetEulaResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetEulaResponse
newGetEulaResponse :: Int -> GetEulaResponse
newGetEulaResponse Int
pHttpStatus_ =
  GetEulaResponse'
    { $sel:eula:GetEulaResponse' :: Maybe Eula
eula = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetEulaResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The EULA.
getEulaResponse_eula :: Lens.Lens' GetEulaResponse (Prelude.Maybe Eula)
getEulaResponse_eula :: Lens' GetEulaResponse (Maybe Eula)
getEulaResponse_eula = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEulaResponse' {Maybe Eula
eula :: Maybe Eula
$sel:eula:GetEulaResponse' :: GetEulaResponse -> Maybe Eula
eula} -> Maybe Eula
eula) (\s :: GetEulaResponse
s@GetEulaResponse' {} Maybe Eula
a -> GetEulaResponse
s {$sel:eula:GetEulaResponse' :: Maybe Eula
eula = Maybe Eula
a} :: GetEulaResponse)

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

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