{-# 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.KinesisAnalytics.DiscoverInputSchema
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This documentation is for version 1 of the Amazon Kinesis Data Analytics
-- API, which only supports SQL applications. Version 2 of the API supports
-- SQL and Java applications. For more information about version 2, see
-- </kinesisanalytics/latest/apiv2/Welcome.html Amazon Kinesis Data Analytics API V2 Documentation>.
--
-- Infers a schema by evaluating sample records on the specified streaming
-- source (Amazon Kinesis stream or Amazon Kinesis Firehose delivery
-- stream) or S3 object. In the response, the operation returns the
-- inferred schema and also the sample records that the operation used to
-- infer the schema.
--
-- You can use the inferred schema when configuring a streaming source for
-- your application. For conceptual information, see
-- <https://docs.aws.amazon.com/kinesisanalytics/latest/dev/how-it-works-input.html Configuring Application Input>.
-- Note that when you create an application using the Amazon Kinesis
-- Analytics console, the console uses this operation to infer a schema and
-- show it in the console user interface.
--
-- This operation requires permissions to perform the
-- @kinesisanalytics:DiscoverInputSchema@ action.
module Amazonka.KinesisAnalytics.DiscoverInputSchema
  ( -- * Creating a Request
    DiscoverInputSchema (..),
    newDiscoverInputSchema,

    -- * Request Lenses
    discoverInputSchema_inputProcessingConfiguration,
    discoverInputSchema_inputStartingPositionConfiguration,
    discoverInputSchema_resourceARN,
    discoverInputSchema_roleARN,
    discoverInputSchema_s3Configuration,

    -- * Destructuring the Response
    DiscoverInputSchemaResponse (..),
    newDiscoverInputSchemaResponse,

    -- * Response Lenses
    discoverInputSchemaResponse_inputSchema,
    discoverInputSchemaResponse_parsedInputRecords,
    discoverInputSchemaResponse_processedInputRecords,
    discoverInputSchemaResponse_rawInputRecords,
    discoverInputSchemaResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDiscoverInputSchema' smart constructor.
data DiscoverInputSchema = DiscoverInputSchema'
  { -- | The
    -- <https://docs.aws.amazon.com/kinesisanalytics/latest/dev/API_InputProcessingConfiguration.html InputProcessingConfiguration>
    -- to use to preprocess the records before discovering the schema of the
    -- records.
    DiscoverInputSchema -> Maybe InputProcessingConfiguration
inputProcessingConfiguration :: Prelude.Maybe InputProcessingConfiguration,
    -- | Point at which you want Amazon Kinesis Analytics to start reading
    -- records from the specified streaming source discovery purposes.
    DiscoverInputSchema -> Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration :: Prelude.Maybe InputStartingPositionConfiguration,
    -- | Amazon Resource Name (ARN) of the streaming source.
    DiscoverInputSchema -> Maybe Text
resourceARN :: Prelude.Maybe Prelude.Text,
    -- | ARN of the IAM role that Amazon Kinesis Analytics can assume to access
    -- the stream on your behalf.
    DiscoverInputSchema -> Maybe Text
roleARN :: Prelude.Maybe Prelude.Text,
    -- | Specify this parameter to discover a schema from data in an Amazon S3
    -- object.
    DiscoverInputSchema -> Maybe S3Configuration
s3Configuration :: Prelude.Maybe S3Configuration
  }
  deriving (DiscoverInputSchema -> DiscoverInputSchema -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiscoverInputSchema -> DiscoverInputSchema -> Bool
$c/= :: DiscoverInputSchema -> DiscoverInputSchema -> Bool
== :: DiscoverInputSchema -> DiscoverInputSchema -> Bool
$c== :: DiscoverInputSchema -> DiscoverInputSchema -> Bool
Prelude.Eq, ReadPrec [DiscoverInputSchema]
ReadPrec DiscoverInputSchema
Int -> ReadS DiscoverInputSchema
ReadS [DiscoverInputSchema]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DiscoverInputSchema]
$creadListPrec :: ReadPrec [DiscoverInputSchema]
readPrec :: ReadPrec DiscoverInputSchema
$creadPrec :: ReadPrec DiscoverInputSchema
readList :: ReadS [DiscoverInputSchema]
$creadList :: ReadS [DiscoverInputSchema]
readsPrec :: Int -> ReadS DiscoverInputSchema
$creadsPrec :: Int -> ReadS DiscoverInputSchema
Prelude.Read, Int -> DiscoverInputSchema -> ShowS
[DiscoverInputSchema] -> ShowS
DiscoverInputSchema -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiscoverInputSchema] -> ShowS
$cshowList :: [DiscoverInputSchema] -> ShowS
show :: DiscoverInputSchema -> String
$cshow :: DiscoverInputSchema -> String
showsPrec :: Int -> DiscoverInputSchema -> ShowS
$cshowsPrec :: Int -> DiscoverInputSchema -> ShowS
Prelude.Show, forall x. Rep DiscoverInputSchema x -> DiscoverInputSchema
forall x. DiscoverInputSchema -> Rep DiscoverInputSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DiscoverInputSchema x -> DiscoverInputSchema
$cfrom :: forall x. DiscoverInputSchema -> Rep DiscoverInputSchema x
Prelude.Generic)

-- |
-- Create a value of 'DiscoverInputSchema' 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:
--
-- 'inputProcessingConfiguration', 'discoverInputSchema_inputProcessingConfiguration' - The
-- <https://docs.aws.amazon.com/kinesisanalytics/latest/dev/API_InputProcessingConfiguration.html InputProcessingConfiguration>
-- to use to preprocess the records before discovering the schema of the
-- records.
--
-- 'inputStartingPositionConfiguration', 'discoverInputSchema_inputStartingPositionConfiguration' - Point at which you want Amazon Kinesis Analytics to start reading
-- records from the specified streaming source discovery purposes.
--
-- 'resourceARN', 'discoverInputSchema_resourceARN' - Amazon Resource Name (ARN) of the streaming source.
--
-- 'roleARN', 'discoverInputSchema_roleARN' - ARN of the IAM role that Amazon Kinesis Analytics can assume to access
-- the stream on your behalf.
--
-- 's3Configuration', 'discoverInputSchema_s3Configuration' - Specify this parameter to discover a schema from data in an Amazon S3
-- object.
newDiscoverInputSchema ::
  DiscoverInputSchema
newDiscoverInputSchema :: DiscoverInputSchema
newDiscoverInputSchema =
  DiscoverInputSchema'
    { $sel:inputProcessingConfiguration:DiscoverInputSchema' :: Maybe InputProcessingConfiguration
inputProcessingConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceARN:DiscoverInputSchema' :: Maybe Text
resourceARN = forall a. Maybe a
Prelude.Nothing,
      $sel:roleARN:DiscoverInputSchema' :: Maybe Text
roleARN = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Configuration:DiscoverInputSchema' :: Maybe S3Configuration
s3Configuration = forall a. Maybe a
Prelude.Nothing
    }

-- | The
-- <https://docs.aws.amazon.com/kinesisanalytics/latest/dev/API_InputProcessingConfiguration.html InputProcessingConfiguration>
-- to use to preprocess the records before discovering the schema of the
-- records.
discoverInputSchema_inputProcessingConfiguration :: Lens.Lens' DiscoverInputSchema (Prelude.Maybe InputProcessingConfiguration)
discoverInputSchema_inputProcessingConfiguration :: Lens' DiscoverInputSchema (Maybe InputProcessingConfiguration)
discoverInputSchema_inputProcessingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchema' {Maybe InputProcessingConfiguration
inputProcessingConfiguration :: Maybe InputProcessingConfiguration
$sel:inputProcessingConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputProcessingConfiguration
inputProcessingConfiguration} -> Maybe InputProcessingConfiguration
inputProcessingConfiguration) (\s :: DiscoverInputSchema
s@DiscoverInputSchema' {} Maybe InputProcessingConfiguration
a -> DiscoverInputSchema
s {$sel:inputProcessingConfiguration:DiscoverInputSchema' :: Maybe InputProcessingConfiguration
inputProcessingConfiguration = Maybe InputProcessingConfiguration
a} :: DiscoverInputSchema)

-- | Point at which you want Amazon Kinesis Analytics to start reading
-- records from the specified streaming source discovery purposes.
discoverInputSchema_inputStartingPositionConfiguration :: Lens.Lens' DiscoverInputSchema (Prelude.Maybe InputStartingPositionConfiguration)
discoverInputSchema_inputStartingPositionConfiguration :: Lens'
  DiscoverInputSchema (Maybe InputStartingPositionConfiguration)
discoverInputSchema_inputStartingPositionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchema' {Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration :: Maybe InputStartingPositionConfiguration
$sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration} -> Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration) (\s :: DiscoverInputSchema
s@DiscoverInputSchema' {} Maybe InputStartingPositionConfiguration
a -> DiscoverInputSchema
s {$sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration = Maybe InputStartingPositionConfiguration
a} :: DiscoverInputSchema)

-- | Amazon Resource Name (ARN) of the streaming source.
discoverInputSchema_resourceARN :: Lens.Lens' DiscoverInputSchema (Prelude.Maybe Prelude.Text)
discoverInputSchema_resourceARN :: Lens' DiscoverInputSchema (Maybe Text)
discoverInputSchema_resourceARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchema' {Maybe Text
resourceARN :: Maybe Text
$sel:resourceARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
resourceARN} -> Maybe Text
resourceARN) (\s :: DiscoverInputSchema
s@DiscoverInputSchema' {} Maybe Text
a -> DiscoverInputSchema
s {$sel:resourceARN:DiscoverInputSchema' :: Maybe Text
resourceARN = Maybe Text
a} :: DiscoverInputSchema)

-- | ARN of the IAM role that Amazon Kinesis Analytics can assume to access
-- the stream on your behalf.
discoverInputSchema_roleARN :: Lens.Lens' DiscoverInputSchema (Prelude.Maybe Prelude.Text)
discoverInputSchema_roleARN :: Lens' DiscoverInputSchema (Maybe Text)
discoverInputSchema_roleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchema' {Maybe Text
roleARN :: Maybe Text
$sel:roleARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
roleARN} -> Maybe Text
roleARN) (\s :: DiscoverInputSchema
s@DiscoverInputSchema' {} Maybe Text
a -> DiscoverInputSchema
s {$sel:roleARN:DiscoverInputSchema' :: Maybe Text
roleARN = Maybe Text
a} :: DiscoverInputSchema)

-- | Specify this parameter to discover a schema from data in an Amazon S3
-- object.
discoverInputSchema_s3Configuration :: Lens.Lens' DiscoverInputSchema (Prelude.Maybe S3Configuration)
discoverInputSchema_s3Configuration :: Lens' DiscoverInputSchema (Maybe S3Configuration)
discoverInputSchema_s3Configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchema' {Maybe S3Configuration
s3Configuration :: Maybe S3Configuration
$sel:s3Configuration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe S3Configuration
s3Configuration} -> Maybe S3Configuration
s3Configuration) (\s :: DiscoverInputSchema
s@DiscoverInputSchema' {} Maybe S3Configuration
a -> DiscoverInputSchema
s {$sel:s3Configuration:DiscoverInputSchema' :: Maybe S3Configuration
s3Configuration = Maybe S3Configuration
a} :: DiscoverInputSchema)

instance Core.AWSRequest DiscoverInputSchema where
  type
    AWSResponse DiscoverInputSchema =
      DiscoverInputSchemaResponse
  request :: (Service -> Service)
-> DiscoverInputSchema -> Request DiscoverInputSchema
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 DiscoverInputSchema
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DiscoverInputSchema)))
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 SourceSchema
-> Maybe [[Text]]
-> Maybe [Text]
-> Maybe [Text]
-> Int
-> DiscoverInputSchemaResponse
DiscoverInputSchemaResponse'
            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
"InputSchema")
            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
"ParsedInputRecords"
                            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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProcessedInputRecords"
                            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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RawInputRecords"
                            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 DiscoverInputSchema where
  hashWithSalt :: Int -> DiscoverInputSchema -> Int
hashWithSalt Int
_salt DiscoverInputSchema' {Maybe Text
Maybe InputProcessingConfiguration
Maybe InputStartingPositionConfiguration
Maybe S3Configuration
s3Configuration :: Maybe S3Configuration
roleARN :: Maybe Text
resourceARN :: Maybe Text
inputStartingPositionConfiguration :: Maybe InputStartingPositionConfiguration
inputProcessingConfiguration :: Maybe InputProcessingConfiguration
$sel:s3Configuration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe S3Configuration
$sel:roleARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:resourceARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputStartingPositionConfiguration
$sel:inputProcessingConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputProcessingConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputProcessingConfiguration
inputProcessingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3Configuration
s3Configuration

instance Prelude.NFData DiscoverInputSchema where
  rnf :: DiscoverInputSchema -> ()
rnf DiscoverInputSchema' {Maybe Text
Maybe InputProcessingConfiguration
Maybe InputStartingPositionConfiguration
Maybe S3Configuration
s3Configuration :: Maybe S3Configuration
roleARN :: Maybe Text
resourceARN :: Maybe Text
inputStartingPositionConfiguration :: Maybe InputStartingPositionConfiguration
inputProcessingConfiguration :: Maybe InputProcessingConfiguration
$sel:s3Configuration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe S3Configuration
$sel:roleARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:resourceARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputStartingPositionConfiguration
$sel:inputProcessingConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputProcessingConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe InputProcessingConfiguration
inputProcessingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputStartingPositionConfiguration
inputStartingPositionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3Configuration
s3Configuration

instance Data.ToHeaders DiscoverInputSchema where
  toHeaders :: DiscoverInputSchema -> 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
"KinesisAnalytics_20150814.DiscoverInputSchema" ::
                          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 DiscoverInputSchema where
  toJSON :: DiscoverInputSchema -> Value
toJSON DiscoverInputSchema' {Maybe Text
Maybe InputProcessingConfiguration
Maybe InputStartingPositionConfiguration
Maybe S3Configuration
s3Configuration :: Maybe S3Configuration
roleARN :: Maybe Text
resourceARN :: Maybe Text
inputStartingPositionConfiguration :: Maybe InputStartingPositionConfiguration
inputProcessingConfiguration :: Maybe InputProcessingConfiguration
$sel:s3Configuration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe S3Configuration
$sel:roleARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:resourceARN:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe Text
$sel:inputStartingPositionConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputStartingPositionConfiguration
$sel:inputProcessingConfiguration:DiscoverInputSchema' :: DiscoverInputSchema -> Maybe InputProcessingConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"InputProcessingConfiguration" 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 InputProcessingConfiguration
inputProcessingConfiguration,
            (Key
"InputStartingPositionConfiguration" 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 InputStartingPositionConfiguration
inputStartingPositionConfiguration,
            (Key
"ResourceARN" 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
resourceARN,
            (Key
"RoleARN" 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
roleARN,
            (Key
"S3Configuration" 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 S3Configuration
s3Configuration
          ]
      )

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

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

-- |
--
-- /See:/ 'newDiscoverInputSchemaResponse' smart constructor.
data DiscoverInputSchemaResponse = DiscoverInputSchemaResponse'
  { -- | Schema inferred from the streaming source. It identifies the format of
    -- the data in the streaming source and how each data element maps to
    -- corresponding columns in the in-application stream that you can create.
    DiscoverInputSchemaResponse -> Maybe SourceSchema
inputSchema :: Prelude.Maybe SourceSchema,
    -- | An array of elements, where each element corresponds to a row in a
    -- stream record (a stream record can have more than one row).
    DiscoverInputSchemaResponse -> Maybe [[Text]]
parsedInputRecords :: Prelude.Maybe [[Prelude.Text]],
    -- | Stream data that was modified by the processor specified in the
    -- @InputProcessingConfiguration@ parameter.
    DiscoverInputSchemaResponse -> Maybe [Text]
processedInputRecords :: Prelude.Maybe [Prelude.Text],
    -- | Raw stream data that was sampled to infer the schema.
    DiscoverInputSchemaResponse -> Maybe [Text]
rawInputRecords :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    DiscoverInputSchemaResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DiscoverInputSchemaResponse -> DiscoverInputSchemaResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiscoverInputSchemaResponse -> DiscoverInputSchemaResponse -> Bool
$c/= :: DiscoverInputSchemaResponse -> DiscoverInputSchemaResponse -> Bool
== :: DiscoverInputSchemaResponse -> DiscoverInputSchemaResponse -> Bool
$c== :: DiscoverInputSchemaResponse -> DiscoverInputSchemaResponse -> Bool
Prelude.Eq, ReadPrec [DiscoverInputSchemaResponse]
ReadPrec DiscoverInputSchemaResponse
Int -> ReadS DiscoverInputSchemaResponse
ReadS [DiscoverInputSchemaResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DiscoverInputSchemaResponse]
$creadListPrec :: ReadPrec [DiscoverInputSchemaResponse]
readPrec :: ReadPrec DiscoverInputSchemaResponse
$creadPrec :: ReadPrec DiscoverInputSchemaResponse
readList :: ReadS [DiscoverInputSchemaResponse]
$creadList :: ReadS [DiscoverInputSchemaResponse]
readsPrec :: Int -> ReadS DiscoverInputSchemaResponse
$creadsPrec :: Int -> ReadS DiscoverInputSchemaResponse
Prelude.Read, Int -> DiscoverInputSchemaResponse -> ShowS
[DiscoverInputSchemaResponse] -> ShowS
DiscoverInputSchemaResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiscoverInputSchemaResponse] -> ShowS
$cshowList :: [DiscoverInputSchemaResponse] -> ShowS
show :: DiscoverInputSchemaResponse -> String
$cshow :: DiscoverInputSchemaResponse -> String
showsPrec :: Int -> DiscoverInputSchemaResponse -> ShowS
$cshowsPrec :: Int -> DiscoverInputSchemaResponse -> ShowS
Prelude.Show, forall x.
Rep DiscoverInputSchemaResponse x -> DiscoverInputSchemaResponse
forall x.
DiscoverInputSchemaResponse -> Rep DiscoverInputSchemaResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DiscoverInputSchemaResponse x -> DiscoverInputSchemaResponse
$cfrom :: forall x.
DiscoverInputSchemaResponse -> Rep DiscoverInputSchemaResponse x
Prelude.Generic)

-- |
-- Create a value of 'DiscoverInputSchemaResponse' 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:
--
-- 'inputSchema', 'discoverInputSchemaResponse_inputSchema' - Schema inferred from the streaming source. It identifies the format of
-- the data in the streaming source and how each data element maps to
-- corresponding columns in the in-application stream that you can create.
--
-- 'parsedInputRecords', 'discoverInputSchemaResponse_parsedInputRecords' - An array of elements, where each element corresponds to a row in a
-- stream record (a stream record can have more than one row).
--
-- 'processedInputRecords', 'discoverInputSchemaResponse_processedInputRecords' - Stream data that was modified by the processor specified in the
-- @InputProcessingConfiguration@ parameter.
--
-- 'rawInputRecords', 'discoverInputSchemaResponse_rawInputRecords' - Raw stream data that was sampled to infer the schema.
--
-- 'httpStatus', 'discoverInputSchemaResponse_httpStatus' - The response's http status code.
newDiscoverInputSchemaResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DiscoverInputSchemaResponse
newDiscoverInputSchemaResponse :: Int -> DiscoverInputSchemaResponse
newDiscoverInputSchemaResponse Int
pHttpStatus_ =
  DiscoverInputSchemaResponse'
    { $sel:inputSchema:DiscoverInputSchemaResponse' :: Maybe SourceSchema
inputSchema =
        forall a. Maybe a
Prelude.Nothing,
      $sel:parsedInputRecords:DiscoverInputSchemaResponse' :: Maybe [[Text]]
parsedInputRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:processedInputRecords:DiscoverInputSchemaResponse' :: Maybe [Text]
processedInputRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:rawInputRecords:DiscoverInputSchemaResponse' :: Maybe [Text]
rawInputRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DiscoverInputSchemaResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Schema inferred from the streaming source. It identifies the format of
-- the data in the streaming source and how each data element maps to
-- corresponding columns in the in-application stream that you can create.
discoverInputSchemaResponse_inputSchema :: Lens.Lens' DiscoverInputSchemaResponse (Prelude.Maybe SourceSchema)
discoverInputSchemaResponse_inputSchema :: Lens' DiscoverInputSchemaResponse (Maybe SourceSchema)
discoverInputSchemaResponse_inputSchema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchemaResponse' {Maybe SourceSchema
inputSchema :: Maybe SourceSchema
$sel:inputSchema:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe SourceSchema
inputSchema} -> Maybe SourceSchema
inputSchema) (\s :: DiscoverInputSchemaResponse
s@DiscoverInputSchemaResponse' {} Maybe SourceSchema
a -> DiscoverInputSchemaResponse
s {$sel:inputSchema:DiscoverInputSchemaResponse' :: Maybe SourceSchema
inputSchema = Maybe SourceSchema
a} :: DiscoverInputSchemaResponse)

-- | An array of elements, where each element corresponds to a row in a
-- stream record (a stream record can have more than one row).
discoverInputSchemaResponse_parsedInputRecords :: Lens.Lens' DiscoverInputSchemaResponse (Prelude.Maybe [[Prelude.Text]])
discoverInputSchemaResponse_parsedInputRecords :: Lens' DiscoverInputSchemaResponse (Maybe [[Text]])
discoverInputSchemaResponse_parsedInputRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchemaResponse' {Maybe [[Text]]
parsedInputRecords :: Maybe [[Text]]
$sel:parsedInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [[Text]]
parsedInputRecords} -> Maybe [[Text]]
parsedInputRecords) (\s :: DiscoverInputSchemaResponse
s@DiscoverInputSchemaResponse' {} Maybe [[Text]]
a -> DiscoverInputSchemaResponse
s {$sel:parsedInputRecords:DiscoverInputSchemaResponse' :: Maybe [[Text]]
parsedInputRecords = Maybe [[Text]]
a} :: DiscoverInputSchemaResponse) 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

-- | Stream data that was modified by the processor specified in the
-- @InputProcessingConfiguration@ parameter.
discoverInputSchemaResponse_processedInputRecords :: Lens.Lens' DiscoverInputSchemaResponse (Prelude.Maybe [Prelude.Text])
discoverInputSchemaResponse_processedInputRecords :: Lens' DiscoverInputSchemaResponse (Maybe [Text])
discoverInputSchemaResponse_processedInputRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchemaResponse' {Maybe [Text]
processedInputRecords :: Maybe [Text]
$sel:processedInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [Text]
processedInputRecords} -> Maybe [Text]
processedInputRecords) (\s :: DiscoverInputSchemaResponse
s@DiscoverInputSchemaResponse' {} Maybe [Text]
a -> DiscoverInputSchemaResponse
s {$sel:processedInputRecords:DiscoverInputSchemaResponse' :: Maybe [Text]
processedInputRecords = Maybe [Text]
a} :: DiscoverInputSchemaResponse) 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

-- | Raw stream data that was sampled to infer the schema.
discoverInputSchemaResponse_rawInputRecords :: Lens.Lens' DiscoverInputSchemaResponse (Prelude.Maybe [Prelude.Text])
discoverInputSchemaResponse_rawInputRecords :: Lens' DiscoverInputSchemaResponse (Maybe [Text])
discoverInputSchemaResponse_rawInputRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchemaResponse' {Maybe [Text]
rawInputRecords :: Maybe [Text]
$sel:rawInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [Text]
rawInputRecords} -> Maybe [Text]
rawInputRecords) (\s :: DiscoverInputSchemaResponse
s@DiscoverInputSchemaResponse' {} Maybe [Text]
a -> DiscoverInputSchemaResponse
s {$sel:rawInputRecords:DiscoverInputSchemaResponse' :: Maybe [Text]
rawInputRecords = Maybe [Text]
a} :: DiscoverInputSchemaResponse) 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.
discoverInputSchemaResponse_httpStatus :: Lens.Lens' DiscoverInputSchemaResponse Prelude.Int
discoverInputSchemaResponse_httpStatus :: Lens' DiscoverInputSchemaResponse Int
discoverInputSchemaResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DiscoverInputSchemaResponse' {Int
httpStatus :: Int
$sel:httpStatus:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DiscoverInputSchemaResponse
s@DiscoverInputSchemaResponse' {} Int
a -> DiscoverInputSchemaResponse
s {$sel:httpStatus:DiscoverInputSchemaResponse' :: Int
httpStatus = Int
a} :: DiscoverInputSchemaResponse)

instance Prelude.NFData DiscoverInputSchemaResponse where
  rnf :: DiscoverInputSchemaResponse -> ()
rnf DiscoverInputSchemaResponse' {Int
Maybe [[Text]]
Maybe [Text]
Maybe SourceSchema
httpStatus :: Int
rawInputRecords :: Maybe [Text]
processedInputRecords :: Maybe [Text]
parsedInputRecords :: Maybe [[Text]]
inputSchema :: Maybe SourceSchema
$sel:httpStatus:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Int
$sel:rawInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [Text]
$sel:processedInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [Text]
$sel:parsedInputRecords:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe [[Text]]
$sel:inputSchema:DiscoverInputSchemaResponse' :: DiscoverInputSchemaResponse -> Maybe SourceSchema
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceSchema
inputSchema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [[Text]]
parsedInputRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
processedInputRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
rawInputRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus