{-# 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.SageMakerGeoSpatial.Types.VectorEnrichmentJobErrorType
-- 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.SageMakerGeoSpatial.Types.VectorEnrichmentJobErrorType
  ( VectorEnrichmentJobErrorType
      ( ..,
        VectorEnrichmentJobErrorType_CLIENT_ERROR,
        VectorEnrichmentJobErrorType_SERVER_ERROR
      ),
  )
where

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

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

pattern VectorEnrichmentJobErrorType_CLIENT_ERROR :: VectorEnrichmentJobErrorType
pattern $bVectorEnrichmentJobErrorType_CLIENT_ERROR :: VectorEnrichmentJobErrorType
$mVectorEnrichmentJobErrorType_CLIENT_ERROR :: forall {r}.
VectorEnrichmentJobErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
VectorEnrichmentJobErrorType_CLIENT_ERROR = VectorEnrichmentJobErrorType' "CLIENT_ERROR"

pattern VectorEnrichmentJobErrorType_SERVER_ERROR :: VectorEnrichmentJobErrorType
pattern $bVectorEnrichmentJobErrorType_SERVER_ERROR :: VectorEnrichmentJobErrorType
$mVectorEnrichmentJobErrorType_SERVER_ERROR :: forall {r}.
VectorEnrichmentJobErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
VectorEnrichmentJobErrorType_SERVER_ERROR = VectorEnrichmentJobErrorType' "SERVER_ERROR"

{-# COMPLETE
  VectorEnrichmentJobErrorType_CLIENT_ERROR,
  VectorEnrichmentJobErrorType_SERVER_ERROR,
  VectorEnrichmentJobErrorType'
  #-}