{-# 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.SSMIncidents.Types.VariableType
-- 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.SSMIncidents.Types.VariableType
  ( VariableType
      ( ..,
        VariableType_INCIDENT_RECORD_ARN,
        VariableType_INVOLVED_RESOURCES
      ),
  )
where

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

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

pattern VariableType_INCIDENT_RECORD_ARN :: VariableType
pattern $bVariableType_INCIDENT_RECORD_ARN :: VariableType
$mVariableType_INCIDENT_RECORD_ARN :: forall {r}. VariableType -> ((# #) -> r) -> ((# #) -> r) -> r
VariableType_INCIDENT_RECORD_ARN = VariableType' "INCIDENT_RECORD_ARN"

pattern VariableType_INVOLVED_RESOURCES :: VariableType
pattern $bVariableType_INVOLVED_RESOURCES :: VariableType
$mVariableType_INVOLVED_RESOURCES :: forall {r}. VariableType -> ((# #) -> r) -> ((# #) -> r) -> r
VariableType_INVOLVED_RESOURCES = VariableType' "INVOLVED_RESOURCES"

{-# COMPLETE
  VariableType_INCIDENT_RECORD_ARN,
  VariableType_INVOLVED_RESOURCES,
  VariableType'
  #-}