module Stratosphere.Batch.SchedulingPolicy (
        module Exports, SchedulingPolicy(..), mkSchedulingPolicy
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Batch.SchedulingPolicy.FairsharePolicyProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SchedulingPolicy
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-batch-schedulingpolicy.html>
    SchedulingPolicy {SchedulingPolicy -> ()
haddock_workaround_ :: (),
                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-batch-schedulingpolicy.html#cfn-batch-schedulingpolicy-fairsharepolicy>
                      SchedulingPolicy -> Maybe FairsharePolicyProperty
fairsharePolicy :: (Prelude.Maybe FairsharePolicyProperty),
                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-batch-schedulingpolicy.html#cfn-batch-schedulingpolicy-name>
                      SchedulingPolicy -> Maybe (Value Text)
name :: (Prelude.Maybe (Value Prelude.Text)),
                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-batch-schedulingpolicy.html#cfn-batch-schedulingpolicy-tags>
                      SchedulingPolicy -> Maybe (Map Text (Value Text))
tags :: (Prelude.Maybe (Prelude.Map Prelude.Text (Value Prelude.Text)))}
  deriving stock (SchedulingPolicy -> SchedulingPolicy -> Bool
(SchedulingPolicy -> SchedulingPolicy -> Bool)
-> (SchedulingPolicy -> SchedulingPolicy -> Bool)
-> Eq SchedulingPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchedulingPolicy -> SchedulingPolicy -> Bool
== :: SchedulingPolicy -> SchedulingPolicy -> Bool
$c/= :: SchedulingPolicy -> SchedulingPolicy -> Bool
/= :: SchedulingPolicy -> SchedulingPolicy -> Bool
Prelude.Eq, Int -> SchedulingPolicy -> ShowS
[SchedulingPolicy] -> ShowS
SchedulingPolicy -> String
(Int -> SchedulingPolicy -> ShowS)
-> (SchedulingPolicy -> String)
-> ([SchedulingPolicy] -> ShowS)
-> Show SchedulingPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchedulingPolicy -> ShowS
showsPrec :: Int -> SchedulingPolicy -> ShowS
$cshow :: SchedulingPolicy -> String
show :: SchedulingPolicy -> String
$cshowList :: [SchedulingPolicy] -> ShowS
showList :: [SchedulingPolicy] -> ShowS
Prelude.Show)
mkSchedulingPolicy :: SchedulingPolicy
mkSchedulingPolicy :: SchedulingPolicy
mkSchedulingPolicy
  = SchedulingPolicy
      {haddock_workaround_ :: ()
haddock_workaround_ = (), fairsharePolicy :: Maybe FairsharePolicyProperty
fairsharePolicy = Maybe FairsharePolicyProperty
forall a. Maybe a
Prelude.Nothing,
       name :: Maybe (Value Text)
name = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, tags :: Maybe (Map Text (Value Text))
tags = Maybe (Map Text (Value Text))
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SchedulingPolicy where
  toResourceProperties :: SchedulingPolicy -> ResourceProperties
toResourceProperties SchedulingPolicy {Maybe (Map Text (Value Text))
Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: SchedulingPolicy -> ()
fairsharePolicy :: SchedulingPolicy -> Maybe FairsharePolicyProperty
name :: SchedulingPolicy -> Maybe (Value Text)
tags :: SchedulingPolicy -> Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Batch::SchedulingPolicy",
         supportsTags :: Bool
supportsTags = Bool
Prelude.True,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [Key -> FairsharePolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FairsharePolicy" (FairsharePolicyProperty -> (Key, Value))
-> Maybe FairsharePolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FairsharePolicyProperty
fairsharePolicy,
                            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..=) Key
"Name" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
name,
                            Key -> Map Text (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..=) Key
"Tags" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
tags])}
instance JSON.ToJSON SchedulingPolicy where
  toJSON :: SchedulingPolicy -> Value
toJSON SchedulingPolicy {Maybe (Map Text (Value Text))
Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: SchedulingPolicy -> ()
fairsharePolicy :: SchedulingPolicy -> Maybe FairsharePolicyProperty
name :: SchedulingPolicy -> Maybe (Value Text)
tags :: SchedulingPolicy -> Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [Key -> FairsharePolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FairsharePolicy" (FairsharePolicyProperty -> (Key, Value))
-> Maybe FairsharePolicyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FairsharePolicyProperty
fairsharePolicy,
               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..=) Key
"Name" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
name,
               Key -> Map Text (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..=) Key
"Tags" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
tags]))
instance Property "FairsharePolicy" SchedulingPolicy where
  type PropertyType "FairsharePolicy" SchedulingPolicy = FairsharePolicyProperty
  set :: PropertyType "FairsharePolicy" SchedulingPolicy
-> SchedulingPolicy -> SchedulingPolicy
set PropertyType "FairsharePolicy" SchedulingPolicy
newValue SchedulingPolicy {Maybe (Map Text (Value Text))
Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: SchedulingPolicy -> ()
fairsharePolicy :: SchedulingPolicy -> Maybe FairsharePolicyProperty
name :: SchedulingPolicy -> Maybe (Value Text)
tags :: SchedulingPolicy -> Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
    = SchedulingPolicy {fairsharePolicy :: Maybe FairsharePolicyProperty
fairsharePolicy = FairsharePolicyProperty -> Maybe FairsharePolicyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FairsharePolicy" SchedulingPolicy
FairsharePolicyProperty
newValue, Maybe (Map Text (Value Text))
Maybe (Value Text)
()
haddock_workaround_ :: ()
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
instance Property "Name" SchedulingPolicy where
  type PropertyType "Name" SchedulingPolicy = Value Prelude.Text
  set :: PropertyType "Name" SchedulingPolicy
-> SchedulingPolicy -> SchedulingPolicy
set PropertyType "Name" SchedulingPolicy
newValue SchedulingPolicy {Maybe (Map Text (Value Text))
Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: SchedulingPolicy -> ()
fairsharePolicy :: SchedulingPolicy -> Maybe FairsharePolicyProperty
name :: SchedulingPolicy -> Maybe (Value Text)
tags :: SchedulingPolicy -> Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
    = SchedulingPolicy {name :: Maybe (Value Text)
name = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Name" SchedulingPolicy
Value Text
newValue, Maybe (Map Text (Value Text))
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
tags :: Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
tags :: Maybe (Map Text (Value Text))
..}
instance Property "Tags" SchedulingPolicy where
  type PropertyType "Tags" SchedulingPolicy = Prelude.Map Prelude.Text (Value Prelude.Text)
  set :: PropertyType "Tags" SchedulingPolicy
-> SchedulingPolicy -> SchedulingPolicy
set PropertyType "Tags" SchedulingPolicy
newValue SchedulingPolicy {Maybe (Map Text (Value Text))
Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: SchedulingPolicy -> ()
fairsharePolicy :: SchedulingPolicy -> Maybe FairsharePolicyProperty
name :: SchedulingPolicy -> Maybe (Value Text)
tags :: SchedulingPolicy -> Maybe (Map Text (Value Text))
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
tags :: Maybe (Map Text (Value Text))
..}
    = SchedulingPolicy {tags :: Maybe (Map Text (Value Text))
tags = Map Text (Value Text) -> Maybe (Map Text (Value Text))
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Map Text (Value Text)
PropertyType "Tags" SchedulingPolicy
newValue, Maybe (Value Text)
Maybe FairsharePolicyProperty
()
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
haddock_workaround_ :: ()
fairsharePolicy :: Maybe FairsharePolicyProperty
name :: Maybe (Value Text)
..}