{-# 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.Omics.DeleteSequenceStore
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a sequence store.
module Amazonka.Omics.DeleteSequenceStore
  ( -- * Creating a Request
    DeleteSequenceStore (..),
    newDeleteSequenceStore,

    -- * Request Lenses
    deleteSequenceStore_id,

    -- * Destructuring the Response
    DeleteSequenceStoreResponse (..),
    newDeleteSequenceStoreResponse,

    -- * Response Lenses
    deleteSequenceStoreResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteSequenceStore' smart constructor.
data DeleteSequenceStore = DeleteSequenceStore'
  { -- | The sequence store\'s ID.
    DeleteSequenceStore -> Text
id :: Prelude.Text
  }
  deriving (DeleteSequenceStore -> DeleteSequenceStore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSequenceStore -> DeleteSequenceStore -> Bool
$c/= :: DeleteSequenceStore -> DeleteSequenceStore -> Bool
== :: DeleteSequenceStore -> DeleteSequenceStore -> Bool
$c== :: DeleteSequenceStore -> DeleteSequenceStore -> Bool
Prelude.Eq, ReadPrec [DeleteSequenceStore]
ReadPrec DeleteSequenceStore
Int -> ReadS DeleteSequenceStore
ReadS [DeleteSequenceStore]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSequenceStore]
$creadListPrec :: ReadPrec [DeleteSequenceStore]
readPrec :: ReadPrec DeleteSequenceStore
$creadPrec :: ReadPrec DeleteSequenceStore
readList :: ReadS [DeleteSequenceStore]
$creadList :: ReadS [DeleteSequenceStore]
readsPrec :: Int -> ReadS DeleteSequenceStore
$creadsPrec :: Int -> ReadS DeleteSequenceStore
Prelude.Read, Int -> DeleteSequenceStore -> ShowS
[DeleteSequenceStore] -> ShowS
DeleteSequenceStore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSequenceStore] -> ShowS
$cshowList :: [DeleteSequenceStore] -> ShowS
show :: DeleteSequenceStore -> String
$cshow :: DeleteSequenceStore -> String
showsPrec :: Int -> DeleteSequenceStore -> ShowS
$cshowsPrec :: Int -> DeleteSequenceStore -> ShowS
Prelude.Show, forall x. Rep DeleteSequenceStore x -> DeleteSequenceStore
forall x. DeleteSequenceStore -> Rep DeleteSequenceStore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSequenceStore x -> DeleteSequenceStore
$cfrom :: forall x. DeleteSequenceStore -> Rep DeleteSequenceStore x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSequenceStore' 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:
--
-- 'id', 'deleteSequenceStore_id' - The sequence store\'s ID.
newDeleteSequenceStore ::
  -- | 'id'
  Prelude.Text ->
  DeleteSequenceStore
newDeleteSequenceStore :: Text -> DeleteSequenceStore
newDeleteSequenceStore Text
pId_ =
  DeleteSequenceStore' {$sel:id:DeleteSequenceStore' :: Text
id = Text
pId_}

-- | The sequence store\'s ID.
deleteSequenceStore_id :: Lens.Lens' DeleteSequenceStore Prelude.Text
deleteSequenceStore_id :: Lens' DeleteSequenceStore Text
deleteSequenceStore_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSequenceStore' {Text
id :: Text
$sel:id:DeleteSequenceStore' :: DeleteSequenceStore -> Text
id} -> Text
id) (\s :: DeleteSequenceStore
s@DeleteSequenceStore' {} Text
a -> DeleteSequenceStore
s {$sel:id:DeleteSequenceStore' :: Text
id = Text
a} :: DeleteSequenceStore)

instance Core.AWSRequest DeleteSequenceStore where
  type
    AWSResponse DeleteSequenceStore =
      DeleteSequenceStoreResponse
  request :: (Service -> Service)
-> DeleteSequenceStore -> Request DeleteSequenceStore
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteSequenceStore
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteSequenceStore)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteSequenceStoreResponse
DeleteSequenceStoreResponse'
            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))
      )

instance Prelude.Hashable DeleteSequenceStore where
  hashWithSalt :: Int -> DeleteSequenceStore -> Int
hashWithSalt Int
_salt DeleteSequenceStore' {Text
id :: Text
$sel:id:DeleteSequenceStore' :: DeleteSequenceStore -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData DeleteSequenceStore where
  rnf :: DeleteSequenceStore -> ()
rnf DeleteSequenceStore' {Text
id :: Text
$sel:id:DeleteSequenceStore' :: DeleteSequenceStore -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders DeleteSequenceStore where
  toHeaders :: DeleteSequenceStore -> 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.ToPath DeleteSequenceStore where
  toPath :: DeleteSequenceStore -> ByteString
toPath DeleteSequenceStore' {Text
id :: Text
$sel:id:DeleteSequenceStore' :: DeleteSequenceStore -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/sequencestore/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

-- |
-- Create a value of 'DeleteSequenceStoreResponse' 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', 'deleteSequenceStoreResponse_httpStatus' - The response's http status code.
newDeleteSequenceStoreResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteSequenceStoreResponse
newDeleteSequenceStoreResponse :: Int -> DeleteSequenceStoreResponse
newDeleteSequenceStoreResponse Int
pHttpStatus_ =
  DeleteSequenceStoreResponse'
    { $sel:httpStatus:DeleteSequenceStoreResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteSequenceStoreResponse where
  rnf :: DeleteSequenceStoreResponse -> ()
rnf DeleteSequenceStoreResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteSequenceStoreResponse' :: DeleteSequenceStoreResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus