module Stratosphere.ElasticLoadBalancing.LoadBalancer.HealthCheckProperty (
HealthCheckProperty(..), mkHealthCheckProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data HealthCheckProperty
=
HealthCheckProperty {HealthCheckProperty -> ()
haddock_workaround_ :: (),
HealthCheckProperty -> Value Text
healthyThreshold :: (Value Prelude.Text),
HealthCheckProperty -> Value Text
interval :: (Value Prelude.Text),
HealthCheckProperty -> Value Text
target :: (Value Prelude.Text),
HealthCheckProperty -> Value Text
timeout :: (Value Prelude.Text),
HealthCheckProperty -> Value Text
unhealthyThreshold :: (Value Prelude.Text)}
deriving stock (HealthCheckProperty -> HealthCheckProperty -> Bool
(HealthCheckProperty -> HealthCheckProperty -> Bool)
-> (HealthCheckProperty -> HealthCheckProperty -> Bool)
-> Eq HealthCheckProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HealthCheckProperty -> HealthCheckProperty -> Bool
== :: HealthCheckProperty -> HealthCheckProperty -> Bool
$c/= :: HealthCheckProperty -> HealthCheckProperty -> Bool
/= :: HealthCheckProperty -> HealthCheckProperty -> Bool
Prelude.Eq, Int -> HealthCheckProperty -> ShowS
[HealthCheckProperty] -> ShowS
HealthCheckProperty -> String
(Int -> HealthCheckProperty -> ShowS)
-> (HealthCheckProperty -> String)
-> ([HealthCheckProperty] -> ShowS)
-> Show HealthCheckProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HealthCheckProperty -> ShowS
showsPrec :: Int -> HealthCheckProperty -> ShowS
$cshow :: HealthCheckProperty -> String
show :: HealthCheckProperty -> String
$cshowList :: [HealthCheckProperty] -> ShowS
showList :: [HealthCheckProperty] -> ShowS
Prelude.Show)
mkHealthCheckProperty ::
Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text -> Value Prelude.Text -> HealthCheckProperty
mkHealthCheckProperty :: Value Text
-> Value Text
-> Value Text
-> Value Text
-> Value Text
-> HealthCheckProperty
mkHealthCheckProperty
Value Text
healthyThreshold
Value Text
interval
Value Text
target
Value Text
timeout
Value Text
unhealthyThreshold
= HealthCheckProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), healthyThreshold :: Value Text
healthyThreshold = Value Text
healthyThreshold,
interval :: Value Text
interval = Value Text
interval, target :: Value Text
target = Value Text
target, timeout :: Value Text
timeout = Value Text
timeout,
unhealthyThreshold :: Value Text
unhealthyThreshold = Value Text
unhealthyThreshold}
instance ToResourceProperties HealthCheckProperty where
toResourceProperties :: HealthCheckProperty -> ResourceProperties
toResourceProperties HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::ElasticLoadBalancing::LoadBalancer.HealthCheck",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"HealthyThreshold" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
healthyThreshold,
Key
"Interval" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
interval, Key
"Target" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
target,
Key
"Timeout" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
timeout,
Key
"UnhealthyThreshold" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
unhealthyThreshold]}
instance JSON.ToJSON HealthCheckProperty where
toJSON :: HealthCheckProperty -> Value
toJSON HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"HealthyThreshold" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
healthyThreshold,
Key
"Interval" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
interval, Key
"Target" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
target,
Key
"Timeout" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
timeout,
Key
"UnhealthyThreshold" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
unhealthyThreshold]
instance Property "HealthyThreshold" HealthCheckProperty where
type PropertyType "HealthyThreshold" HealthCheckProperty = Value Prelude.Text
set :: PropertyType "HealthyThreshold" HealthCheckProperty
-> HealthCheckProperty -> HealthCheckProperty
set PropertyType "HealthyThreshold" HealthCheckProperty
newValue HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= HealthCheckProperty {healthyThreshold :: Value Text
healthyThreshold = PropertyType "HealthyThreshold" HealthCheckProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
haddock_workaround_ :: ()
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
instance Property "Interval" HealthCheckProperty where
type PropertyType "Interval" HealthCheckProperty = Value Prelude.Text
set :: PropertyType "Interval" HealthCheckProperty
-> HealthCheckProperty -> HealthCheckProperty
set PropertyType "Interval" HealthCheckProperty
newValue HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= HealthCheckProperty {interval :: Value Text
interval = PropertyType "Interval" HealthCheckProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
instance Property "Target" HealthCheckProperty where
type PropertyType "Target" HealthCheckProperty = Value Prelude.Text
set :: PropertyType "Target" HealthCheckProperty
-> HealthCheckProperty -> HealthCheckProperty
set PropertyType "Target" HealthCheckProperty
newValue HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= HealthCheckProperty {target :: Value Text
target = PropertyType "Target" HealthCheckProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
instance Property "Timeout" HealthCheckProperty where
type PropertyType "Timeout" HealthCheckProperty = Value Prelude.Text
set :: PropertyType "Timeout" HealthCheckProperty
-> HealthCheckProperty -> HealthCheckProperty
set PropertyType "Timeout" HealthCheckProperty
newValue HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= HealthCheckProperty {timeout :: Value Text
timeout = PropertyType "Timeout" HealthCheckProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
unhealthyThreshold :: Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
unhealthyThreshold :: Value Text
..}
instance Property "UnhealthyThreshold" HealthCheckProperty where
type PropertyType "UnhealthyThreshold" HealthCheckProperty = Value Prelude.Text
set :: PropertyType "UnhealthyThreshold" HealthCheckProperty
-> HealthCheckProperty -> HealthCheckProperty
set PropertyType "UnhealthyThreshold" HealthCheckProperty
newValue HealthCheckProperty {()
Value Text
haddock_workaround_ :: HealthCheckProperty -> ()
healthyThreshold :: HealthCheckProperty -> Value Text
interval :: HealthCheckProperty -> Value Text
target :: HealthCheckProperty -> Value Text
timeout :: HealthCheckProperty -> Value Text
unhealthyThreshold :: HealthCheckProperty -> Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
unhealthyThreshold :: Value Text
..}
= HealthCheckProperty {unhealthyThreshold :: Value Text
unhealthyThreshold = PropertyType "UnhealthyThreshold" HealthCheckProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
haddock_workaround_ :: ()
healthyThreshold :: Value Text
interval :: Value Text
target :: Value Text
timeout :: Value Text
..}