{-# 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.GetReadSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a file from a read set.
module Amazonka.Omics.GetReadSet
  ( -- * Creating a Request
    GetReadSet (..),
    newGetReadSet,

    -- * Request Lenses
    getReadSet_file,
    getReadSet_id,
    getReadSet_partNumber,
    getReadSet_sequenceStoreId,

    -- * Destructuring the Response
    GetReadSetResponse (..),
    newGetReadSetResponse,

    -- * Response Lenses
    getReadSetResponse_httpStatus,
    getReadSetResponse_payload,
  )
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:/ 'newGetReadSet' smart constructor.
data GetReadSet = GetReadSet'
  { -- | The file to retrieve.
    GetReadSet -> Maybe ReadSetFile
file :: Prelude.Maybe ReadSetFile,
    -- | The read set\'s ID.
    GetReadSet -> Text
id :: Prelude.Text,
    -- | The part number to retrieve.
    GetReadSet -> Natural
partNumber :: Prelude.Natural,
    -- | The read set\'s sequence store ID.
    GetReadSet -> Text
sequenceStoreId :: Prelude.Text
  }
  deriving (GetReadSet -> GetReadSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetReadSet -> GetReadSet -> Bool
$c/= :: GetReadSet -> GetReadSet -> Bool
== :: GetReadSet -> GetReadSet -> Bool
$c== :: GetReadSet -> GetReadSet -> Bool
Prelude.Eq, ReadPrec [GetReadSet]
ReadPrec GetReadSet
Int -> ReadS GetReadSet
ReadS [GetReadSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetReadSet]
$creadListPrec :: ReadPrec [GetReadSet]
readPrec :: ReadPrec GetReadSet
$creadPrec :: ReadPrec GetReadSet
readList :: ReadS [GetReadSet]
$creadList :: ReadS [GetReadSet]
readsPrec :: Int -> ReadS GetReadSet
$creadsPrec :: Int -> ReadS GetReadSet
Prelude.Read, Int -> GetReadSet -> ShowS
[GetReadSet] -> ShowS
GetReadSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReadSet] -> ShowS
$cshowList :: [GetReadSet] -> ShowS
show :: GetReadSet -> String
$cshow :: GetReadSet -> String
showsPrec :: Int -> GetReadSet -> ShowS
$cshowsPrec :: Int -> GetReadSet -> ShowS
Prelude.Show, forall x. Rep GetReadSet x -> GetReadSet
forall x. GetReadSet -> Rep GetReadSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetReadSet x -> GetReadSet
$cfrom :: forall x. GetReadSet -> Rep GetReadSet x
Prelude.Generic)

-- |
-- Create a value of 'GetReadSet' 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:
--
-- 'file', 'getReadSet_file' - The file to retrieve.
--
-- 'id', 'getReadSet_id' - The read set\'s ID.
--
-- 'partNumber', 'getReadSet_partNumber' - The part number to retrieve.
--
-- 'sequenceStoreId', 'getReadSet_sequenceStoreId' - The read set\'s sequence store ID.
newGetReadSet ::
  -- | 'id'
  Prelude.Text ->
  -- | 'partNumber'
  Prelude.Natural ->
  -- | 'sequenceStoreId'
  Prelude.Text ->
  GetReadSet
newGetReadSet :: Text -> Natural -> Text -> GetReadSet
newGetReadSet Text
pId_ Natural
pPartNumber_ Text
pSequenceStoreId_ =
  GetReadSet'
    { $sel:file:GetReadSet' :: Maybe ReadSetFile
file = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetReadSet' :: Text
id = Text
pId_,
      $sel:partNumber:GetReadSet' :: Natural
partNumber = Natural
pPartNumber_,
      $sel:sequenceStoreId:GetReadSet' :: Text
sequenceStoreId = Text
pSequenceStoreId_
    }

