{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.DataBrew.UpdateRecipe
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the definition of the @LATEST_WORKING@ version of a DataBrew
-- recipe.
module Amazonka.DataBrew.UpdateRecipe
  ( -- * Creating a Request
    UpdateRecipe (..),
    newUpdateRecipe,

    -- * Request Lenses
    updateRecipe_description,
    updateRecipe_steps,
    updateRecipe_name,

    -- * Destructuring the Response
    UpdateRecipeResponse (..),
    newUpdateRecipeResponse,

    -- * Response Lenses
    updateRecipeResponse_httpStatus,
    updateRecipeResponse_name,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataBrew.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateRecipe' smart constructor.
data UpdateRecipe = UpdateRecipe'
  { -- | A description of the recipe.
    UpdateRecipe -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | One or more steps to be performed by the recipe. Each step consists of
    -- an action, and the conditions under which the action should succeed.
    UpdateRecipe -> Maybe [RecipeStep]
steps :: Prelude.Maybe [RecipeStep],
    -- | The name of the recipe to be updated.
    UpdateRecipe -> Text
name :: Prelude.Text
  }
  deriving (UpdateRecipe -> UpdateRecipe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecipe -> UpdateRecipe -> Bool
$c/= :: UpdateRecipe -> UpdateRecipe -> Bool
== :: UpdateRecipe -> UpdateRecipe -> Bool
$c== :: UpdateRecipe -> UpdateRecipe -> Bool
Prelude.Eq, ReadPrec [UpdateRecipe]
ReadPrec UpdateRecipe
Int -> ReadS UpdateRecipe
ReadS [UpdateRecipe]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecipe]
$creadListPrec :: ReadPrec [UpdateRecipe]
readPrec :: ReadPrec UpdateRecipe
$creadPrec :: ReadPrec UpdateRecipe
readList :: ReadS [UpdateRecipe]
$creadList :: ReadS [UpdateRecipe]
readsPrec :: Int -> ReadS UpdateRecipe
$creadsPrec :: Int -> ReadS UpdateRecipe
Prelude.Read, Int -> UpdateRecipe -> ShowS
[UpdateRecipe] -> ShowS
UpdateRecipe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecipe] -> ShowS
$cshowList :: [UpdateRecipe] -> ShowS
show :: UpdateRecipe -> String
$cshow :: UpdateRecipe -> String
showsPrec :: Int -> UpdateRecipe -> ShowS
$cshowsPrec :: Int -> UpdateRecipe -> ShowS
Prelude.Show, forall x. Rep UpdateRecipe x -> UpdateRecipe
forall x. UpdateRecipe -> Rep UpdateRecipe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRecipe x -> UpdateRecipe
$cfrom :: forall x. UpdateRecipe -> Rep UpdateRecipe x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRecipe' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'description', 'updateRecipe_description' - A description of the recipe.
--
-- 'steps', 'updateRecipe_steps' - One or more steps to be performed by the recipe. Each step consists of
-- an action, and the conditions under which the action should succeed.
--
-- 'name', 'updateRecipe_name' - The name of the recipe to be updated.
newUpdateRecipe ::
  -- | 'name'
  Prelude.Text ->
  UpdateRecipe
newUpdateRecipe :: Text -> UpdateRecipe
newUpdateRecipe Text
pName_ =
  UpdateRecipe'
    { $sel:description:UpdateRecipe' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:steps:UpdateRecipe' :: Maybe [RecipeStep]
steps = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateRecipe' :: Text
name = Text
pName_
    }

-- | A description of the recipe.
updateRecipe_description :: Lens.Lens' UpdateRecipe (Prelude.Maybe Prelude.Text)
updateRecipe_description :: Lens' UpdateRecipe (Maybe Text)
updateRecipe_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecipe' {Maybe Text
description :: Maybe Text
$sel:description:UpdateRecipe' :: UpdateRecipe -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateRecipe
s@UpdateRecipe' {} Maybe Text
a -> UpdateRecipe
s {$sel:description:UpdateRecipe' :: Maybe Text
description = Maybe Text
a} :: UpdateRecipe)

