{-# 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.Organizations.Types.EffectivePolicyType
-- 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.Organizations.Types.EffectivePolicyType
  ( EffectivePolicyType
      ( ..,
        EffectivePolicyType_AISERVICES_OPT_OUT_POLICY,
        EffectivePolicyType_BACKUP_POLICY,
        EffectivePolicyType_TAG_POLICY
      ),
  )
where

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

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

pattern EffectivePolicyType_AISERVICES_OPT_OUT_POLICY :: EffectivePolicyType
pattern $bEffectivePolicyType_AISERVICES_OPT_OUT_POLICY :: EffectivePolicyType
$mEffectivePolicyType_AISERVICES_OPT_OUT_POLICY :: forall {r}.
EffectivePolicyType -> ((# #) -> r) -> ((# #) -> r) -> r
EffectivePolicyType_AISERVICES_OPT_OUT_POLICY = EffectivePolicyType' "AISERVICES_OPT_OUT_POLICY"

pattern EffectivePolicyType_BACKUP_POLICY :: EffectivePolicyType
pattern $bEffectivePolicyType_BACKUP_POLICY :: EffectivePolicyType
$mEffectivePolicyType_BACKUP_POLICY :: forall {r}.
EffectivePolicyType -> ((# #) -> r) -> ((# #) -> r) -> r
EffectivePolicyType_BACKUP_POLICY = EffectivePolicyType' "BACKUP_POLICY"

pattern EffectivePolicyType_TAG_POLICY :: EffectivePolicyType
pattern $bEffectivePolicyType_TAG_POLICY :: EffectivePolicyType
$mEffectivePolicyType_TAG_POLICY :: forall {r}.
EffectivePolicyType -> ((# #) -> r) -> ((# #) -> r) -> r
EffectivePolicyType_TAG_POLICY = EffectivePolicyType' "TAG_POLICY"

{-# COMPLETE
  EffectivePolicyType_AISERVICES_OPT_OUT_POLICY,
  EffectivePolicyType_BACKUP_POLICY,
  EffectivePolicyType_TAG_POLICY,
  EffectivePolicyType'
  #-}