{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CostExplorer.Types.AccountScope
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CostExplorer.Types.AccountScope
  ( AccountScope
      ( ..,
        AccountScope_LINKED,
        AccountScope_PAYER
      ),
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

newtype AccountScope = AccountScope'
  { AccountScope -> Text
fromAccountScope ::
      Data.Text
  }
  deriving stock
    ( Int -> AccountScope -> ShowS
[AccountScope] -> ShowS
AccountScope -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountScope] -> ShowS
$cshowList :: [AccountScope] -> ShowS
show :: AccountScope -> String
$cshow :: AccountScope -> String
showsPrec :: Int -> AccountScope -> ShowS
$cshowsPrec :: Int -> AccountScope -> ShowS
Prelude.Show,
      ReadPrec [AccountScope]
ReadPrec AccountScope
Int -> ReadS AccountScope
ReadS [AccountScope]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AccountScope]
$creadListPrec :: ReadPrec [AccountScope]
readPrec :: ReadPrec AccountScope
$creadPrec :: ReadPrec AccountScope
readList :: ReadS [AccountScope]
$creadList :: ReadS [AccountScope]
readsPrec :: Int -> ReadS AccountScope
$creadsPrec :: Int -> ReadS AccountScope
Prelude.Read,
      AccountScope -> AccountScope -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountScope -> AccountScope -> Bool
$c/= :: AccountScope -> AccountScope -> Bool
== :: AccountScope -> AccountScope -> Bool
$c== :: AccountScope -> AccountScope -> Bool
Prelude.Eq,
      Eq AccountScope
AccountScope -> AccountScope -> Bool
AccountScope -> AccountScope -> Ordering
AccountScope -> AccountScope -> AccountScope
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AccountScope -> AccountScope -> AccountScope
$cmin :: AccountScope -> AccountScope -> AccountScope
max :: AccountScope -> AccountScope -> AccountScope
$cmax :: AccountScope -> AccountScope -> AccountScope
>= :: AccountScope -> AccountScope -> Bool
$c>= :: AccountScope -> AccountScope -> Bool
> :: AccountScope -> AccountScope -> Bool
$c> :: AccountScope -> AccountScope -> Bool
<= :: AccountScope -> AccountScope -> Bool
$c<= :: AccountScope -> AccountScope -> Bool
< :: AccountScope -> AccountScope -> Bool
$c< :: AccountScope -> AccountScope -> Bool
compare :: AccountScope -> AccountScope -> Ordering
$ccompare :: AccountScope -> AccountScope -> Ordering
Prelude.Ord,
      forall x. Rep AccountScope x -> AccountScope
forall x. AccountScope -> Rep AccountScope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountScope x -> AccountScope
$cfrom :: forall x. AccountScope -> Rep AccountScope x
Prelude.Generic
    )
  deriving newtype
    ( Eq AccountScope
Int -> AccountScope -> Int
AccountScope -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AccountScope -> Int
$chash :: AccountScope -> Int
hashWithSalt :: Int -> AccountScope -> Int
$chashWithSalt :: Int -> AccountScope -> Int
Prelude.Hashable,
      AccountScope -> ()
forall a. (a -> ()) -> NFData a
rnf :: AccountScope -> ()
$crnf :: AccountScope -> ()
Prelude.NFData,
      Text -> Either String AccountScope
forall a. (Text -> Either String a) -> FromText a
fromText :: Text -> Either String AccountScope
$cfromText :: Text -> Either String AccountScope
Data.FromText,
      AccountScope -> Text
forall a. (a -> Text) -> ToText a
toText :: AccountScope -> Text
$ctoText :: AccountScope -> Text
Data.ToText,
      AccountScope -> ByteString
forall a. (a -> ByteString) -> ToByteString a
toBS :: AccountScope -> ByteString
$ctoBS :: AccountScope -> ByteString
Data.ToByteString,
      AccountScope -> ByteStringBuilder
forall a. (a -> ByteStringBuilder) -> ToLog a
build :: AccountScope -> ByteStringBuilder
$cbuild :: AccountScope -> ByteStringBuilder
Data.ToLog,
      HeaderName -> AccountScope -> [Header]
forall a. (HeaderName -> a -> [Header]) -> ToHeader a
toHeader :: HeaderName -> AccountScope -> [Header]
$ctoHeader :: HeaderName -> AccountScope -> [Header]
Data.ToHeader,
      AccountScope -> QueryString
forall a. (a -> QueryString) -> ToQuery a
toQuery :: AccountScope -> QueryString
$ctoQuery :: AccountScope -> QueryString
Data.ToQuery,
      Value -> Parser [AccountScope]
Value -> Parser AccountScope
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AccountScope]
$cparseJSONList :: Value -> Parser [AccountScope]
parseJSON :: Value -> Parser AccountScope
$cparseJSON :: Value -> Parser AccountScope
Data.FromJSON,
      FromJSONKeyFunction [AccountScope]
FromJSONKeyFunction AccountScope
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [AccountScope]
$cfromJSONKeyList :: FromJSONKeyFunction [AccountScope]
fromJSONKey :: FromJSONKeyFunction AccountScope
$cfromJSONKey :: FromJSONKeyFunction AccountScope
Data.FromJSONKey,
      [AccountScope] -> Encoding
[AccountScope] -> Value
AccountScope -> Encoding
AccountScope -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountScope] -> Encoding
$ctoEncodingList :: [AccountScope] -> Encoding
toJSONList :: [AccountScope] -> Value
$ctoJSONList :: [AccountScope] -> Value
toEncoding :: AccountScope -> Encoding
$ctoEncoding :: AccountScope -> Encoding
toJSON :: AccountScope -> Value
$ctoJSON :: AccountScope -> Value
Data.ToJSON,
      ToJSONKeyFunction [AccountScope]
ToJSONKeyFunction AccountScope
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [AccountScope]
$ctoJSONKeyList :: ToJSONKeyFunction [AccountScope]
toJSONKey :: ToJSONKeyFunction AccountScope
$ctoJSONKey :: ToJSONKeyFunction AccountScope
Data.ToJSONKey,
      [Node] -> Either String AccountScope
forall a. ([Node] -> Either String a) -> FromXML a
parseXML :: [Node] -> Either String AccountScope
$cparseXML :: [Node] -> Either String AccountScope
Data.FromXML,
      AccountScope -> XML
forall a. (a -> XML) -> ToXML a
toXML :: AccountScope -> XML
$ctoXML :: AccountScope -> XML
Data.ToXML
    )

pattern AccountScope_LINKED :: AccountScope
pattern $bAccountScope_LINKED :: AccountScope
$mAccountScope_LINKED :: forall {r}. AccountScope -> ((# #) -> r) -> ((# #) -> r) -> r
AccountScope_LINKED = AccountScope' "LINKED"

pattern AccountScope_PAYER :: AccountScope
pattern $bAccountScope_PAYER :: AccountScope
$mAccountScope_PAYER :: forall {r}. AccountScope -> ((# #) -> r) -> ((# #) -> r) -> r
AccountScope_PAYER = AccountScope' "PAYER"

{-# COMPLETE
  AccountScope_LINKED,
  AccountScope_PAYER,
  AccountScope'
  #-}