-- | One or more steps to be performed by the recipe. Each step consists of
-- an action, and the conditions under which the action should succeed.
updateRecipe_steps :: Lens.Lens' UpdateRecipe (Prelude.Maybe [RecipeStep])
updateRecipe_steps :: Lens' UpdateRecipe (Maybe [RecipeStep])
updateRecipe_steps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecipe' {Maybe [RecipeStep]
steps :: Maybe [RecipeStep]
$sel:steps:UpdateRecipe' :: UpdateRecipe -> Maybe [RecipeStep]
steps} -> Maybe [RecipeStep]
steps) (\s :: UpdateRecipe
s@UpdateRecipe' {} Maybe [RecipeStep]
a -> UpdateRecipe
s {$sel:steps:UpdateRecipe' :: Maybe [RecipeStep]
steps = Maybe [RecipeStep]
a} :: UpdateRecipe) 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

-- | The name of the recipe to be updated.
updateRecipe_name :: Lens.Lens' UpdateRecipe Prelude.Text
updateRecipe_name :: Lens' UpdateRecipe Text
updateRecipe_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecipe' {Text
name :: Text
$sel:name:UpdateRecipe' :: UpdateRecipe -> Text
name} -> Text
name) (\s :: UpdateRecipe
s@UpdateRecipe' {} Text
a -> UpdateRecipe
s {$sel:name:UpdateRecipe' :: Text
name = Text
a} :: UpdateRecipe)

instance Core.AWSRequest UpdateRecipe where
  type AWSResponse UpdateRecipe = UpdateRecipeResponse
  request :: (Service -> Service) -> UpdateRecipe -> Request UpdateRecipe
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 UpdateRecipe
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateRecipe)))
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 ->
          Int -> Text -> UpdateRecipeResponse
UpdateRecipeResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Name")
      )

instance Prelude.Hashable UpdateRecipe where
  hashWithSalt :: Int -> UpdateRecipe -> Int
hashWithSalt Int
_salt UpdateRecipe' {Maybe [RecipeStep]
Maybe Text
Text
name :: Text
steps :: Maybe [RecipeStep]
description :: Maybe Text
$sel:name:UpdateRecipe' :: UpdateRecipe -> Text
$sel:steps:UpdateRecipe' :: UpdateRecipe -> Maybe [RecipeStep]
$sel:description:UpdateRecipe' :: UpdateRecipe -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [RecipeStep]
steps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData UpdateRecipe where
  rnf :: UpdateRecipe -> ()
rnf UpdateRecipe' {Maybe [RecipeStep]
Maybe Text
Text
name :: Text
steps :: Maybe [RecipeStep]
description :: Maybe Text
$sel:name:UpdateRecipe' :: UpdateRecipe -> Text
$sel:steps:UpdateRecipe' :: UpdateRecipe -> Maybe [RecipeStep]
$sel:description:UpdateRecipe' :: UpdateRecipe -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RecipeStep]
steps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders UpdateRecipe where
  toHeaders :: UpdateRecipe -> 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 UpdateRecipe where
  toJSON :: UpdateRecipe -> Value
toJSON UpdateRecipe' {Maybe [RecipeStep]
Maybe Text
Text
name :: Text
steps :: Maybe [RecipeStep]
description :: Maybe Text
$sel:name:UpdateRecipe' :: UpdateRecipe -> Text
$sel:steps:UpdateRecipe' :: UpdateRecipe -> Maybe [RecipeStep]
$sel:description:UpdateRecipe' :: UpdateRecipe -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"Steps" 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 [RecipeStep]
steps
          ]
      )

instance Data.ToPath UpdateRecipe where
  toPath :: UpdateRecipe -> ByteString
toPath UpdateRecipe' {Maybe [RecipeStep]
Maybe Text
Text
name :: Text
steps :: Maybe [RecipeStep]
description :: Maybe Text
$sel:name:UpdateRecipe' :: UpdateRecipe -> Text
$sel:steps:UpdateRecipe' :: UpdateRecipe -> Maybe [RecipeStep]
$sel:description:UpdateRecipe' :: UpdateRecipe -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/recipes/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

instance Data.ToQuery UpdateRecipe where
  toQuery :: UpdateRecipe -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateRecipeResponse' smart constructor.
data UpdateRecipeResponse = UpdateRecipeResponse'
  { -- | The response's http status code.
    UpdateRecipeResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the recipe that was updated.
    UpdateRecipeResponse -> Text
name :: Prelude.Text
  }
  deriving (UpdateRecipeResponse -> UpdateRecipeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRecipeResponse -> UpdateRecipeResponse -> Bool
$c/= :: UpdateRecipeResponse -> UpdateRecipeResponse -> Bool
== :: UpdateRecipeResponse -> UpdateRecipeResponse -> Bool
$c== :: UpdateRecipeResponse -> UpdateRecipeResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRecipeResponse]
ReadPrec UpdateRecipeResponse
Int -> ReadS UpdateRecipeResponse
ReadS [UpdateRecipeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRecipeResponse]
$creadListPrec :: ReadPrec [UpdateRecipeResponse]
readPrec :: ReadPrec UpdateRecipeResponse
$creadPrec :: ReadPrec UpdateRecipeResponse
readList :: ReadS [UpdateRecipeResponse]
$creadList :: ReadS [UpdateRecipeResponse]
readsPrec :: Int -> ReadS UpdateRecipeResponse
$creadsPrec :: Int -> ReadS UpdateRecipeResponse
Prelude.Read, Int -> UpdateRecipeResponse -> ShowS
[UpdateRecipeResponse] -> ShowS
UpdateRecipeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRecipeResponse] -> ShowS
$cshowList :: [UpdateRecipeResponse] -> ShowS
show :: UpdateRecipeResponse -> String
$cshow :: UpdateRecipeResponse -> String
showsPrec :: Int -> UpdateRecipeResponse -> ShowS
$cshowsPrec :: Int -> UpdateRecipeResponse -> ShowS
Prelude.Show, forall x. Rep UpdateRecipeResponse x -> UpdateRecipeResponse
forall x. UpdateRecipeResponse -> Rep UpdateRecipeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRecipeResponse x -> UpdateRecipeResponse
$cfrom :: forall x. UpdateRecipeResponse -> Rep UpdateRecipeResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRecipeResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'updateRecipeResponse_httpStatus' - The response's http status code.
--
-- 'name', 'updateRecipeResponse_name' - The name of the recipe that was updated.
newUpdateRecipeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  UpdateRecipeResponse
newUpdateRecipeResponse :: Int -> Text -> UpdateRecipeResponse
newUpdateRecipeResponse Int
pHttpStatus_ Text
pName_ =
  UpdateRecipeResponse'
    { $sel:httpStatus:UpdateRecipeResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:name:UpdateRecipeResponse' :: Text
name = Text
pName_
    }

-- | The response's http status code.
updateRecipeResponse_httpStatus :: Lens.Lens' UpdateRecipeResponse Prelude.Int
updateRecipeResponse_httpStatus :: Lens' UpdateRecipeResponse Int
updateRecipeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecipeResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateRecipeResponse' :: UpdateRecipeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateRecipeResponse
s@UpdateRecipeResponse' {} Int
a -> UpdateRecipeResponse
s {$sel:httpStatus:UpdateRecipeResponse' :: Int
httpStatus = Int
a} :: UpdateRecipeResponse)

-- | The name of the recipe that was updated.
updateRecipeResponse_name :: Lens.Lens' UpdateRecipeResponse Prelude.Text
updateRecipeResponse_name :: Lens' UpdateRecipeResponse Text
updateRecipeResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRecipeResponse' {Text
name :: Text
$sel:name:UpdateRecipeResponse' :: UpdateRecipeResponse -> Text
name} -> Text
name) (\s :: UpdateRecipeResponse
s@UpdateRecipeResponse' {} Text
a -> UpdateRecipeResponse
s {$sel:name:UpdateRecipeResponse' :: Text
name = Text
a} :: UpdateRecipeResponse)

instance Prelude.NFData UpdateRecipeResponse where
  rnf :: UpdateRecipeResponse -> ()
rnf UpdateRecipeResponse' {Int
Text
name :: Text
httpStatus :: Int
$sel:name:UpdateRecipeResponse' :: UpdateRecipeResponse -> Text
$sel:httpStatus:UpdateRecipeResponse' :: UpdateRecipeResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name