-- | The file to retrieve.
getReadSet_file :: Lens.Lens' GetReadSet (Prelude.Maybe ReadSetFile)
getReadSet_file :: Lens' GetReadSet (Maybe ReadSetFile)
getReadSet_file = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadSet' {Maybe ReadSetFile
file :: Maybe ReadSetFile
$sel:file:GetReadSet' :: GetReadSet -> Maybe ReadSetFile
file} -> Maybe ReadSetFile
file) (\s :: GetReadSet
s@GetReadSet' {} Maybe ReadSetFile
a -> GetReadSet
s {$sel:file:GetReadSet' :: Maybe ReadSetFile
file = Maybe ReadSetFile
a} :: GetReadSet)

-- | The read set\'s ID.
getReadSet_id :: Lens.Lens' GetReadSet Prelude.Text
getReadSet_id :: Lens' GetReadSet Text
getReadSet_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadSet' {Text
id :: Text
$sel:id:GetReadSet' :: GetReadSet -> Text
id} -> Text
id) (\s :: GetReadSet
s@GetReadSet' {} Text
a -> GetReadSet
s {$sel:id:GetReadSet' :: Text
id = Text
a} :: GetReadSet)

-- | The part number to retrieve.
getReadSet_partNumber :: Lens.Lens' GetReadSet Prelude.Natural
getReadSet_partNumber :: Lens' GetReadSet Natural
getReadSet_partNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadSet' {Natural
partNumber :: Natural
$sel:partNumber:GetReadSet' :: GetReadSet -> Natural
partNumber} -> Natural
partNumber) (\s :: GetReadSet
s@GetReadSet' {} Natural
a -> GetReadSet
s {$sel:partNumber:GetReadSet' :: Natural
partNumber = Natural
a} :: GetReadSet)

-- | The read set\'s sequence store ID.
getReadSet_sequenceStoreId :: Lens.Lens' GetReadSet Prelude.Text
getReadSet_sequenceStoreId :: Lens' GetReadSet Text
getReadSet_sequenceStoreId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadSet' {Text
sequenceStoreId :: Text
$sel:sequenceStoreId:GetReadSet' :: GetReadSet -> Text
sequenceStoreId} -> Text
sequenceStoreId) (\s :: GetReadSet
s@GetReadSet' {} Text
a -> GetReadSet
s {$sel:sequenceStoreId:GetReadSet' :: Text
sequenceStoreId = Text
a} :: GetReadSet)

instance Core.AWSRequest GetReadSet where
  type AWSResponse GetReadSet = GetReadSetResponse
  request :: (Service -> Service) -> GetReadSet -> Request GetReadSet
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetReadSet
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetReadSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders
 -> ResponseBody
 -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBody
      ( \Int
s ResponseHeaders
h ResponseBody
x ->
          Int -> ResponseBody -> GetReadSetResponse
GetReadSetResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure ResponseBody
x)
      )

instance Prelude.Hashable GetReadSet where
  hashWithSalt :: Int -> GetReadSet -> Int
hashWithSalt Int
_salt GetReadSet' {Natural
Maybe ReadSetFile
Text
sequenceStoreId :: Text
partNumber :: Natural
id :: Text
file :: Maybe ReadSetFile
$sel:sequenceStoreId:GetReadSet' :: GetReadSet -> Text
$sel:partNumber:GetReadSet' :: GetReadSet -> Natural
$sel:id:GetReadSet' :: GetReadSet -> Text
$sel:file:GetReadSet' :: GetReadSet -> Maybe ReadSetFile
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReadSetFile
file
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
partNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sequenceStoreId

instance Prelude.NFData GetReadSet where
  rnf :: GetReadSet -> ()
rnf GetReadSet' {Natural
Maybe ReadSetFile
Text
sequenceStoreId :: Text
partNumber :: Natural
id :: Text
file :: Maybe ReadSetFile
$sel:sequenceStoreId:GetReadSet' :: GetReadSet -> Text
$sel:partNumber:GetReadSet' :: GetReadSet -> Natural
$sel:id:GetReadSet' :: GetReadSet -> Text
$sel:file:GetReadSet' :: GetReadSet -> Maybe ReadSetFile
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ReadSetFile
file
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
partNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sequenceStoreId

