{-# 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.Glue.DeleteSchemaVersions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Remove versions from the specified schema. A version number or range may
-- be supplied. If the compatibility mode forbids deleting of a version
-- that is necessary, such as BACKWARDS_FULL, an error is returned. Calling
-- the @GetSchemaVersions@ API after this call will list the status of the
-- deleted versions.
--
-- When the range of version numbers contain check pointed version, the API
-- will return a 409 conflict and will not proceed with the deletion. You
-- have to remove the checkpoint first using the @DeleteSchemaCheckpoint@
-- API before using this API.
--
-- You cannot use the @DeleteSchemaVersions@ API to delete the first schema
-- version in the schema set. The first schema version can only be deleted
-- by the @DeleteSchema@ API. This operation will also delete the attached
-- @SchemaVersionMetadata@ under the schema versions. Hard deletes will be
-- enforced on the database.
--
-- If the compatibility mode forbids deleting of a version that is
-- necessary, such as BACKWARDS_FULL, an error is returned.
module Amazonka.Glue.DeleteSchemaVersions
  ( -- * Creating a Request
    DeleteSchemaVersions (..),
    newDeleteSchemaVersions,

    -- * Request Lenses
    deleteSchemaVersions_schemaId,
    deleteSchemaVersions_versions,

    -- * Destructuring the Response
    DeleteSchemaVersionsResponse (..),
    newDeleteSchemaVersionsResponse,

    -- * Response Lenses
    deleteSchemaVersionsResponse_schemaVersionErrors,
    deleteSchemaVersionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteSchemaVersions' smart constructor.
data DeleteSchemaVersions = DeleteSchemaVersions'
  { -- | This is a wrapper structure that may contain the schema name and Amazon
    -- Resource Name (ARN).
    DeleteSchemaVersions -> SchemaId
schemaId :: SchemaId,
    -- | A version range may be supplied which may be of the format:
    --
    -- -   a single version number, 5
    --
    -- -   a range, 5-8 : deletes versions 5, 6, 7, 8
    DeleteSchemaVersions -> Text
versions :: Prelude.Text
  }
  deriving (DeleteSchemaVersions -> DeleteSchemaVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSchemaVersions -> DeleteSchemaVersions -> Bool
$c/= :: DeleteSchemaVersions -> DeleteSchemaVersions -> Bool
== :: DeleteSchemaVersions -> DeleteSchemaVersions -> Bool
$c== :: DeleteSchemaVersions -> DeleteSchemaVersions -> Bool
Prelude.Eq, ReadPrec [DeleteSchemaVersions]
ReadPrec DeleteSchemaVersions
Int -> ReadS DeleteSchemaVersions
ReadS [DeleteSchemaVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSchemaVersions]
$creadListPrec :: ReadPrec [DeleteSchemaVersions]
readPrec :: ReadPrec DeleteSchemaVersions
$creadPrec :: ReadPrec DeleteSchemaVersions
readList :: ReadS [DeleteSchemaVersions]
$creadList :: ReadS [DeleteSchemaVersions]
readsPrec :: Int -> ReadS DeleteSchemaVersions
$creadsPrec :: Int -> ReadS DeleteSchemaVersions
Prelude.Read, Int -> DeleteSchemaVersions -> ShowS
[DeleteSchemaVersions] -> ShowS
DeleteSchemaVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSchemaVersions] -> ShowS
$cshowList :: [DeleteSchemaVersions] -> ShowS
show :: DeleteSchemaVersions -> String
$cshow :: DeleteSchemaVersions -> String
showsPrec :: Int -> DeleteSchemaVersions -> ShowS
$cshowsPrec :: Int -> DeleteSchemaVersions -> ShowS
Prelude.Show, forall x. Rep DeleteSchemaVersions x -> DeleteSchemaVersions
forall x. DeleteSchemaVersions -> Rep DeleteSchemaVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSchemaVersions x -> DeleteSchemaVersions
$cfrom :: forall x. DeleteSchemaVersions -> Rep DeleteSchemaVersions x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSchemaVersions' 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:
--
-- 'schemaId', 'deleteSchemaVersions_schemaId' - This is a wrapper structure that may contain the schema name and Amazon
-- Resource Name (ARN).
--
-- 'versions', 'deleteSchemaVersions_versions' - A version range may be supplied which may be of the format:
--
-- -   a single version number, 5
--
-- -   a range, 5-8 : deletes versions 5, 6, 7, 8
newDeleteSchemaVersions ::
  -- | 'schemaId'
  SchemaId ->
  -- | 'versions'
  Prelude.Text ->
  DeleteSchemaVersions
newDeleteSchemaVersions :: SchemaId -> Text -> DeleteSchemaVersions
newDeleteSchemaVersions SchemaId
pSchemaId_ Text
pVersions_ =
  DeleteSchemaVersions'
    { $sel:schemaId:DeleteSchemaVersions' :: SchemaId
schemaId = SchemaId
pSchemaId_,
      $sel:versions:DeleteSchemaVersions' :: Text
versions = Text
pVersions_
    }

-- | This is a wrapper structure that may contain the schema name and Amazon
-- Resource Name (ARN).
deleteSchemaVersions_schemaId :: Lens.Lens' DeleteSchemaVersions SchemaId
deleteSchemaVersions_schemaId :: Lens' DeleteSchemaVersions SchemaId
deleteSchemaVersions_schemaId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSchemaVersions' {SchemaId
schemaId :: SchemaId
$sel:schemaId:DeleteSchemaVersions' :: DeleteSchemaVersions -> SchemaId
schemaId} -> SchemaId
schemaId) (\s :: DeleteSchemaVersions
s@DeleteSchemaVersions' {} SchemaId
a -> DeleteSchemaVersions
s {$sel:schemaId:DeleteSchemaVersions' :: SchemaId
schemaId = SchemaId
a} :: DeleteSchemaVersions)

-- | A version range may be supplied which may be of the format:
--
-- -   a single version number, 5
--
-- -   a range, 5-8 : deletes versions 5, 6, 7, 8
deleteSchemaVersions_versions :: Lens.Lens' DeleteSchemaVersions Prelude.Text
deleteSchemaVersions_versions :: Lens' DeleteSchemaVersions Text
deleteSchemaVersions_versions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSchemaVersions' {Text
versions :: Text
$sel:versions:DeleteSchemaVersions' :: DeleteSchemaVersions -> Text
versions} -> Text
versions) (\s :: DeleteSchemaVersions
s@DeleteSchemaVersions' {} Text
a -> DeleteSchemaVersions
s {$sel:versions:DeleteSchemaVersions' :: Text
versions = Text
a} :: DeleteSchemaVersions)

instance Core.AWSRequest DeleteSchemaVersions where
  type
    AWSResponse DeleteSchemaVersions =
      DeleteSchemaVersionsResponse
  request :: (Service -> Service)
-> DeleteSchemaVersions -> Request DeleteSchemaVersions
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteSchemaVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteSchemaVersions)))
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 [SchemaVersionErrorItem]
-> Int -> DeleteSchemaVersionsResponse
DeleteSchemaVersionsResponse'
            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
"SchemaVersionErrors"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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 DeleteSchemaVersions where
  hashWithSalt :: Int -> DeleteSchemaVersions -> Int
hashWithSalt Int
_salt DeleteSchemaVersions' {Text
SchemaId
versions :: Text
schemaId :: SchemaId
$sel:versions:DeleteSchemaVersions' :: DeleteSchemaVersions -> Text
$sel:schemaId:DeleteSchemaVersions' :: DeleteSchemaVersions -> SchemaId
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SchemaId
schemaId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
versions

instance Prelude.NFData DeleteSchemaVersions where
  rnf :: DeleteSchemaVersions -> ()
rnf DeleteSchemaVersions' {Text
SchemaId
versions :: Text
schemaId :: SchemaId
$sel:versions:DeleteSchemaVersions' :: DeleteSchemaVersions -> Text
$sel:schemaId:DeleteSchemaVersions' :: DeleteSchemaVersions -> SchemaId
..} =
    forall a. NFData a => a -> ()
Prelude.rnf SchemaId
schemaId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
versions

instance Data.ToHeaders DeleteSchemaVersions where
  toHeaders :: DeleteSchemaVersions -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSGlue.DeleteSchemaVersions" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteSchemaVersions where
  toJSON :: DeleteSchemaVersions -> Value
toJSON DeleteSchemaVersions' {Text
SchemaId
versions :: Text
schemaId :: SchemaId
$sel:versions:DeleteSchemaVersions' :: DeleteSchemaVersions -> Text
$sel:schemaId:DeleteSchemaVersions' :: DeleteSchemaVersions -> SchemaId
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"SchemaId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SchemaId
schemaId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Versions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
versions)
          ]
      )

instance Data.ToPath DeleteSchemaVersions where
  toPath :: DeleteSchemaVersions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDeleteSchemaVersionsResponse' smart constructor.
data DeleteSchemaVersionsResponse = DeleteSchemaVersionsResponse'
  { -- | A list of @SchemaVersionErrorItem@ objects, each containing an error and
    -- schema version.
    DeleteSchemaVersionsResponse -> Maybe [SchemaVersionErrorItem]
schemaVersionErrors :: Prelude.Maybe [SchemaVersionErrorItem],
    -- | The response's http status code.
    DeleteSchemaVersionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteSchemaVersionsResponse
-> DeleteSchemaVersionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSchemaVersionsResponse
-> DeleteSchemaVersionsResponse -> Bool
$c/= :: DeleteSchemaVersionsResponse
-> DeleteSchemaVersionsResponse -> Bool
== :: DeleteSchemaVersionsResponse
-> DeleteSchemaVersionsResponse -> Bool
$c== :: DeleteSchemaVersionsResponse
-> DeleteSchemaVersionsResponse -> Bool
Prelude.Eq, ReadPrec [DeleteSchemaVersionsResponse]
ReadPrec DeleteSchemaVersionsResponse
Int -> ReadS DeleteSchemaVersionsResponse
ReadS [DeleteSchemaVersionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSchemaVersionsResponse]
$creadListPrec :: ReadPrec [DeleteSchemaVersionsResponse]
readPrec :: ReadPrec DeleteSchemaVersionsResponse
$creadPrec :: ReadPrec DeleteSchemaVersionsResponse
readList :: ReadS [DeleteSchemaVersionsResponse]
$creadList :: ReadS [DeleteSchemaVersionsResponse]
readsPrec :: Int -> ReadS DeleteSchemaVersionsResponse
$creadsPrec :: Int -> ReadS DeleteSchemaVersionsResponse
Prelude.Read, Int -> DeleteSchemaVersionsResponse -> ShowS
[DeleteSchemaVersionsResponse] -> ShowS
DeleteSchemaVersionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSchemaVersionsResponse] -> ShowS
$cshowList :: [DeleteSchemaVersionsResponse] -> ShowS
show :: DeleteSchemaVersionsResponse -> String
$cshow :: DeleteSchemaVersionsResponse -> String
showsPrec :: Int -> DeleteSchemaVersionsResponse -> ShowS
$cshowsPrec :: Int -> DeleteSchemaVersionsResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteSchemaVersionsResponse x -> DeleteSchemaVersionsResponse
forall x.
DeleteSchemaVersionsResponse -> Rep DeleteSchemaVersionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteSchemaVersionsResponse x -> DeleteSchemaVersionsResponse
$cfrom :: forall x.
DeleteSchemaVersionsResponse -> Rep DeleteSchemaVersionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSchemaVersionsResponse' 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:
--
-- 'schemaVersionErrors', 'deleteSchemaVersionsResponse_schemaVersionErrors' - A list of @SchemaVersionErrorItem@ objects, each containing an error and
-- schema version.
--
-- 'httpStatus', 'deleteSchemaVersionsResponse_httpStatus' - The response's http status code.
newDeleteSchemaVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteSchemaVersionsResponse
newDeleteSchemaVersionsResponse :: Int -> DeleteSchemaVersionsResponse
newDeleteSchemaVersionsResponse Int
pHttpStatus_ =
  DeleteSchemaVersionsResponse'
    { $sel:schemaVersionErrors:DeleteSchemaVersionsResponse' :: Maybe [SchemaVersionErrorItem]
schemaVersionErrors =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteSchemaVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of @SchemaVersionErrorItem@ objects, each containing an error and
-- schema version.
deleteSchemaVersionsResponse_schemaVersionErrors :: Lens.Lens' DeleteSchemaVersionsResponse (Prelude.Maybe [SchemaVersionErrorItem])
deleteSchemaVersionsResponse_schemaVersionErrors :: Lens' DeleteSchemaVersionsResponse (Maybe [SchemaVersionErrorItem])
deleteSchemaVersionsResponse_schemaVersionErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSchemaVersionsResponse' {Maybe [SchemaVersionErrorItem]
schemaVersionErrors :: Maybe [SchemaVersionErrorItem]
$sel:schemaVersionErrors:DeleteSchemaVersionsResponse' :: DeleteSchemaVersionsResponse -> Maybe [SchemaVersionErrorItem]
schemaVersionErrors} -> Maybe [SchemaVersionErrorItem]
schemaVersionErrors) (\s :: DeleteSchemaVersionsResponse
s@DeleteSchemaVersionsResponse' {} Maybe [SchemaVersionErrorItem]
a -> DeleteSchemaVersionsResponse
s {$sel:schemaVersionErrors:DeleteSchemaVersionsResponse' :: Maybe [SchemaVersionErrorItem]
schemaVersionErrors = Maybe [SchemaVersionErrorItem]
a} :: DeleteSchemaVersionsResponse) 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 response's http status code.
deleteSchemaVersionsResponse_httpStatus :: Lens.Lens' DeleteSchemaVersionsResponse Prelude.Int
deleteSchemaVersionsResponse_httpStatus :: Lens' DeleteSchemaVersionsResponse Int
deleteSchemaVersionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSchemaVersionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteSchemaVersionsResponse' :: DeleteSchemaVersionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteSchemaVersionsResponse
s@DeleteSchemaVersionsResponse' {} Int
a -> DeleteSchemaVersionsResponse
s {$sel:httpStatus:DeleteSchemaVersionsResponse' :: Int
httpStatus = Int
a} :: DeleteSchemaVersionsResponse)

instance Prelude.NFData DeleteSchemaVersionsResponse where
  rnf :: DeleteSchemaVersionsResponse -> ()
rnf DeleteSchemaVersionsResponse' {Int
Maybe [SchemaVersionErrorItem]
httpStatus :: Int
schemaVersionErrors :: Maybe [SchemaVersionErrorItem]
$sel:httpStatus:DeleteSchemaVersionsResponse' :: DeleteSchemaVersionsResponse -> Int
$sel:schemaVersionErrors:DeleteSchemaVersionsResponse' :: DeleteSchemaVersionsResponse -> Maybe [SchemaVersionErrorItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [SchemaVersionErrorItem]
schemaVersionErrors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus