module Stratosphere.Lambda.Permission (
Permission(..), mkPermission
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data Permission
=
Permission {Permission -> ()
haddock_workaround_ :: (),
Permission -> Value Text
action :: (Value Prelude.Text),
Permission -> Maybe (Value Text)
eventSourceToken :: (Prelude.Maybe (Value Prelude.Text)),
Permission -> Value Text
functionName :: (Value Prelude.Text),
Permission -> Maybe (Value Text)
functionUrlAuthType :: (Prelude.Maybe (Value Prelude.Text)),
Permission -> Maybe (Value Bool)
invokedViaFunctionUrl :: (Prelude.Maybe (Value Prelude.Bool)),
Permission -> Value Text
principal :: (Value Prelude.Text),
Permission -> Maybe (Value Text)
principalOrgID :: (Prelude.Maybe (Value Prelude.Text)),
Permission -> Maybe (Value Text)
sourceAccount :: (Prelude.Maybe (Value Prelude.Text)),
Permission -> Maybe (Value Text)
sourceArn :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (Permission -> Permission -> Bool
(Permission -> Permission -> Bool)
-> (Permission -> Permission -> Bool) -> Eq Permission
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Permission -> Permission -> Bool
== :: Permission -> Permission -> Bool
$c/= :: Permission -> Permission -> Bool
/= :: Permission -> Permission -> Bool
Prelude.Eq, Int -> Permission -> ShowS
[Permission] -> ShowS
Permission -> String
(Int -> Permission -> ShowS)
-> (Permission -> String)
-> ([Permission] -> ShowS)
-> Show Permission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Permission -> ShowS
showsPrec :: Int -> Permission -> ShowS
$cshow :: Permission -> String
show :: Permission -> String
$cshowList :: [Permission] -> ShowS
showList :: [Permission] -> ShowS
Prelude.Show)
mkPermission ::
Value Prelude.Text
-> Value Prelude.Text -> Value Prelude.Text -> Permission
mkPermission :: Value Text -> Value Text -> Value Text -> Permission
mkPermission Value Text
action Value Text
functionName Value Text
principal
= Permission
{haddock_workaround_ :: ()
haddock_workaround_ = (), action :: Value Text
action = Value Text
action,
functionName :: Value Text
functionName = Value Text
functionName, principal :: Value Text
principal = Value Text
principal,
eventSourceToken :: Maybe (Value Text)
eventSourceToken = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
functionUrlAuthType :: Maybe (Value Text)
functionUrlAuthType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
invokedViaFunctionUrl :: Maybe (Value Bool)
invokedViaFunctionUrl = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
principalOrgID :: Maybe (Value Text)
principalOrgID = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, sourceAccount :: Maybe (Value Text)
sourceAccount = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
sourceArn :: Maybe (Value Text)
sourceArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Permission where
toResourceProperties :: Permission -> ResourceProperties
toResourceProperties Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Lambda::Permission", supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Action" 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
action, Key
"FunctionName" 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
functionName,
Key
"Principal" 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
principal]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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
"EventSourceToken" (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)
eventSourceToken,
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
"FunctionUrlAuthType" (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)
functionUrlAuthType,
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..=) Key
"InvokedViaFunctionUrl"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
invokedViaFunctionUrl,
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
"PrincipalOrgID" (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)
principalOrgID,
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
"SourceAccount" (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)
sourceAccount,
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
"SourceArn" (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)
sourceArn]))}
instance JSON.ToJSON Permission where
toJSON :: Permission -> Value
toJSON Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Action" 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
action, Key
"FunctionName" 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
functionName,
Key
"Principal" 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
principal]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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
"EventSourceToken" (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)
eventSourceToken,
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
"FunctionUrlAuthType" (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)
functionUrlAuthType,
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..=) Key
"InvokedViaFunctionUrl"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
invokedViaFunctionUrl,
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
"PrincipalOrgID" (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)
principalOrgID,
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
"SourceAccount" (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)
sourceAccount,
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
"SourceArn" (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)
sourceArn])))
instance Property "Action" Permission where
type PropertyType "Action" Permission = Value Prelude.Text
set :: PropertyType "Action" Permission -> Permission -> Permission
set PropertyType "Action" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..} = Permission {action :: Value Text
action = PropertyType "Action" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "EventSourceToken" Permission where
type PropertyType "EventSourceToken" Permission = Value Prelude.Text
set :: PropertyType "EventSourceToken" Permission
-> Permission -> Permission
set PropertyType "EventSourceToken" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {eventSourceToken :: Maybe (Value Text)
eventSourceToken = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EventSourceToken" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "FunctionName" Permission where
type PropertyType "FunctionName" Permission = Value Prelude.Text
set :: PropertyType "FunctionName" Permission -> Permission -> Permission
set PropertyType "FunctionName" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {functionName :: Value Text
functionName = PropertyType "FunctionName" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "FunctionUrlAuthType" Permission where
type PropertyType "FunctionUrlAuthType" Permission = Value Prelude.Text
set :: PropertyType "FunctionUrlAuthType" Permission
-> Permission -> Permission
set PropertyType "FunctionUrlAuthType" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {functionUrlAuthType :: Maybe (Value Text)
functionUrlAuthType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FunctionUrlAuthType" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "InvokedViaFunctionUrl" Permission where
type PropertyType "InvokedViaFunctionUrl" Permission = Value Prelude.Bool
set :: PropertyType "InvokedViaFunctionUrl" Permission
-> Permission -> Permission
set PropertyType "InvokedViaFunctionUrl" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {invokedViaFunctionUrl :: Maybe (Value Bool)
invokedViaFunctionUrl = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InvokedViaFunctionUrl" Permission
Value Bool
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "Principal" Permission where
type PropertyType "Principal" Permission = Value Prelude.Text
set :: PropertyType "Principal" Permission -> Permission -> Permission
set PropertyType "Principal" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {principal :: Value Text
principal = PropertyType "Principal" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "PrincipalOrgID" Permission where
type PropertyType "PrincipalOrgID" Permission = Value Prelude.Text
set :: PropertyType "PrincipalOrgID" Permission
-> Permission -> Permission
set PropertyType "PrincipalOrgID" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {principalOrgID :: Maybe (Value Text)
principalOrgID = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PrincipalOrgID" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "SourceAccount" Permission where
type PropertyType "SourceAccount" Permission = Value Prelude.Text
set :: PropertyType "SourceAccount" Permission -> Permission -> Permission
set PropertyType "SourceAccount" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {sourceAccount :: Maybe (Value Text)
sourceAccount = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SourceAccount" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
instance Property "SourceArn" Permission where
type PropertyType "SourceArn" Permission = Value Prelude.Text
set :: PropertyType "SourceArn" Permission -> Permission -> Permission
set PropertyType "SourceArn" Permission
newValue Permission {Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Permission -> ()
action :: Permission -> Value Text
eventSourceToken :: Permission -> Maybe (Value Text)
functionName :: Permission -> Value Text
functionUrlAuthType :: Permission -> Maybe (Value Text)
invokedViaFunctionUrl :: Permission -> Maybe (Value Bool)
principal :: Permission -> Value Text
principalOrgID :: Permission -> Maybe (Value Text)
sourceAccount :: Permission -> Maybe (Value Text)
sourceArn :: Permission -> Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
sourceArn :: Maybe (Value Text)
..}
= Permission {sourceArn :: Maybe (Value Text)
sourceArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SourceArn" Permission
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
haddock_workaround_ :: ()
action :: Value Text
eventSourceToken :: Maybe (Value Text)
functionName :: Value Text
functionUrlAuthType :: Maybe (Value Text)
invokedViaFunctionUrl :: Maybe (Value Bool)
principal :: Value Text
principalOrgID :: Maybe (Value Text)
sourceAccount :: Maybe (Value Text)
..}