instance Data.ToHeaders GetReadSet where
  toHeaders :: GetReadSet -> 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 GetReadSet where
  toPath :: GetReadSet -> ByteString
toPath GetReadSet' {Natural
Maybe ReadSetFile
Text
sequenceStoreId :: Text
partNumber :: Natural
id :: Text
file :: Maybe ReadSetFile
$sel:sequenceStoreId:GetReadSet' :: GetReadSet -> Text
$sel:partNumber:GetReadSet' :: GetReadSet -> Natural
$sel:id:GetReadSet' :: GetReadSet -> Text
$sel:file:GetReadSet' :: GetReadSet -> Maybe ReadSetFile
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/sequencestore/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
sequenceStoreId,
        ByteString
"/readset/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id
      ]

instance Data.ToQuery GetReadSet where
  toQuery :: GetReadSet -> QueryString
toQuery GetReadSet' {Natural
Maybe ReadSetFile
Text
sequenceStoreId :: Text
partNumber :: Natural
id :: Text
file :: Maybe ReadSetFile
$sel:sequenceStoreId:GetReadSet' :: GetReadSet -> Text
$sel:partNumber:GetReadSet' :: GetReadSet -> Natural
$sel:id:GetReadSet' :: GetReadSet -> Text
$sel:file:GetReadSet' :: GetReadSet -> Maybe ReadSetFile
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"file" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ReadSetFile
file,
        ByteString
"partNumber" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Natural
partNumber
      ]

-- | /See:/ 'newGetReadSetResponse' smart constructor.
data GetReadSetResponse = GetReadSetResponse'
  { -- | The response's http status code.
    GetReadSetResponse -> Int
httpStatus :: Prelude.Int,
    -- | The read set file payload.
    GetReadSetResponse -> ResponseBody
payload :: Data.ResponseBody
  }
  deriving (Int -> GetReadSetResponse -> ShowS
[GetReadSetResponse] -> ShowS
GetReadSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetReadSetResponse] -> ShowS
$cshowList :: [GetReadSetResponse] -> ShowS
show :: GetReadSetResponse -> String
$cshow :: GetReadSetResponse -> String
showsPrec :: Int -> GetReadSetResponse -> ShowS
$cshowsPrec :: Int -> GetReadSetResponse -> ShowS
Prelude.Show, forall x. Rep GetReadSetResponse x -> GetReadSetResponse
forall x. GetReadSetResponse -> Rep GetReadSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetReadSetResponse x -> GetReadSetResponse
$cfrom :: forall x. GetReadSetResponse -> Rep GetReadSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetReadSetResponse' 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', 'getReadSetResponse_httpStatus' - The response's http status code.
--
-- 'payload', 'getReadSetResponse_payload' - The read set file payload.
newGetReadSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'payload'
  Data.ResponseBody ->
  GetReadSetResponse
newGetReadSetResponse :: Int -> ResponseBody -> GetReadSetResponse
newGetReadSetResponse Int
pHttpStatus_ ResponseBody
pPayload_ =
  GetReadSetResponse'
    { $sel:httpStatus:GetReadSetResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:payload:GetReadSetResponse' :: ResponseBody
payload = ResponseBody
pPayload_
    }

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

-- | The read set file payload.
getReadSetResponse_payload :: Lens.Lens' GetReadSetResponse Data.ResponseBody
getReadSetResponse_payload :: Lens' GetReadSetResponse ResponseBody
getReadSetResponse_payload = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetReadSetResponse' {ResponseBody
payload :: ResponseBody
$sel:payload:GetReadSetResponse' :: GetReadSetResponse -> ResponseBody
payload} -> ResponseBody
payload) (\s :: GetReadSetResponse
s@GetReadSetResponse' {} ResponseBody
a -> GetReadSetResponse
s {$sel:payload:GetReadSetResponse' :: ResponseBody
payload = ResponseBody
a} :: GetReadSetResponse)