{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.MediaLive.UpdateInput
(
UpdateInput' (..),
newUpdateInput',
updateInput'_destinations,
updateInput'_inputDevices,
updateInput'_inputSecurityGroups,
updateInput'_mediaConnectFlows,
updateInput'_name,
updateInput'_roleArn,
updateInput'_sources,
updateInput'_inputId,
UpdateInputResponse (..),
newUpdateInputResponse,
updateInputResponse_input,
updateInputResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data UpdateInput' = UpdateInput''
{
UpdateInput' -> Maybe [InputDestinationRequest]
destinations :: Prelude.Maybe [InputDestinationRequest],
UpdateInput' -> Maybe [InputDeviceRequest]
inputDevices :: Prelude.Maybe [InputDeviceRequest],
UpdateInput' -> Maybe [Text]
inputSecurityGroups :: Prelude.Maybe [Prelude.Text],
UpdateInput' -> Maybe [MediaConnectFlowRequest]
mediaConnectFlows :: Prelude.Maybe [MediaConnectFlowRequest],
UpdateInput' -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateInput' -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
UpdateInput' -> Maybe [InputSourceRequest]
sources :: Prelude.Maybe [InputSourceRequest],
UpdateInput' -> Text
inputId :: Prelude.Text
}
deriving (UpdateInput' -> UpdateInput' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateInput' -> UpdateInput' -> Bool
$c/= :: UpdateInput' -> UpdateInput' -> Bool
== :: UpdateInput' -> UpdateInput' -> Bool
$c== :: UpdateInput' -> UpdateInput' -> Bool
Prelude.Eq, ReadPrec [UpdateInput']
ReadPrec UpdateInput'
Int -> ReadS UpdateInput'
ReadS [UpdateInput']
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateInput']
$creadListPrec :: ReadPrec [UpdateInput']
readPrec :: ReadPrec UpdateInput'
$creadPrec :: ReadPrec UpdateInput'
readList :: ReadS [UpdateInput']
$creadList :: ReadS [UpdateInput']
readsPrec :: Int -> ReadS UpdateInput'
$creadsPrec :: Int -> ReadS UpdateInput'
Prelude.Read, Int -> UpdateInput' -> ShowS
[UpdateInput'] -> ShowS
UpdateInput' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateInput'] -> ShowS
$cshowList :: [UpdateInput'] -> ShowS
show :: UpdateInput' -> String
$cshow :: UpdateInput' -> String
showsPrec :: Int -> UpdateInput' -> ShowS
$cshowsPrec :: Int -> UpdateInput' -> ShowS
Prelude.Show, forall x. Rep UpdateInput' x -> UpdateInput'
forall x. UpdateInput' -> Rep UpdateInput' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateInput' x -> UpdateInput'
$cfrom :: forall x. UpdateInput' -> Rep UpdateInput' x
Prelude.Generic)
newUpdateInput' ::
Prelude.Text ->
UpdateInput'
newUpdateInput' :: Text -> UpdateInput'
newUpdateInput' Text
pInputId_ =
UpdateInput''
{ $sel:destinations:UpdateInput'' :: Maybe [InputDestinationRequest]
destinations = forall a. Maybe a
Prelude.Nothing,
$sel:inputDevices:UpdateInput'' :: Maybe [InputDeviceRequest]
inputDevices = forall a. Maybe a
Prelude.Nothing,
$sel:inputSecurityGroups:UpdateInput'' :: Maybe [Text]
inputSecurityGroups = forall a. Maybe a
Prelude.Nothing,
$sel:mediaConnectFlows:UpdateInput'' :: Maybe [MediaConnectFlowRequest]
mediaConnectFlows = forall a. Maybe a
Prelude.Nothing,
$sel:name:UpdateInput'' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:roleArn:UpdateInput'' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
$sel:sources:UpdateInput'' :: Maybe [InputSourceRequest]
sources = forall a. Maybe a
Prelude.Nothing,
$sel:inputId:UpdateInput'' :: Text
inputId = Text
pInputId_
}
updateInput'_destinations :: Lens.Lens' UpdateInput' (Prelude.Maybe [InputDestinationRequest])
updateInput'_destinations :: Lens' UpdateInput' (Maybe [InputDestinationRequest])
updateInput'_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe [InputDestinationRequest]
destinations :: Maybe [InputDestinationRequest]
$sel:destinations:UpdateInput'' :: UpdateInput' -> Maybe [InputDestinationRequest]
destinations} -> Maybe [InputDestinationRequest]
destinations) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe [InputDestinationRequest]
a -> UpdateInput'
s {$sel:destinations:UpdateInput'' :: Maybe [InputDestinationRequest]
destinations = Maybe [InputDestinationRequest]
a} :: UpdateInput') forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateInput'_inputDevices :: Lens.Lens' UpdateInput' (Prelude.Maybe [InputDeviceRequest])
updateInput'_inputDevices :: Lens' UpdateInput' (Maybe [InputDeviceRequest])
updateInput'_inputDevices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe [InputDeviceRequest]
inputDevices :: Maybe [InputDeviceRequest]
$sel:inputDevices:UpdateInput'' :: UpdateInput' -> Maybe [InputDeviceRequest]
inputDevices} -> Maybe [InputDeviceRequest]
inputDevices) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe [InputDeviceRequest]
a -> UpdateInput'
s {$sel:inputDevices:UpdateInput'' :: Maybe [InputDeviceRequest]
inputDevices = Maybe [InputDeviceRequest]
a} :: UpdateInput') forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateInput'_inputSecurityGroups :: Lens.Lens' UpdateInput' (Prelude.Maybe [Prelude.Text])
updateInput'_inputSecurityGroups :: Lens' UpdateInput' (Maybe [Text])
updateInput'_inputSecurityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe [Text]
inputSecurityGroups :: Maybe [Text]
$sel:inputSecurityGroups:UpdateInput'' :: UpdateInput' -> Maybe [Text]
inputSecurityGroups} -> Maybe [Text]
inputSecurityGroups) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe [Text]
a -> UpdateInput'
s {$sel:inputSecurityGroups:UpdateInput'' :: Maybe [Text]
inputSecurityGroups = Maybe [Text]
a} :: UpdateInput') forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateInput'_mediaConnectFlows :: Lens.Lens' UpdateInput' (Prelude.Maybe [MediaConnectFlowRequest])
updateInput'_mediaConnectFlows :: Lens' UpdateInput' (Maybe [MediaConnectFlowRequest])
updateInput'_mediaConnectFlows = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe [MediaConnectFlowRequest]
mediaConnectFlows :: Maybe [MediaConnectFlowRequest]
$sel:mediaConnectFlows:UpdateInput'' :: UpdateInput' -> Maybe [MediaConnectFlowRequest]
mediaConnectFlows} -> Maybe [MediaConnectFlowRequest]
mediaConnectFlows) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe [MediaConnectFlowRequest]
a -> UpdateInput'
s {$sel:mediaConnectFlows:UpdateInput'' :: Maybe [MediaConnectFlowRequest]
mediaConnectFlows = Maybe [MediaConnectFlowRequest]
a} :: UpdateInput') forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateInput'_name :: Lens.Lens' UpdateInput' (Prelude.Maybe Prelude.Text)
updateInput'_name :: Lens' UpdateInput' (Maybe Text)
updateInput'_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe Text
name :: Maybe Text
$sel:name:UpdateInput'' :: UpdateInput' -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe Text
a -> UpdateInput'
s {$sel:name:UpdateInput'' :: Maybe Text
name = Maybe Text
a} :: UpdateInput')
updateInput'_roleArn :: Lens.Lens' UpdateInput' (Prelude.Maybe Prelude.Text)
updateInput'_roleArn :: Lens' UpdateInput' (Maybe Text)
updateInput'_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateInput'' :: UpdateInput' -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe Text
a -> UpdateInput'
s {$sel:roleArn:UpdateInput'' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateInput')
updateInput'_sources :: Lens.Lens' UpdateInput' (Prelude.Maybe [InputSourceRequest])
updateInput'_sources :: Lens' UpdateInput' (Maybe [InputSourceRequest])
updateInput'_sources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Maybe [InputSourceRequest]
sources :: Maybe [InputSourceRequest]
$sel:sources:UpdateInput'' :: UpdateInput' -> Maybe [InputSourceRequest]
sources} -> Maybe [InputSourceRequest]
sources) (\s :: UpdateInput'
s@UpdateInput'' {} Maybe [InputSourceRequest]
a -> UpdateInput'
s {$sel:sources:UpdateInput'' :: Maybe [InputSourceRequest]
sources = Maybe [InputSourceRequest]
a} :: UpdateInput') forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateInput'_inputId :: Lens.Lens' UpdateInput' Prelude.Text
updateInput'_inputId :: Lens' UpdateInput' Text
updateInput'_inputId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInput'' {Text
inputId :: Text
$sel:inputId:UpdateInput'' :: UpdateInput' -> Text
inputId} -> Text
inputId) (\s :: UpdateInput'
s@UpdateInput'' {} Text
a -> UpdateInput'
s {$sel:inputId:UpdateInput'' :: Text
inputId = Text
a} :: UpdateInput')
instance Core.AWSRequest UpdateInput' where
type AWSResponse UpdateInput' = UpdateInputResponse
request :: (Service -> Service) -> UpdateInput' -> Request UpdateInput'
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateInput'
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateInput')))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe Input -> Int -> UpdateInputResponse
UpdateInputResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"input")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable UpdateInput' where
hashWithSalt :: Int -> UpdateInput' -> Int
hashWithSalt Int
_salt UpdateInput'' {Maybe [Text]
Maybe [InputDestinationRequest]
Maybe [InputDeviceRequest]
Maybe [InputSourceRequest]
Maybe [MediaConnectFlowRequest]
Maybe Text
Text
inputId :: Text
sources :: Maybe [InputSourceRequest]
roleArn :: Maybe Text
name :: Maybe Text
mediaConnectFlows :: Maybe [MediaConnectFlowRequest]
inputSecurityGroups :: Maybe [Text]
inputDevices :: Maybe [InputDeviceRequest]
destinations :: Maybe [InputDestinationRequest]
$sel:inputId:UpdateInput'' :: UpdateInput' -> Text
$sel:sources:UpdateInput'' :: UpdateInput' -> Maybe [InputSourceRequest]
$sel:roleArn:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:name:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:mediaConnectFlows:UpdateInput'' :: UpdateInput' -> Maybe [MediaConnectFlowRequest]
$sel:inputSecurityGroups:UpdateInput'' :: UpdateInput' -> Maybe [Text]
$sel:inputDevices:UpdateInput'' :: UpdateInput' -> Maybe [InputDeviceRequest]
$sel:destinations:UpdateInput'' :: UpdateInput' -> Maybe [InputDestinationRequest]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InputDestinationRequest]
destinations
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InputDeviceRequest]
inputDevices
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
inputSecurityGroups
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MediaConnectFlowRequest]
mediaConnectFlows
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InputSourceRequest]
sources
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
inputId
instance Prelude.NFData UpdateInput' where
rnf :: UpdateInput' -> ()
rnf UpdateInput'' {Maybe [Text]
Maybe [InputDestinationRequest]
Maybe [InputDeviceRequest]
Maybe [InputSourceRequest]
Maybe [MediaConnectFlowRequest]
Maybe Text
Text
inputId :: Text
sources :: Maybe [InputSourceRequest]
roleArn :: Maybe Text
name :: Maybe Text
mediaConnectFlows :: Maybe [MediaConnectFlowRequest]
inputSecurityGroups :: Maybe [Text]
inputDevices :: Maybe [InputDeviceRequest]
destinations :: Maybe [InputDestinationRequest]
$sel:inputId:UpdateInput'' :: UpdateInput' -> Text
$sel:sources:UpdateInput'' :: UpdateInput' -> Maybe [InputSourceRequest]
$sel:roleArn:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:name:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:mediaConnectFlows:UpdateInput'' :: UpdateInput' -> Maybe [MediaConnectFlowRequest]
$sel:inputSecurityGroups:UpdateInput'' :: UpdateInput' -> Maybe [Text]
$sel:inputDevices:UpdateInput'' :: UpdateInput' -> Maybe [InputDeviceRequest]
$sel:destinations:UpdateInput'' :: UpdateInput' -> Maybe [InputDestinationRequest]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputDestinationRequest]
destinations
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputDeviceRequest]
inputDevices
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
inputSecurityGroups
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MediaConnectFlowRequest]
mediaConnectFlows
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputSourceRequest]
sources
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
inputId
instance Data.ToHeaders UpdateInput' where
toHeaders :: UpdateInput' -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON UpdateInput' where
toJSON :: UpdateInput' -> Value
toJSON UpdateInput'' {Maybe [Text]
Maybe [InputDestinationRequest]
Maybe [InputDeviceRequest]
Maybe [InputSourceRequest]
Maybe [MediaConnectFlowRequest]
Maybe Text
Text
inputId :: Text
sources :: Maybe [InputSourceRequest]
roleArn :: Maybe Text
name :: Maybe Text
mediaConnectFlows :: Maybe [MediaConnectFlowRequest]
inputSecurityGroups :: Maybe [Text]
inputDevices :: Maybe [InputDeviceRequest]
destinations :: Maybe [InputDestinationRequest]
$sel:inputId:UpdateInput'' :: UpdateInput' -> Text
$sel:sources:UpdateInput'' :: UpdateInput' -> Maybe [InputSourceRequest]
$sel:roleArn:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:name:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:mediaConnectFlows:UpdateInput'' :: UpdateInput' -> Maybe [MediaConnectFlowRequest]
$sel:inputSecurityGroups:UpdateInput'' :: UpdateInput' -> Maybe [Text]
$sel:inputDevices:UpdateInput'' :: UpdateInput' -> Maybe [InputDeviceRequest]
$sel:destinations:UpdateInput'' :: UpdateInput' -> Maybe [InputDestinationRequest]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"destinations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InputDestinationRequest]
destinations,
(Key
"inputDevices" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InputDeviceRequest]
inputDevices,
(Key
"inputSecurityGroups" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
inputSecurityGroups,
(Key
"mediaConnectFlows" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [MediaConnectFlowRequest]
mediaConnectFlows,
(Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
(Key
"roleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
roleArn,
(Key
"sources" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InputSourceRequest]
sources
]
)
instance Data.ToPath UpdateInput' where
toPath :: UpdateInput' -> ByteString
toPath UpdateInput'' {Maybe [Text]
Maybe [InputDestinationRequest]
Maybe [InputDeviceRequest]
Maybe [InputSourceRequest]
Maybe [MediaConnectFlowRequest]
Maybe Text
Text
inputId :: Text
sources :: Maybe [InputSourceRequest]
roleArn :: Maybe Text
name :: Maybe Text
mediaConnectFlows :: Maybe [MediaConnectFlowRequest]
inputSecurityGroups :: Maybe [Text]
inputDevices :: Maybe [InputDeviceRequest]
destinations :: Maybe [InputDestinationRequest]
$sel:inputId:UpdateInput'' :: UpdateInput' -> Text
$sel:sources:UpdateInput'' :: UpdateInput' -> Maybe [InputSourceRequest]
$sel:roleArn:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:name:UpdateInput'' :: UpdateInput' -> Maybe Text
$sel:mediaConnectFlows:UpdateInput'' :: UpdateInput' -> Maybe [MediaConnectFlowRequest]
$sel:inputSecurityGroups:UpdateInput'' :: UpdateInput' -> Maybe [Text]
$sel:inputDevices:UpdateInput'' :: UpdateInput' -> Maybe [InputDeviceRequest]
$sel:destinations:UpdateInput'' :: UpdateInput' -> Maybe [InputDestinationRequest]
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/prod/inputs/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
inputId]
instance Data.ToQuery UpdateInput' where
toQuery :: UpdateInput' -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateInputResponse = UpdateInputResponse'
{ UpdateInputResponse -> Maybe Input
input :: Prelude.Maybe Input,
UpdateInputResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateInputResponse -> UpdateInputResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateInputResponse -> UpdateInputResponse -> Bool
$c/= :: UpdateInputResponse -> UpdateInputResponse -> Bool
== :: UpdateInputResponse -> UpdateInputResponse -> Bool
$c== :: UpdateInputResponse -> UpdateInputResponse -> Bool
Prelude.Eq, ReadPrec [UpdateInputResponse]
ReadPrec UpdateInputResponse
Int -> ReadS UpdateInputResponse
ReadS [UpdateInputResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateInputResponse]
$creadListPrec :: ReadPrec [UpdateInputResponse]
readPrec :: ReadPrec UpdateInputResponse
$creadPrec :: ReadPrec UpdateInputResponse
readList :: ReadS [UpdateInputResponse]
$creadList :: ReadS [UpdateInputResponse]
readsPrec :: Int -> ReadS UpdateInputResponse
$creadsPrec :: Int -> ReadS UpdateInputResponse
Prelude.Read, Int -> UpdateInputResponse -> ShowS
[UpdateInputResponse] -> ShowS
UpdateInputResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateInputResponse] -> ShowS
$cshowList :: [UpdateInputResponse] -> ShowS
show :: UpdateInputResponse -> String
$cshow :: UpdateInputResponse -> String
showsPrec :: Int -> UpdateInputResponse -> ShowS
$cshowsPrec :: Int -> UpdateInputResponse -> ShowS
Prelude.Show, forall x. Rep UpdateInputResponse x -> UpdateInputResponse
forall x. UpdateInputResponse -> Rep UpdateInputResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateInputResponse x -> UpdateInputResponse
$cfrom :: forall x. UpdateInputResponse -> Rep UpdateInputResponse x
Prelude.Generic)
newUpdateInputResponse ::
Prelude.Int ->
UpdateInputResponse
newUpdateInputResponse :: Int -> UpdateInputResponse
newUpdateInputResponse Int
pHttpStatus_ =
UpdateInputResponse'
{ $sel:input:UpdateInputResponse' :: Maybe Input
input = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateInputResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateInputResponse_input :: Lens.Lens' UpdateInputResponse (Prelude.Maybe Input)
updateInputResponse_input :: Lens' UpdateInputResponse (Maybe Input)
updateInputResponse_input = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputResponse' {Maybe Input
input :: Maybe Input
$sel:input:UpdateInputResponse' :: UpdateInputResponse -> Maybe Input
input} -> Maybe Input
input) (\s :: UpdateInputResponse
s@UpdateInputResponse' {} Maybe Input
a -> UpdateInputResponse
s {$sel:input:UpdateInputResponse' :: Maybe Input
input = Maybe Input
a} :: UpdateInputResponse)
updateInputResponse_httpStatus :: Lens.Lens' UpdateInputResponse Prelude.Int
updateInputResponse_httpStatus :: Lens' UpdateInputResponse Int
updateInputResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateInputResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateInputResponse' :: UpdateInputResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateInputResponse
s@UpdateInputResponse' {} Int
a -> UpdateInputResponse
s {$sel:httpStatus:UpdateInputResponse' :: Int
httpStatus = Int
a} :: UpdateInputResponse)
instance Prelude.NFData UpdateInputResponse where
rnf :: UpdateInputResponse -> ()
rnf UpdateInputResponse' {Int
Maybe Input
httpStatus :: Int
input :: Maybe Input
$sel:httpStatus:UpdateInputResponse' :: UpdateInputResponse -> Int
$sel:input:UpdateInputResponse' :: UpdateInputResponse -> Maybe Input
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Input
input
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus