{-# 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.Translate.GetParallelData
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides information about a parallel data resource.
module Amazonka.Translate.GetParallelData
  ( -- * Creating a Request
    GetParallelData (..),
    newGetParallelData,

    -- * Request Lenses
    getParallelData_name,

    -- * Destructuring the Response
    GetParallelDataResponse (..),
    newGetParallelDataResponse,

    -- * Response Lenses
    getParallelDataResponse_auxiliaryDataLocation,
    getParallelDataResponse_dataLocation,
    getParallelDataResponse_latestUpdateAttemptAuxiliaryDataLocation,
    getParallelDataResponse_parallelDataProperties,
    getParallelDataResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetParallelData' smart constructor.
data GetParallelData = GetParallelData'
  { -- | The name of the parallel data resource that is being retrieved.
    GetParallelData -> Text
name :: Prelude.Text
  }
  deriving (GetParallelData -> GetParallelData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParallelData -> GetParallelData -> Bool
$c/= :: GetParallelData -> GetParallelData -> Bool
== :: GetParallelData -> GetParallelData -> Bool
$c== :: GetParallelData -> GetParallelData -> Bool
Prelude.Eq, ReadPrec [GetParallelData]
ReadPrec GetParallelData
Int -> ReadS GetParallelData
ReadS [GetParallelData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetParallelData]
$creadListPrec :: ReadPrec [GetParallelData]
readPrec :: ReadPrec GetParallelData
$creadPrec :: ReadPrec GetParallelData
readList :: ReadS [GetParallelData]
$creadList :: ReadS [GetParallelData]
readsPrec :: Int -> ReadS GetParallelData
$creadsPrec :: Int -> ReadS GetParallelData
Prelude.Read, Int -> GetParallelData -> ShowS
[GetParallelData] -> ShowS
GetParallelData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParallelData] -> ShowS
$cshowList :: [GetParallelData] -> ShowS
show :: GetParallelData -> String
$cshow :: GetParallelData -> String
showsPrec :: Int -> GetParallelData -> ShowS
$cshowsPrec :: Int -> GetParallelData -> ShowS
Prelude.Show, forall x. Rep GetParallelData x -> GetParallelData
forall x. GetParallelData -> Rep GetParallelData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetParallelData x -> GetParallelData
$cfrom :: forall x. GetParallelData -> Rep GetParallelData x
Prelude.Generic)

-- |
-- Create a value of 'GetParallelData' 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:
--
-- 'name', 'getParallelData_name' - The name of the parallel data resource that is being retrieved.
newGetParallelData ::
  -- | 'name'
  Prelude.Text ->
  GetParallelData
newGetParallelData :: Text -> GetParallelData
newGetParallelData Text
pName_ =
  GetParallelData' {$sel:name:GetParallelData' :: Text
name = Text
pName_}

-- | The name of the parallel data resource that is being retrieved.
getParallelData_name :: Lens.Lens' GetParallelData Prelude.Text
getParallelData_name :: Lens' GetParallelData Text
getParallelData_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParallelData' {Text
name :: Text
$sel:name:GetParallelData' :: GetParallelData -> Text
name} -> Text
name) (\s :: GetParallelData
s@GetParallelData' {} Text
a -> GetParallelData
s {$sel:name:GetParallelData' :: Text
name = Text
a} :: GetParallelData)

instance Core.AWSRequest GetParallelData where
  type
    AWSResponse GetParallelData =
      GetParallelDataResponse
  request :: (Service -> Service) -> GetParallelData -> Request GetParallelData
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 GetParallelData
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetParallelData)))
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 ParallelDataDataLocation
-> Maybe ParallelDataDataLocation
-> Maybe ParallelDataDataLocation
-> Maybe ParallelDataProperties
-> Int
-> GetParallelDataResponse
GetParallelDataResponse'
            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
"AuxiliaryDataLocation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DataLocation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LatestUpdateAttemptAuxiliaryDataLocation"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ParallelDataProperties")
            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 GetParallelData where
  hashWithSalt :: Int -> GetParallelData -> Int
hashWithSalt Int
_salt GetParallelData' {Text
name :: Text
$sel:name:GetParallelData' :: GetParallelData -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders GetParallelData where
  toHeaders :: GetParallelData -> 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
"AWSShineFrontendService_20170701.GetParallelData" ::
                          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 GetParallelData where
  toJSON :: GetParallelData -> Value
toJSON GetParallelData' {Text
name :: Text
$sel:name:GetParallelData' :: GetParallelData -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

-- | /See:/ 'newGetParallelDataResponse' smart constructor.
data GetParallelDataResponse = GetParallelDataResponse'
  { -- | The Amazon S3 location of a file that provides any errors or warnings
    -- that were produced by your input file. This file was created when Amazon
    -- Translate attempted to create a parallel data resource. The location is
    -- returned as a presigned URL to that has a 30-minute expiration.
    GetParallelDataResponse -> Maybe ParallelDataDataLocation
auxiliaryDataLocation :: Prelude.Maybe ParallelDataDataLocation,
    -- | The Amazon S3 location of the most recent parallel data input file that
    -- was successfully imported into Amazon Translate. The location is
    -- returned as a presigned URL that has a 30-minute expiration.
    --
    -- Amazon Translate doesn\'t scan all input files for the risk of CSV
    -- injection attacks.
    --
    -- CSV injection occurs when a .csv or .tsv file is altered so that a
    -- record contains malicious code. The record begins with a special
    -- character, such as =, +, -, or \@. When the file is opened in a
    -- spreadsheet program, the program might interpret the record as a formula
    -- and run the code within it.
    --
    -- Before you download an input file from Amazon S3, ensure that you
    -- recognize the file and trust its creator.
    GetParallelDataResponse -> Maybe ParallelDataDataLocation
dataLocation :: Prelude.Maybe ParallelDataDataLocation,
    -- | The Amazon S3 location of a file that provides any errors or warnings
    -- that were produced by your input file. This file was created when Amazon
    -- Translate attempted to update a parallel data resource. The location is
    -- returned as a presigned URL to that has a 30-minute expiration.
    GetParallelDataResponse -> Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation :: Prelude.Maybe ParallelDataDataLocation,
    -- | The properties of the parallel data resource that is being retrieved.
    GetParallelDataResponse -> Maybe ParallelDataProperties
parallelDataProperties :: Prelude.Maybe ParallelDataProperties,
    -- | The response's http status code.
    GetParallelDataResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetParallelDataResponse -> GetParallelDataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParallelDataResponse -> GetParallelDataResponse -> Bool
$c/= :: GetParallelDataResponse -> GetParallelDataResponse -> Bool
== :: GetParallelDataResponse -> GetParallelDataResponse -> Bool
$c== :: GetParallelDataResponse -> GetParallelDataResponse -> Bool
Prelude.Eq, ReadPrec [GetParallelDataResponse]
ReadPrec GetParallelDataResponse
Int -> ReadS GetParallelDataResponse
ReadS [GetParallelDataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetParallelDataResponse]
$creadListPrec :: ReadPrec [GetParallelDataResponse]
readPrec :: ReadPrec GetParallelDataResponse
$creadPrec :: ReadPrec GetParallelDataResponse
readList :: ReadS [GetParallelDataResponse]
$creadList :: ReadS [GetParallelDataResponse]
readsPrec :: Int -> ReadS GetParallelDataResponse
$creadsPrec :: Int -> ReadS GetParallelDataResponse
Prelude.Read, Int -> GetParallelDataResponse -> ShowS
[GetParallelDataResponse] -> ShowS
GetParallelDataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParallelDataResponse] -> ShowS
$cshowList :: [GetParallelDataResponse] -> ShowS
show :: GetParallelDataResponse -> String
$cshow :: GetParallelDataResponse -> String
showsPrec :: Int -> GetParallelDataResponse -> ShowS
$cshowsPrec :: Int -> GetParallelDataResponse -> ShowS
Prelude.Show, forall x. Rep GetParallelDataResponse x -> GetParallelDataResponse
forall x. GetParallelDataResponse -> Rep GetParallelDataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetParallelDataResponse x -> GetParallelDataResponse
$cfrom :: forall x. GetParallelDataResponse -> Rep GetParallelDataResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetParallelDataResponse' 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:
--
-- 'auxiliaryDataLocation', 'getParallelDataResponse_auxiliaryDataLocation' - The Amazon S3 location of a file that provides any errors or warnings
-- that were produced by your input file. This file was created when Amazon
-- Translate attempted to create a parallel data resource. The location is
-- returned as a presigned URL to that has a 30-minute expiration.
--
-- 'dataLocation', 'getParallelDataResponse_dataLocation' - The Amazon S3 location of the most recent parallel data input file that
-- was successfully imported into Amazon Translate. The location is
-- returned as a presigned URL that has a 30-minute expiration.
--
-- Amazon Translate doesn\'t scan all input files for the risk of CSV
-- injection attacks.
--
-- CSV injection occurs when a .csv or .tsv file is altered so that a
-- record contains malicious code. The record begins with a special
-- character, such as =, +, -, or \@. When the file is opened in a
-- spreadsheet program, the program might interpret the record as a formula
-- and run the code within it.
--
-- Before you download an input file from Amazon S3, ensure that you
-- recognize the file and trust its creator.
--
-- 'latestUpdateAttemptAuxiliaryDataLocation', 'getParallelDataResponse_latestUpdateAttemptAuxiliaryDataLocation' - The Amazon S3 location of a file that provides any errors or warnings
-- that were produced by your input file. This file was created when Amazon
-- Translate attempted to update a parallel data resource. The location is
-- returned as a presigned URL to that has a 30-minute expiration.
--
-- 'parallelDataProperties', 'getParallelDataResponse_parallelDataProperties' - The properties of the parallel data resource that is being retrieved.
--
-- 'httpStatus', 'getParallelDataResponse_httpStatus' - The response's http status code.
newGetParallelDataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetParallelDataResponse
newGetParallelDataResponse :: Int -> GetParallelDataResponse
newGetParallelDataResponse Int
pHttpStatus_ =
  GetParallelDataResponse'
    { $sel:auxiliaryDataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
auxiliaryDataLocation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
dataLocation = forall a. Maybe a
Prelude.Nothing,
      $sel:latestUpdateAttemptAuxiliaryDataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:parallelDataProperties:GetParallelDataResponse' :: Maybe ParallelDataProperties
parallelDataProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetParallelDataResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon S3 location of a file that provides any errors or warnings
-- that were produced by your input file. This file was created when Amazon
-- Translate attempted to create a parallel data resource. The location is
-- returned as a presigned URL to that has a 30-minute expiration.
getParallelDataResponse_auxiliaryDataLocation :: Lens.Lens' GetParallelDataResponse (Prelude.Maybe ParallelDataDataLocation)
getParallelDataResponse_auxiliaryDataLocation :: Lens' GetParallelDataResponse (Maybe ParallelDataDataLocation)
getParallelDataResponse_auxiliaryDataLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParallelDataResponse' {Maybe ParallelDataDataLocation
auxiliaryDataLocation :: Maybe ParallelDataDataLocation
$sel:auxiliaryDataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
auxiliaryDataLocation} -> Maybe ParallelDataDataLocation
auxiliaryDataLocation) (\s :: GetParallelDataResponse
s@GetParallelDataResponse' {} Maybe ParallelDataDataLocation
a -> GetParallelDataResponse
s {$sel:auxiliaryDataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
auxiliaryDataLocation = Maybe ParallelDataDataLocation
a} :: GetParallelDataResponse)

-- | The Amazon S3 location of the most recent parallel data input file that
-- was successfully imported into Amazon Translate. The location is
-- returned as a presigned URL that has a 30-minute expiration.
--
-- Amazon Translate doesn\'t scan all input files for the risk of CSV
-- injection attacks.
--
-- CSV injection occurs when a .csv or .tsv file is altered so that a
-- record contains malicious code. The record begins with a special
-- character, such as =, +, -, or \@. When the file is opened in a
-- spreadsheet program, the program might interpret the record as a formula
-- and run the code within it.
--
-- Before you download an input file from Amazon S3, ensure that you
-- recognize the file and trust its creator.
getParallelDataResponse_dataLocation :: Lens.Lens' GetParallelDataResponse (Prelude.Maybe ParallelDataDataLocation)
getParallelDataResponse_dataLocation :: Lens' GetParallelDataResponse (Maybe ParallelDataDataLocation)
getParallelDataResponse_dataLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParallelDataResponse' {Maybe ParallelDataDataLocation
dataLocation :: Maybe ParallelDataDataLocation
$sel:dataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
dataLocation} -> Maybe ParallelDataDataLocation
dataLocation) (\s :: GetParallelDataResponse
s@GetParallelDataResponse' {} Maybe ParallelDataDataLocation
a -> GetParallelDataResponse
s {$sel:dataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
dataLocation = Maybe ParallelDataDataLocation
a} :: GetParallelDataResponse)

-- | The Amazon S3 location of a file that provides any errors or warnings
-- that were produced by your input file. This file was created when Amazon
-- Translate attempted to update a parallel data resource. The location is
-- returned as a presigned URL to that has a 30-minute expiration.
getParallelDataResponse_latestUpdateAttemptAuxiliaryDataLocation :: Lens.Lens' GetParallelDataResponse (Prelude.Maybe ParallelDataDataLocation)
getParallelDataResponse_latestUpdateAttemptAuxiliaryDataLocation :: Lens' GetParallelDataResponse (Maybe ParallelDataDataLocation)
getParallelDataResponse_latestUpdateAttemptAuxiliaryDataLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParallelDataResponse' {Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation :: Maybe ParallelDataDataLocation
$sel:latestUpdateAttemptAuxiliaryDataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation} -> Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation) (\s :: GetParallelDataResponse
s@GetParallelDataResponse' {} Maybe ParallelDataDataLocation
a -> GetParallelDataResponse
s {$sel:latestUpdateAttemptAuxiliaryDataLocation:GetParallelDataResponse' :: Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation = Maybe ParallelDataDataLocation
a} :: GetParallelDataResponse)

-- | The properties of the parallel data resource that is being retrieved.
getParallelDataResponse_parallelDataProperties :: Lens.Lens' GetParallelDataResponse (Prelude.Maybe ParallelDataProperties)
getParallelDataResponse_parallelDataProperties :: Lens' GetParallelDataResponse (Maybe ParallelDataProperties)
getParallelDataResponse_parallelDataProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParallelDataResponse' {Maybe ParallelDataProperties
parallelDataProperties :: Maybe ParallelDataProperties
$sel:parallelDataProperties:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataProperties
parallelDataProperties} -> Maybe ParallelDataProperties
parallelDataProperties) (\s :: GetParallelDataResponse
s@GetParallelDataResponse' {} Maybe ParallelDataProperties
a -> GetParallelDataResponse
s {$sel:parallelDataProperties:GetParallelDataResponse' :: Maybe ParallelDataProperties
parallelDataProperties = Maybe ParallelDataProperties
a} :: GetParallelDataResponse)

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

instance Prelude.NFData GetParallelDataResponse where
  rnf :: GetParallelDataResponse -> ()
rnf GetParallelDataResponse' {Int
Maybe ParallelDataDataLocation
Maybe ParallelDataProperties
httpStatus :: Int
parallelDataProperties :: Maybe ParallelDataProperties
latestUpdateAttemptAuxiliaryDataLocation :: Maybe ParallelDataDataLocation
dataLocation :: Maybe ParallelDataDataLocation
auxiliaryDataLocation :: Maybe ParallelDataDataLocation
$sel:httpStatus:GetParallelDataResponse' :: GetParallelDataResponse -> Int
$sel:parallelDataProperties:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataProperties
$sel:latestUpdateAttemptAuxiliaryDataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
$sel:dataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
$sel:auxiliaryDataLocation:GetParallelDataResponse' :: GetParallelDataResponse -> Maybe ParallelDataDataLocation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ParallelDataDataLocation
auxiliaryDataLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ParallelDataDataLocation
dataLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ParallelDataDataLocation
latestUpdateAttemptAuxiliaryDataLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ParallelDataProperties
parallelDataProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus