{-# 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.MGN.Types.ReplicationType
-- 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.MGN.Types.ReplicationType
  ( ReplicationType
      ( ..,
        ReplicationType_AGENT_BASED,
        ReplicationType_SNAPSHOT_SHIPPING
      ),
  )
where

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

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

pattern ReplicationType_AGENT_BASED :: ReplicationType
pattern $bReplicationType_AGENT_BASED :: ReplicationType
$mReplicationType_AGENT_BASED :: forall {r}. ReplicationType -> ((# #) -> r) -> ((# #) -> r) -> r
ReplicationType_AGENT_BASED = ReplicationType' "AGENT_BASED"

pattern ReplicationType_SNAPSHOT_SHIPPING :: ReplicationType
pattern $bReplicationType_SNAPSHOT_SHIPPING :: ReplicationType
$mReplicationType_SNAPSHOT_SHIPPING :: forall {r}. ReplicationType -> ((# #) -> r) -> ((# #) -> r) -> r
ReplicationType_SNAPSHOT_SHIPPING = ReplicationType' "SNAPSHOT_SHIPPING"

{-# COMPLETE
  ReplicationType_AGENT_BASED,
  ReplicationType_SNAPSHOT_SHIPPING,
  ReplicationType'
  #-}