{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Amazonka.Inspector2.Types.GroupKey
( GroupKey
( ..,
GroupKey_ACCOUNT_ID,
GroupKey_ECR_REPOSITORY_NAME,
GroupKey_RESOURCE_TYPE,
GroupKey_SCAN_STATUS_CODE,
GroupKey_SCAN_STATUS_REASON
),
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
newtype GroupKey = GroupKey'
{ GroupKey -> Text
fromGroupKey ::
Data.Text
}
deriving stock
( Int -> GroupKey -> ShowS
[GroupKey] -> ShowS
GroupKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupKey] -> ShowS
$cshowList :: [GroupKey] -> ShowS
show :: GroupKey -> String
$cshow :: GroupKey -> String
showsPrec :: Int -> GroupKey -> ShowS
$cshowsPrec :: Int -> GroupKey -> ShowS
Prelude.Show,
ReadPrec [GroupKey]
ReadPrec GroupKey
Int -> ReadS GroupKey
ReadS [GroupKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GroupKey]
$creadListPrec :: ReadPrec [GroupKey]
readPrec :: ReadPrec GroupKey
$creadPrec :: ReadPrec GroupKey
readList :: ReadS [GroupKey]
$creadList :: ReadS [GroupKey]
readsPrec :: Int -> ReadS GroupKey
$creadsPrec :: Int -> ReadS GroupKey
Prelude.Read,
GroupKey -> GroupKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupKey -> GroupKey -> Bool
$c/= :: GroupKey -> GroupKey -> Bool
== :: GroupKey -> GroupKey -> Bool
$c== :: GroupKey -> GroupKey -> Bool
Prelude.Eq,
Eq GroupKey
GroupKey -> GroupKey -> Bool
GroupKey -> GroupKey -> Ordering
GroupKey -> GroupKey -> GroupKey
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 :: GroupKey -> GroupKey -> GroupKey
$cmin :: GroupKey -> GroupKey -> GroupKey
max :: GroupKey -> GroupKey -> GroupKey
$cmax :: GroupKey -> GroupKey -> GroupKey
>= :: GroupKey -> GroupKey -> Bool
$c>= :: GroupKey -> GroupKey -> Bool
> :: GroupKey -> GroupKey -> Bool
$c> :: GroupKey -> GroupKey -> Bool
<= :: GroupKey -> GroupKey -> Bool
$c<= :: GroupKey -> GroupKey -> Bool
< :: GroupKey -> GroupKey -> Bool
$c< :: GroupKey -> GroupKey -> Bool
compare :: GroupKey -> GroupKey -> Ordering
$ccompare :: GroupKey -> GroupKey -> Ordering
Prelude.Ord,
forall x. Rep GroupKey x -> GroupKey
forall x. GroupKey -> Rep GroupKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupKey x -> GroupKey
$cfrom :: forall x. GroupKey -> Rep GroupKey x
Prelude.Generic
)
deriving newtype
( Eq GroupKey
Int -> GroupKey -> Int
GroupKey -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GroupKey -> Int
$chash :: GroupKey -> Int
hashWithSalt :: Int -> GroupKey -> Int
$chashWithSalt :: Int -> GroupKey -> Int
Prelude.Hashable,
GroupKey -> ()
forall a. (a -> ()) -> NFData a
rnf :: GroupKey -> ()
$crnf :: GroupKey -> ()
Prelude.NFData,
Text -> Either String GroupKey
forall a. (Text -> Either String a) -> FromText a
fromText :: Text -> Either String GroupKey
$cfromText :: Text -> Either String GroupKey
Data.FromText,
GroupKey -> Text
forall a. (a -> Text) -> ToText a
toText :: GroupKey -> Text
$ctoText :: GroupKey -> Text
Data.ToText,
GroupKey -> ByteString
forall a. (a -> ByteString) -> ToByteString a
toBS :: GroupKey -> ByteString
$ctoBS :: GroupKey -> ByteString
Data.ToByteString,
GroupKey -> ByteStringBuilder
forall a. (a -> ByteStringBuilder) -> ToLog a
build :: GroupKey -> ByteStringBuilder
$cbuild :: GroupKey -> ByteStringBuilder
Data.ToLog,
HeaderName -> GroupKey -> [Header]
forall a. (HeaderName -> a -> [Header]) -> ToHeader a
toHeader :: HeaderName -> GroupKey -> [Header]
$ctoHeader :: HeaderName -> GroupKey -> [Header]
Data.ToHeader,
GroupKey -> QueryString
forall a. (a -> QueryString) -> ToQuery a
toQuery :: GroupKey -> QueryString
$ctoQuery :: GroupKey -> QueryString
Data.ToQuery,
Value -> Parser [GroupKey]
Value -> Parser GroupKey
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GroupKey]
$cparseJSONList :: Value -> Parser [GroupKey]
parseJSON :: Value -> Parser GroupKey
$cparseJSON :: Value -> Parser GroupKey
Data.FromJSON,
FromJSONKeyFunction [GroupKey]
FromJSONKeyFunction GroupKey
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [GroupKey]
$cfromJSONKeyList :: FromJSONKeyFunction [GroupKey]
fromJSONKey :: FromJSONKeyFunction GroupKey
$cfromJSONKey :: FromJSONKeyFunction GroupKey
Data.FromJSONKey,
[GroupKey] -> Encoding
[GroupKey] -> Value
GroupKey -> Encoding
GroupKey -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [GroupKey] -> Encoding
$ctoEncodingList :: [GroupKey] -> Encoding
toJSONList :: [GroupKey] -> Value
$ctoJSONList :: [GroupKey] -> Value
toEncoding :: GroupKey -> Encoding
$ctoEncoding :: GroupKey -> Encoding
toJSON :: GroupKey -> Value
$ctoJSON :: GroupKey -> Value
Data.ToJSON,
ToJSONKeyFunction [GroupKey]
ToJSONKeyFunction GroupKey
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [GroupKey]
$ctoJSONKeyList :: ToJSONKeyFunction [GroupKey]
toJSONKey :: ToJSONKeyFunction GroupKey
$ctoJSONKey :: ToJSONKeyFunction GroupKey
Data.ToJSONKey,
[Node] -> Either String GroupKey
forall a. ([Node] -> Either String a) -> FromXML a
parseXML :: [Node] -> Either String GroupKey
$cparseXML :: [Node] -> Either String GroupKey
Data.FromXML,
GroupKey -> XML
forall a. (a -> XML) -> ToXML a
toXML :: GroupKey -> XML
$ctoXML :: GroupKey -> XML
Data.ToXML
)
pattern GroupKey_ACCOUNT_ID :: GroupKey
pattern $bGroupKey_ACCOUNT_ID :: GroupKey
$mGroupKey_ACCOUNT_ID :: forall {r}. GroupKey -> ((# #) -> r) -> ((# #) -> r) -> r
GroupKey_ACCOUNT_ID = GroupKey' "ACCOUNT_ID"
pattern GroupKey_ECR_REPOSITORY_NAME :: GroupKey
pattern $bGroupKey_ECR_REPOSITORY_NAME :: GroupKey
$mGroupKey_ECR_REPOSITORY_NAME :: forall {r}. GroupKey -> ((# #) -> r) -> ((# #) -> r) -> r
GroupKey_ECR_REPOSITORY_NAME = GroupKey' "ECR_REPOSITORY_NAME"
pattern GroupKey_RESOURCE_TYPE :: GroupKey
pattern $bGroupKey_RESOURCE_TYPE :: GroupKey
$mGroupKey_RESOURCE_TYPE :: forall {r}. GroupKey -> ((# #) -> r) -> ((# #) -> r) -> r
GroupKey_RESOURCE_TYPE = GroupKey' "RESOURCE_TYPE"
pattern GroupKey_SCAN_STATUS_CODE :: GroupKey
pattern $bGroupKey_SCAN_STATUS_CODE :: GroupKey
$mGroupKey_SCAN_STATUS_CODE :: forall {r}. GroupKey -> ((# #) -> r) -> ((# #) -> r) -> r
GroupKey_SCAN_STATUS_CODE = GroupKey' "SCAN_STATUS_CODE"
pattern GroupKey_SCAN_STATUS_REASON :: GroupKey
pattern $bGroupKey_SCAN_STATUS_REASON :: GroupKey
$mGroupKey_SCAN_STATUS_REASON :: forall {r}. GroupKey -> ((# #) -> r) -> ((# #) -> r) -> r
GroupKey_SCAN_STATUS_REASON = GroupKey' "SCAN_STATUS_REASON"
{-# COMPLETE
GroupKey_ACCOUNT_ID,
GroupKey_ECR_REPOSITORY_NAME,
GroupKey_RESOURCE_TYPE,
GroupKey_SCAN_STATUS_CODE,
GroupKey_SCAN_STATUS_REASON,
GroupKey'
#-}