module Stratosphere.CodeBuild.Project.GitSubmodulesConfigProperty (
GitSubmodulesConfigProperty(..), mkGitSubmodulesConfigProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data GitSubmodulesConfigProperty
=
GitSubmodulesConfigProperty {GitSubmodulesConfigProperty -> ()
haddock_workaround_ :: (),
GitSubmodulesConfigProperty -> Value Bool
fetchSubmodules :: (Value Prelude.Bool)}
deriving stock (GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty -> Bool
(GitSubmodulesConfigProperty
-> GitSubmodulesConfigProperty -> Bool)
-> (GitSubmodulesConfigProperty
-> GitSubmodulesConfigProperty -> Bool)
-> Eq GitSubmodulesConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty -> Bool
== :: GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty -> Bool
$c/= :: GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty -> Bool
/= :: GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty -> Bool
Prelude.Eq, Int -> GitSubmodulesConfigProperty -> ShowS
[GitSubmodulesConfigProperty] -> ShowS
GitSubmodulesConfigProperty -> String
(Int -> GitSubmodulesConfigProperty -> ShowS)
-> (GitSubmodulesConfigProperty -> String)
-> ([GitSubmodulesConfigProperty] -> ShowS)
-> Show GitSubmodulesConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GitSubmodulesConfigProperty -> ShowS
showsPrec :: Int -> GitSubmodulesConfigProperty -> ShowS
$cshow :: GitSubmodulesConfigProperty -> String
show :: GitSubmodulesConfigProperty -> String
$cshowList :: [GitSubmodulesConfigProperty] -> ShowS
showList :: [GitSubmodulesConfigProperty] -> ShowS
Prelude.Show)
mkGitSubmodulesConfigProperty ::
Value Prelude.Bool -> GitSubmodulesConfigProperty
mkGitSubmodulesConfigProperty :: Value Bool -> GitSubmodulesConfigProperty
mkGitSubmodulesConfigProperty Value Bool
fetchSubmodules
= GitSubmodulesConfigProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), fetchSubmodules :: Value Bool
fetchSubmodules = Value Bool
fetchSubmodules}
instance ToResourceProperties GitSubmodulesConfigProperty where
toResourceProperties :: GitSubmodulesConfigProperty -> ResourceProperties
toResourceProperties GitSubmodulesConfigProperty {()
Value Bool
haddock_workaround_ :: GitSubmodulesConfigProperty -> ()
fetchSubmodules :: GitSubmodulesConfigProperty -> Value Bool
haddock_workaround_ :: ()
fetchSubmodules :: Value Bool
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::CodeBuild::Project.GitSubmodulesConfig",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"FetchSubmodules" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
fetchSubmodules]}
instance JSON.ToJSON GitSubmodulesConfigProperty where
toJSON :: GitSubmodulesConfigProperty -> Value
toJSON GitSubmodulesConfigProperty {()
Value Bool
haddock_workaround_ :: GitSubmodulesConfigProperty -> ()
fetchSubmodules :: GitSubmodulesConfigProperty -> Value Bool
haddock_workaround_ :: ()
fetchSubmodules :: Value Bool
..}
= [(Key, Value)] -> Value
JSON.object [Key
"FetchSubmodules" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
fetchSubmodules]
instance Property "FetchSubmodules" GitSubmodulesConfigProperty where
type PropertyType "FetchSubmodules" GitSubmodulesConfigProperty = Value Prelude.Bool
set :: PropertyType "FetchSubmodules" GitSubmodulesConfigProperty
-> GitSubmodulesConfigProperty -> GitSubmodulesConfigProperty
set PropertyType "FetchSubmodules" GitSubmodulesConfigProperty
newValue GitSubmodulesConfigProperty {()
Value Bool
haddock_workaround_ :: GitSubmodulesConfigProperty -> ()
fetchSubmodules :: GitSubmodulesConfigProperty -> Value Bool
haddock_workaround_ :: ()
fetchSubmodules :: Value Bool
..}
= GitSubmodulesConfigProperty {fetchSubmodules :: Value Bool
fetchSubmodules = PropertyType "FetchSubmodules" GitSubmodulesConfigProperty
Value Bool
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}