{-# 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.MechanicalTurk.GetAccountBalance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The @GetAccountBalance@ operation retrieves the Prepaid HITs balance in
-- your Amazon Mechanical Turk account if you are a Prepaid Requester.
-- Alternatively, this operation will retrieve the remaining available AWS
-- Billing usage if you have enabled AWS Billing. Note: If you have enabled
-- AWS Billing and still have a remaining Prepaid HITs balance, this
-- balance can be viewed on the My Account page in the Requester console.
module Amazonka.MechanicalTurk.GetAccountBalance
  ( -- * Creating a Request
    GetAccountBalance (..),
    newGetAccountBalance,

    -- * Destructuring the Response
    GetAccountBalanceResponse (..),
    newGetAccountBalanceResponse,

    -- * Response Lenses
    getAccountBalanceResponse_availableBalance,
    getAccountBalanceResponse_onHoldBalance,
    getAccountBalanceResponse_httpStatus,
  )
where

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

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

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

instance Core.AWSRequest GetAccountBalance where
  type
    AWSResponse GetAccountBalance =
      GetAccountBalanceResponse
  request :: (Service -> Service)
-> GetAccountBalance -> Request GetAccountBalance
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 GetAccountBalance
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAccountBalance)))
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 -> Maybe Text -> Int -> GetAccountBalanceResponse
GetAccountBalanceResponse'
            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
"AvailableBalance")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OnHoldBalance")
            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 GetAccountBalance where
  hashWithSalt :: Int -> GetAccountBalance -> Int
hashWithSalt Int
_salt GetAccountBalance
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetAccountBalance where
  toHeaders :: GetAccountBalance -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"MTurkRequesterServiceV20170117.GetAccountBalance" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetAccountBalance where
  toJSON :: GetAccountBalance -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'GetAccountBalanceResponse' 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:
--
-- 'availableBalance', 'getAccountBalanceResponse_availableBalance' - Undocumented member.
--
-- 'onHoldBalance', 'getAccountBalanceResponse_onHoldBalance' - Undocumented member.
--
-- 'httpStatus', 'getAccountBalanceResponse_httpStatus' - The response's http status code.
newGetAccountBalanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAccountBalanceResponse
newGetAccountBalanceResponse :: Int -> GetAccountBalanceResponse
newGetAccountBalanceResponse Int
pHttpStatus_ =
  GetAccountBalanceResponse'
    { $sel:availableBalance:GetAccountBalanceResponse' :: Maybe Text
availableBalance =
        forall a. Maybe a
Prelude.Nothing,
      $sel:onHoldBalance:GetAccountBalanceResponse' :: Maybe Text
onHoldBalance = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAccountBalanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
getAccountBalanceResponse_availableBalance :: Lens.Lens' GetAccountBalanceResponse (Prelude.Maybe Prelude.Text)
getAccountBalanceResponse_availableBalance :: Lens' GetAccountBalanceResponse (Maybe Text)
getAccountBalanceResponse_availableBalance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAccountBalanceResponse' {Maybe Text
availableBalance :: Maybe Text
$sel:availableBalance:GetAccountBalanceResponse' :: GetAccountBalanceResponse -> Maybe Text
availableBalance} -> Maybe Text
availableBalance) (\s :: GetAccountBalanceResponse
s@GetAccountBalanceResponse' {} Maybe Text
a -> GetAccountBalanceResponse
s {$sel:availableBalance:GetAccountBalanceResponse' :: Maybe Text
availableBalance = Maybe Text
a} :: GetAccountBalanceResponse)

-- | Undocumented member.
getAccountBalanceResponse_onHoldBalance :: Lens.Lens' GetAccountBalanceResponse (Prelude.Maybe Prelude.Text)
getAccountBalanceResponse_onHoldBalance :: Lens' GetAccountBalanceResponse (Maybe Text)
getAccountBalanceResponse_onHoldBalance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAccountBalanceResponse' {Maybe Text
onHoldBalance :: Maybe Text
$sel:onHoldBalance:GetAccountBalanceResponse' :: GetAccountBalanceResponse -> Maybe Text
onHoldBalance} -> Maybe Text
onHoldBalance) (\s :: GetAccountBalanceResponse
s@GetAccountBalanceResponse' {} Maybe Text
a -> GetAccountBalanceResponse
s {$sel:onHoldBalance:GetAccountBalanceResponse' :: Maybe Text
onHoldBalance = Maybe Text
a} :: GetAccountBalanceResponse)

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

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