{-# 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.Panorama.Types.DeviceAggregatedStatus
-- 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.Panorama.Types.DeviceAggregatedStatus
  ( DeviceAggregatedStatus
      ( ..,
        DeviceAggregatedStatus_AWAITING_PROVISIONING,
        DeviceAggregatedStatus_DELETING,
        DeviceAggregatedStatus_ERROR,
        DeviceAggregatedStatus_FAILED,
        DeviceAggregatedStatus_LEASE_EXPIRED,
        DeviceAggregatedStatus_OFFLINE,
        DeviceAggregatedStatus_ONLINE,
        DeviceAggregatedStatus_PENDING,
        DeviceAggregatedStatus_REBOOTING,
        DeviceAggregatedStatus_UPDATE_NEEDED
      ),
  )
where

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

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

pattern DeviceAggregatedStatus_AWAITING_PROVISIONING :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_AWAITING_PROVISIONING :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_AWAITING_PROVISIONING :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_AWAITING_PROVISIONING = DeviceAggregatedStatus' "AWAITING_PROVISIONING"

pattern DeviceAggregatedStatus_DELETING :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_DELETING :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_DELETING :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_DELETING = DeviceAggregatedStatus' "DELETING"

pattern DeviceAggregatedStatus_ERROR :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_ERROR :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_ERROR :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_ERROR = DeviceAggregatedStatus' "ERROR"

pattern DeviceAggregatedStatus_FAILED :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_FAILED :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_FAILED :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_FAILED = DeviceAggregatedStatus' "FAILED"

pattern DeviceAggregatedStatus_LEASE_EXPIRED :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_LEASE_EXPIRED :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_LEASE_EXPIRED :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_LEASE_EXPIRED = DeviceAggregatedStatus' "LEASE_EXPIRED"

pattern DeviceAggregatedStatus_OFFLINE :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_OFFLINE :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_OFFLINE :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_OFFLINE = DeviceAggregatedStatus' "OFFLINE"

pattern DeviceAggregatedStatus_ONLINE :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_ONLINE :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_ONLINE :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_ONLINE = DeviceAggregatedStatus' "ONLINE"

pattern DeviceAggregatedStatus_PENDING :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_PENDING :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_PENDING :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_PENDING = DeviceAggregatedStatus' "PENDING"

pattern DeviceAggregatedStatus_REBOOTING :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_REBOOTING :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_REBOOTING :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_REBOOTING = DeviceAggregatedStatus' "REBOOTING"

pattern DeviceAggregatedStatus_UPDATE_NEEDED :: DeviceAggregatedStatus
pattern $bDeviceAggregatedStatus_UPDATE_NEEDED :: DeviceAggregatedStatus
$mDeviceAggregatedStatus_UPDATE_NEEDED :: forall {r}.
DeviceAggregatedStatus -> ((# #) -> r) -> ((# #) -> r) -> r
DeviceAggregatedStatus_UPDATE_NEEDED = DeviceAggregatedStatus' "UPDATE_NEEDED"

{-# COMPLETE
  DeviceAggregatedStatus_AWAITING_PROVISIONING,
  DeviceAggregatedStatus_DELETING,
  DeviceAggregatedStatus_ERROR,
  DeviceAggregatedStatus_FAILED,
  DeviceAggregatedStatus_LEASE_EXPIRED,
  DeviceAggregatedStatus_OFFLINE,
  DeviceAggregatedStatus_ONLINE,
  DeviceAggregatedStatus_PENDING,
  DeviceAggregatedStatus_REBOOTING,
  DeviceAggregatedStatus_UPDATE_NEEDED,
  DeviceAggregatedStatus'
  #-}