{-# 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.SageMaker.CreateFeatureGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a new @FeatureGroup@. A @FeatureGroup@ is a group of @Features@
-- defined in the @FeatureStore@ to describe a @Record@.
--
-- The @FeatureGroup@ defines the schema and features contained in the
-- FeatureGroup. A @FeatureGroup@ definition is composed of a list of
-- @Features@, a @RecordIdentifierFeatureName@, an @EventTimeFeatureName@
-- and configurations for its @OnlineStore@ and @OfflineStore@. Check
-- <https://docs.aws.amazon.com/general/latest/gr/aws_service_limits.html Amazon Web Services service quotas>
-- to see the @FeatureGroup@s quota for your Amazon Web Services account.
--
-- You must include at least one of @OnlineStoreConfig@ and
-- @OfflineStoreConfig@ to create a @FeatureGroup@.
module Amazonka.SageMaker.CreateFeatureGroup
  ( -- * Creating a Request
    CreateFeatureGroup (..),
    newCreateFeatureGroup,

    -- * Request Lenses
    createFeatureGroup_description,
    createFeatureGroup_offlineStoreConfig,
    createFeatureGroup_onlineStoreConfig,
    createFeatureGroup_roleArn,
    createFeatureGroup_tags,
    createFeatureGroup_featureGroupName,
    createFeatureGroup_recordIdentifierFeatureName,
    createFeatureGroup_eventTimeFeatureName,
    createFeatureGroup_featureDefinitions,

    -- * Destructuring the Response
    CreateFeatureGroupResponse (..),
    newCreateFeatureGroupResponse,

    -- * Response Lenses
    createFeatureGroupResponse_httpStatus,
    createFeatureGroupResponse_featureGroupArn,
  )
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.SageMaker.Types

-- | /See:/ 'newCreateFeatureGroup' smart constructor.
data CreateFeatureGroup = CreateFeatureGroup'
  { -- | A free-form description of a @FeatureGroup@.
    CreateFeatureGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Use this to configure an @OfflineFeatureStore@. This parameter allows
    -- you to specify:
    --
    -- -   The Amazon Simple Storage Service (Amazon S3) location of an
    --     @OfflineStore@.
    --
    -- -   A configuration for an Amazon Web Services Glue or Amazon Web
    --     Services Hive data catalog.
    --
    -- -   An KMS encryption key to encrypt the Amazon S3 location used for
    --     @OfflineStore@. If KMS encryption key is not specified, by default
    --     we encrypt all data at rest using Amazon Web Services KMS key. By
    --     defining your
    --     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucket-key.html bucket-level key>
    --     for SSE, you can reduce Amazon Web Services KMS requests costs by up
    --     to 99 percent.
    --
    -- -   Format for the offline store table. Supported formats are Glue
    --     (Default) and <https://iceberg.apache.org/ Apache Iceberg>.
    --
    -- To learn more about this parameter, see OfflineStoreConfig.
    CreateFeatureGroup -> Maybe OfflineStoreConfig
offlineStoreConfig :: Prelude.Maybe OfflineStoreConfig,
    -- | You can turn the @OnlineStore@ on or off by specifying @True@ for the
    -- @EnableOnlineStore@ flag in @OnlineStoreConfig@; the default value is
    -- @False@.
    --
    -- You can also include an Amazon Web Services KMS key ID (@KMSKeyId@) for
    -- at-rest encryption of the @OnlineStore@.
    CreateFeatureGroup -> Maybe OnlineStoreConfig
onlineStoreConfig :: Prelude.Maybe OnlineStoreConfig,
    -- | The Amazon Resource Name (ARN) of the IAM execution role used to persist
    -- data into the @OfflineStore@ if an @OfflineStoreConfig@ is provided.
    CreateFeatureGroup -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Tags used to identify @Features@ in each @FeatureGroup@.
    CreateFeatureGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the @FeatureGroup@. The name must be unique within an Amazon
    -- Web Services Region in an Amazon Web Services account. The name:
    --
    -- -   Must start and end with an alphanumeric character.
    --
    -- -   Can only contain alphanumeric character and hyphens. Spaces are not
    --     allowed.
    CreateFeatureGroup -> Text
featureGroupName :: Prelude.Text,
    -- | The name of the @Feature@ whose value uniquely identifies a @Record@
    -- defined in the @FeatureStore@. Only the latest record per identifier
    -- value will be stored in the @OnlineStore@. @RecordIdentifierFeatureName@
    -- must be one of feature definitions\' names.
    --
    -- You use the @RecordIdentifierFeatureName@ to access data in a
    -- @FeatureStore@.
    --
    -- This name:
    --
    -- -   Must start and end with an alphanumeric character.
    --
    -- -   Can only contains alphanumeric characters, hyphens, underscores.
    --     Spaces are not allowed.
    CreateFeatureGroup -> Text
recordIdentifierFeatureName :: Prelude.Text,
    -- | The name of the feature that stores the @EventTime@ of a @Record@ in a
    -- @FeatureGroup@.
    --
    -- An @EventTime@ is a point in time when a new event occurs that
    -- corresponds to the creation or update of a @Record@ in a @FeatureGroup@.
    -- All @Records@ in the @FeatureGroup@ must have a corresponding
    -- @EventTime@.
    --
    -- An @EventTime@ can be a @String@ or @Fractional@.
    --
    -- -   @Fractional@: @EventTime@ feature values must be a Unix timestamp in
    --     seconds.
    --
    -- -   @String@: @EventTime@ feature values must be an ISO-8601 string in
    --     the format. The following formats are supported
    --     @yyyy-MM-dd\'T\'HH:mm:ssZ@ and @yyyy-MM-dd\'T\'HH:mm:ss.SSSZ@ where
    --     @yyyy@, @MM@, and @dd@ represent the year, month, and day
    --     respectively and @HH@, @mm@, @ss@, and if applicable, @SSS@
    --     represent the hour, month, second and milliseconds respsectively.
    --     @\'T\'@ and @Z@ are constants.
    CreateFeatureGroup -> Text
eventTimeFeatureName :: Prelude.Text,
    -- | A list of @Feature@ names and types. @Name@ and @Type@ is compulsory per
    -- @Feature@.
    --
    -- Valid feature @FeatureType@s are @Integral@, @Fractional@ and @String@.
    --
    -- @FeatureName@s cannot be any of the following: @is_deleted@,
    -- @write_time@, @api_invocation_time@
    --
    -- You can create up to 2,500 @FeatureDefinition@s per @FeatureGroup@.
    CreateFeatureGroup -> NonEmpty FeatureDefinition
featureDefinitions :: Prelude.NonEmpty FeatureDefinition
  }
  deriving (CreateFeatureGroup -> CreateFeatureGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFeatureGroup -> CreateFeatureGroup -> Bool
$c/= :: CreateFeatureGroup -> CreateFeatureGroup -> Bool
== :: CreateFeatureGroup -> CreateFeatureGroup -> Bool
$c== :: CreateFeatureGroup -> CreateFeatureGroup -> Bool
Prelude.Eq, ReadPrec [CreateFeatureGroup]
ReadPrec CreateFeatureGroup
Int -> ReadS CreateFeatureGroup
ReadS [CreateFeatureGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFeatureGroup]
$creadListPrec :: ReadPrec [CreateFeatureGroup]
readPrec :: ReadPrec CreateFeatureGroup
$creadPrec :: ReadPrec CreateFeatureGroup
readList :: ReadS [CreateFeatureGroup]
$creadList :: ReadS [CreateFeatureGroup]
readsPrec :: Int -> ReadS CreateFeatureGroup
$creadsPrec :: Int -> ReadS CreateFeatureGroup
Prelude.Read, Int -> CreateFeatureGroup -> ShowS
[CreateFeatureGroup] -> ShowS
CreateFeatureGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFeatureGroup] -> ShowS
$cshowList :: [CreateFeatureGroup] -> ShowS
show :: CreateFeatureGroup -> String
$cshow :: CreateFeatureGroup -> String
showsPrec :: Int -> CreateFeatureGroup -> ShowS
$cshowsPrec :: Int -> CreateFeatureGroup -> ShowS
Prelude.Show, forall x. Rep CreateFeatureGroup x -> CreateFeatureGroup
forall x. CreateFeatureGroup -> Rep CreateFeatureGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFeatureGroup x -> CreateFeatureGroup
$cfrom :: forall x. CreateFeatureGroup -> Rep CreateFeatureGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateFeatureGroup' 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:
--
-- 'description', 'createFeatureGroup_description' - A free-form description of a @FeatureGroup@.
--
-- 'offlineStoreConfig', 'createFeatureGroup_offlineStoreConfig' - Use this to configure an @OfflineFeatureStore@. This parameter allows
-- you to specify:
--
-- -   The Amazon Simple Storage Service (Amazon S3) location of an
--     @OfflineStore@.
--
-- -   A configuration for an Amazon Web Services Glue or Amazon Web
--     Services Hive data catalog.
--
-- -   An KMS encryption key to encrypt the Amazon S3 location used for
--     @OfflineStore@. If KMS encryption key is not specified, by default
--     we encrypt all data at rest using Amazon Web Services KMS key. By
--     defining your
--     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucket-key.html bucket-level key>
--     for SSE, you can reduce Amazon Web Services KMS requests costs by up
--     to 99 percent.
--
-- -   Format for the offline store table. Supported formats are Glue
--     (Default) and <https://iceberg.apache.org/ Apache Iceberg>.
--
-- To learn more about this parameter, see OfflineStoreConfig.
--
-- 'onlineStoreConfig', 'createFeatureGroup_onlineStoreConfig' - You can turn the @OnlineStore@ on or off by specifying @True@ for the
-- @EnableOnlineStore@ flag in @OnlineStoreConfig@; the default value is
-- @False@.
--
-- You can also include an Amazon Web Services KMS key ID (@KMSKeyId@) for
-- at-rest encryption of the @OnlineStore@.
--
-- 'roleArn', 'createFeatureGroup_roleArn' - The Amazon Resource Name (ARN) of the IAM execution role used to persist
-- data into the @OfflineStore@ if an @OfflineStoreConfig@ is provided.
--
-- 'tags', 'createFeatureGroup_tags' - Tags used to identify @Features@ in each @FeatureGroup@.
--
-- 'featureGroupName', 'createFeatureGroup_featureGroupName' - The name of the @FeatureGroup@. The name must be unique within an Amazon
-- Web Services Region in an Amazon Web Services account. The name:
--
-- -   Must start and end with an alphanumeric character.
--
-- -   Can only contain alphanumeric character and hyphens. Spaces are not
--     allowed.
--
-- 'recordIdentifierFeatureName', 'createFeatureGroup_recordIdentifierFeatureName' - The name of the @Feature@ whose value uniquely identifies a @Record@
-- defined in the @FeatureStore@. Only the latest record per identifier
-- value will be stored in the @OnlineStore@. @RecordIdentifierFeatureName@
-- must be one of feature definitions\' names.
--
-- You use the @RecordIdentifierFeatureName@ to access data in a
-- @FeatureStore@.
--
-- This name:
--
-- -   Must start and end with an alphanumeric character.
--
-- -   Can only contains alphanumeric characters, hyphens, underscores.
--     Spaces are not allowed.
--
-- 'eventTimeFeatureName', 'createFeatureGroup_eventTimeFeatureName' - The name of the feature that stores the @EventTime@ of a @Record@ in a
-- @FeatureGroup@.
--
-- An @EventTime@ is a point in time when a new event occurs that
-- corresponds to the creation or update of a @Record@ in a @FeatureGroup@.
-- All @Records@ in the @FeatureGroup@ must have a corresponding
-- @EventTime@.
--
-- An @EventTime@ can be a @String@ or @Fractional@.
--
-- -   @Fractional@: @EventTime@ feature values must be a Unix timestamp in
--     seconds.
--
-- -   @String@: @EventTime@ feature values must be an ISO-8601 string in
--     the format. The following formats are supported
--     @yyyy-MM-dd\'T\'HH:mm:ssZ@ and @yyyy-MM-dd\'T\'HH:mm:ss.SSSZ@ where
--     @yyyy@, @MM@, and @dd@ represent the year, month, and day
--     respectively and @HH@, @mm@, @ss@, and if applicable, @SSS@
--     represent the hour, month, second and milliseconds respsectively.
--     @\'T\'@ and @Z@ are constants.
--
-- 'featureDefinitions', 'createFeatureGroup_featureDefinitions' - A list of @Feature@ names and types. @Name@ and @Type@ is compulsory per
-- @Feature@.
--
-- Valid feature @FeatureType@s are @Integral@, @Fractional@ and @String@.
--
-- @FeatureName@s cannot be any of the following: @is_deleted@,
-- @write_time@, @api_invocation_time@
--
-- You can create up to 2,500 @FeatureDefinition@s per @FeatureGroup@.
newCreateFeatureGroup ::
  -- | 'featureGroupName'
  Prelude.Text ->
  -- | 'recordIdentifierFeatureName'
  Prelude.Text ->
  -- | 'eventTimeFeatureName'
  Prelude.Text ->
  -- | 'featureDefinitions'
  Prelude.NonEmpty FeatureDefinition ->
  CreateFeatureGroup
newCreateFeatureGroup :: Text
-> Text -> Text -> NonEmpty FeatureDefinition -> CreateFeatureGroup
newCreateFeatureGroup
  Text
pFeatureGroupName_
  Text
pRecordIdentifierFeatureName_
  Text
pEventTimeFeatureName_
  NonEmpty FeatureDefinition
pFeatureDefinitions_ =
    CreateFeatureGroup'
      { $sel:description:CreateFeatureGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:offlineStoreConfig:CreateFeatureGroup' :: Maybe OfflineStoreConfig
offlineStoreConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:onlineStoreConfig:CreateFeatureGroup' :: Maybe OnlineStoreConfig
onlineStoreConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:roleArn:CreateFeatureGroup' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateFeatureGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:featureGroupName:CreateFeatureGroup' :: Text
featureGroupName = Text
pFeatureGroupName_,
        $sel:recordIdentifierFeatureName:CreateFeatureGroup' :: Text
recordIdentifierFeatureName =
          Text
pRecordIdentifierFeatureName_,
        $sel:eventTimeFeatureName:CreateFeatureGroup' :: Text
eventTimeFeatureName = Text
pEventTimeFeatureName_,
        $sel:featureDefinitions:CreateFeatureGroup' :: NonEmpty FeatureDefinition
featureDefinitions =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty FeatureDefinition
pFeatureDefinitions_
      }

-- | A free-form description of a @FeatureGroup@.
createFeatureGroup_description :: Lens.Lens' CreateFeatureGroup (Prelude.Maybe Prelude.Text)
createFeatureGroup_description :: Lens' CreateFeatureGroup (Maybe Text)
createFeatureGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Maybe Text
description :: Maybe Text
$sel:description:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Maybe Text
a -> CreateFeatureGroup
s {$sel:description:CreateFeatureGroup' :: Maybe Text
description = Maybe Text
a} :: CreateFeatureGroup)

-- | Use this to configure an @OfflineFeatureStore@. This parameter allows
-- you to specify:
--
-- -   The Amazon Simple Storage Service (Amazon S3) location of an
--     @OfflineStore@.
--
-- -   A configuration for an Amazon Web Services Glue or Amazon Web
--     Services Hive data catalog.
--
-- -   An KMS encryption key to encrypt the Amazon S3 location used for
--     @OfflineStore@. If KMS encryption key is not specified, by default
--     we encrypt all data at rest using Amazon Web Services KMS key. By
--     defining your
--     <https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucket-key.html bucket-level key>
--     for SSE, you can reduce Amazon Web Services KMS requests costs by up
--     to 99 percent.
--
-- -   Format for the offline store table. Supported formats are Glue
--     (Default) and <https://iceberg.apache.org/ Apache Iceberg>.
--
-- To learn more about this parameter, see OfflineStoreConfig.
createFeatureGroup_offlineStoreConfig :: Lens.Lens' CreateFeatureGroup (Prelude.Maybe OfflineStoreConfig)
createFeatureGroup_offlineStoreConfig :: Lens' CreateFeatureGroup (Maybe OfflineStoreConfig)
createFeatureGroup_offlineStoreConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Maybe OfflineStoreConfig
offlineStoreConfig :: Maybe OfflineStoreConfig
$sel:offlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OfflineStoreConfig
offlineStoreConfig} -> Maybe OfflineStoreConfig
offlineStoreConfig) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Maybe OfflineStoreConfig
a -> CreateFeatureGroup
s {$sel:offlineStoreConfig:CreateFeatureGroup' :: Maybe OfflineStoreConfig
offlineStoreConfig = Maybe OfflineStoreConfig
a} :: CreateFeatureGroup)

-- | You can turn the @OnlineStore@ on or off by specifying @True@ for the
-- @EnableOnlineStore@ flag in @OnlineStoreConfig@; the default value is
-- @False@.
--
-- You can also include an Amazon Web Services KMS key ID (@KMSKeyId@) for
-- at-rest encryption of the @OnlineStore@.
createFeatureGroup_onlineStoreConfig :: Lens.Lens' CreateFeatureGroup (Prelude.Maybe OnlineStoreConfig)
createFeatureGroup_onlineStoreConfig :: Lens' CreateFeatureGroup (Maybe OnlineStoreConfig)
createFeatureGroup_onlineStoreConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Maybe OnlineStoreConfig
onlineStoreConfig :: Maybe OnlineStoreConfig
$sel:onlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OnlineStoreConfig
onlineStoreConfig} -> Maybe OnlineStoreConfig
onlineStoreConfig) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Maybe OnlineStoreConfig
a -> CreateFeatureGroup
s {$sel:onlineStoreConfig:CreateFeatureGroup' :: Maybe OnlineStoreConfig
onlineStoreConfig = Maybe OnlineStoreConfig
a} :: CreateFeatureGroup)

-- | The Amazon Resource Name (ARN) of the IAM execution role used to persist
-- data into the @OfflineStore@ if an @OfflineStoreConfig@ is provided.
createFeatureGroup_roleArn :: Lens.Lens' CreateFeatureGroup (Prelude.Maybe Prelude.Text)
createFeatureGroup_roleArn :: Lens' CreateFeatureGroup (Maybe Text)
createFeatureGroup_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Maybe Text
a -> CreateFeatureGroup
s {$sel:roleArn:CreateFeatureGroup' :: Maybe Text
roleArn = Maybe Text
a} :: CreateFeatureGroup)

-- | Tags used to identify @Features@ in each @FeatureGroup@.
createFeatureGroup_tags :: Lens.Lens' CreateFeatureGroup (Prelude.Maybe [Tag])
createFeatureGroup_tags :: Lens' CreateFeatureGroup (Maybe [Tag])
createFeatureGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Maybe [Tag]
a -> CreateFeatureGroup
s {$sel:tags:CreateFeatureGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateFeatureGroup) 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 name of the @FeatureGroup@. The name must be unique within an Amazon
-- Web Services Region in an Amazon Web Services account. The name:
--
-- -   Must start and end with an alphanumeric character.
--
-- -   Can only contain alphanumeric character and hyphens. Spaces are not
--     allowed.
createFeatureGroup_featureGroupName :: Lens.Lens' CreateFeatureGroup Prelude.Text
createFeatureGroup_featureGroupName :: Lens' CreateFeatureGroup Text
createFeatureGroup_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Text
featureGroupName :: Text
$sel:featureGroupName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
featureGroupName} -> Text
featureGroupName) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Text
a -> CreateFeatureGroup
s {$sel:featureGroupName:CreateFeatureGroup' :: Text
featureGroupName = Text
a} :: CreateFeatureGroup)

-- | The name of the @Feature@ whose value uniquely identifies a @Record@
-- defined in the @FeatureStore@. Only the latest record per identifier
-- value will be stored in the @OnlineStore@. @RecordIdentifierFeatureName@
-- must be one of feature definitions\' names.
--
-- You use the @RecordIdentifierFeatureName@ to access data in a
-- @FeatureStore@.
--
-- This name:
--
-- -   Must start and end with an alphanumeric character.
--
-- -   Can only contains alphanumeric characters, hyphens, underscores.
--     Spaces are not allowed.
createFeatureGroup_recordIdentifierFeatureName :: Lens.Lens' CreateFeatureGroup Prelude.Text
createFeatureGroup_recordIdentifierFeatureName :: Lens' CreateFeatureGroup Text
createFeatureGroup_recordIdentifierFeatureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Text
recordIdentifierFeatureName :: Text
$sel:recordIdentifierFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
recordIdentifierFeatureName} -> Text
recordIdentifierFeatureName) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Text
a -> CreateFeatureGroup
s {$sel:recordIdentifierFeatureName:CreateFeatureGroup' :: Text
recordIdentifierFeatureName = Text
a} :: CreateFeatureGroup)

-- | The name of the feature that stores the @EventTime@ of a @Record@ in a
-- @FeatureGroup@.
--
-- An @EventTime@ is a point in time when a new event occurs that
-- corresponds to the creation or update of a @Record@ in a @FeatureGroup@.
-- All @Records@ in the @FeatureGroup@ must have a corresponding
-- @EventTime@.
--
-- An @EventTime@ can be a @String@ or @Fractional@.
--
-- -   @Fractional@: @EventTime@ feature values must be a Unix timestamp in
--     seconds.
--
-- -   @String@: @EventTime@ feature values must be an ISO-8601 string in
--     the format. The following formats are supported
--     @yyyy-MM-dd\'T\'HH:mm:ssZ@ and @yyyy-MM-dd\'T\'HH:mm:ss.SSSZ@ where
--     @yyyy@, @MM@, and @dd@ represent the year, month, and day
--     respectively and @HH@, @mm@, @ss@, and if applicable, @SSS@
--     represent the hour, month, second and milliseconds respsectively.
--     @\'T\'@ and @Z@ are constants.
createFeatureGroup_eventTimeFeatureName :: Lens.Lens' CreateFeatureGroup Prelude.Text
createFeatureGroup_eventTimeFeatureName :: Lens' CreateFeatureGroup Text
createFeatureGroup_eventTimeFeatureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {Text
eventTimeFeatureName :: Text
$sel:eventTimeFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
eventTimeFeatureName} -> Text
eventTimeFeatureName) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} Text
a -> CreateFeatureGroup
s {$sel:eventTimeFeatureName:CreateFeatureGroup' :: Text
eventTimeFeatureName = Text
a} :: CreateFeatureGroup)

-- | A list of @Feature@ names and types. @Name@ and @Type@ is compulsory per
-- @Feature@.
--
-- Valid feature @FeatureType@s are @Integral@, @Fractional@ and @String@.
--
-- @FeatureName@s cannot be any of the following: @is_deleted@,
-- @write_time@, @api_invocation_time@
--
-- You can create up to 2,500 @FeatureDefinition@s per @FeatureGroup@.
createFeatureGroup_featureDefinitions :: Lens.Lens' CreateFeatureGroup (Prelude.NonEmpty FeatureDefinition)
createFeatureGroup_featureDefinitions :: Lens' CreateFeatureGroup (NonEmpty FeatureDefinition)
createFeatureGroup_featureDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroup' {NonEmpty FeatureDefinition
featureDefinitions :: NonEmpty FeatureDefinition
$sel:featureDefinitions:CreateFeatureGroup' :: CreateFeatureGroup -> NonEmpty FeatureDefinition
featureDefinitions} -> NonEmpty FeatureDefinition
featureDefinitions) (\s :: CreateFeatureGroup
s@CreateFeatureGroup' {} NonEmpty FeatureDefinition
a -> CreateFeatureGroup
s {$sel:featureDefinitions:CreateFeatureGroup' :: NonEmpty FeatureDefinition
featureDefinitions = NonEmpty FeatureDefinition
a} :: CreateFeatureGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateFeatureGroup where
  type
    AWSResponse CreateFeatureGroup =
      CreateFeatureGroupResponse
  request :: (Service -> Service)
-> CreateFeatureGroup -> Request CreateFeatureGroup
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 CreateFeatureGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateFeatureGroup)))
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 ->
          Int -> Text -> CreateFeatureGroupResponse
CreateFeatureGroupResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"FeatureGroupArn")
      )

instance Prelude.Hashable CreateFeatureGroup where
  hashWithSalt :: Int -> CreateFeatureGroup -> Int
hashWithSalt Int
_salt CreateFeatureGroup' {Maybe [Tag]
Maybe Text
Maybe OnlineStoreConfig
Maybe OfflineStoreConfig
NonEmpty FeatureDefinition
Text
featureDefinitions :: NonEmpty FeatureDefinition
eventTimeFeatureName :: Text
recordIdentifierFeatureName :: Text
featureGroupName :: Text
tags :: Maybe [Tag]
roleArn :: Maybe Text
onlineStoreConfig :: Maybe OnlineStoreConfig
offlineStoreConfig :: Maybe OfflineStoreConfig
description :: Maybe Text
$sel:featureDefinitions:CreateFeatureGroup' :: CreateFeatureGroup -> NonEmpty FeatureDefinition
$sel:eventTimeFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:recordIdentifierFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:featureGroupName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:tags:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe [Tag]
$sel:roleArn:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
$sel:onlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OnlineStoreConfig
$sel:offlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OfflineStoreConfig
$sel:description:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OfflineStoreConfig
offlineStoreConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OnlineStoreConfig
onlineStoreConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
featureGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recordIdentifierFeatureName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
eventTimeFeatureName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty FeatureDefinition
featureDefinitions

instance Prelude.NFData CreateFeatureGroup where
  rnf :: CreateFeatureGroup -> ()
rnf CreateFeatureGroup' {Maybe [Tag]
Maybe Text
Maybe OnlineStoreConfig
Maybe OfflineStoreConfig
NonEmpty FeatureDefinition
Text
featureDefinitions :: NonEmpty FeatureDefinition
eventTimeFeatureName :: Text
recordIdentifierFeatureName :: Text
featureGroupName :: Text
tags :: Maybe [Tag]
roleArn :: Maybe Text
onlineStoreConfig :: Maybe OnlineStoreConfig
offlineStoreConfig :: Maybe OfflineStoreConfig
description :: Maybe Text
$sel:featureDefinitions:CreateFeatureGroup' :: CreateFeatureGroup -> NonEmpty FeatureDefinition
$sel:eventTimeFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:recordIdentifierFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:featureGroupName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:tags:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe [Tag]
$sel:roleArn:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
$sel:onlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OnlineStoreConfig
$sel:offlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OfflineStoreConfig
$sel:description:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OfflineStoreConfig
offlineStoreConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OnlineStoreConfig
onlineStoreConfig
      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 [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
recordIdentifierFeatureName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
eventTimeFeatureName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty FeatureDefinition
featureDefinitions

instance Data.ToHeaders CreateFeatureGroup where
  toHeaders :: CreateFeatureGroup -> 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
"SageMaker.CreateFeatureGroup" ::
                          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 CreateFeatureGroup where
  toJSON :: CreateFeatureGroup -> Value
toJSON CreateFeatureGroup' {Maybe [Tag]
Maybe Text
Maybe OnlineStoreConfig
Maybe OfflineStoreConfig
NonEmpty FeatureDefinition
Text
featureDefinitions :: NonEmpty FeatureDefinition
eventTimeFeatureName :: Text
recordIdentifierFeatureName :: Text
featureGroupName :: Text
tags :: Maybe [Tag]
roleArn :: Maybe Text
onlineStoreConfig :: Maybe OnlineStoreConfig
offlineStoreConfig :: Maybe OfflineStoreConfig
description :: Maybe Text
$sel:featureDefinitions:CreateFeatureGroup' :: CreateFeatureGroup -> NonEmpty FeatureDefinition
$sel:eventTimeFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:recordIdentifierFeatureName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:featureGroupName:CreateFeatureGroup' :: CreateFeatureGroup -> Text
$sel:tags:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe [Tag]
$sel:roleArn:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
$sel:onlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OnlineStoreConfig
$sel:offlineStoreConfig:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe OfflineStoreConfig
$sel:description:CreateFeatureGroup' :: CreateFeatureGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"OfflineStoreConfig" 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 OfflineStoreConfig
offlineStoreConfig,
            (Key
"OnlineStoreConfig" 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 OnlineStoreConfig
onlineStoreConfig,
            (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
"Tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"FeatureGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
featureGroupName),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"RecordIdentifierFeatureName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
recordIdentifierFeatureName
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"EventTimeFeatureName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
eventTimeFeatureName
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"FeatureDefinitions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty FeatureDefinition
featureDefinitions)
          ]
      )

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

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

-- | /See:/ 'newCreateFeatureGroupResponse' smart constructor.
data CreateFeatureGroupResponse = CreateFeatureGroupResponse'
  { -- | The response's http status code.
    CreateFeatureGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the @FeatureGroup@. This is a unique
    -- identifier for the feature group.
    CreateFeatureGroupResponse -> Text
featureGroupArn :: Prelude.Text
  }
  deriving (CreateFeatureGroupResponse -> CreateFeatureGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFeatureGroupResponse -> CreateFeatureGroupResponse -> Bool
$c/= :: CreateFeatureGroupResponse -> CreateFeatureGroupResponse -> Bool
== :: CreateFeatureGroupResponse -> CreateFeatureGroupResponse -> Bool
$c== :: CreateFeatureGroupResponse -> CreateFeatureGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateFeatureGroupResponse]
ReadPrec CreateFeatureGroupResponse
Int -> ReadS CreateFeatureGroupResponse
ReadS [CreateFeatureGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFeatureGroupResponse]
$creadListPrec :: ReadPrec [CreateFeatureGroupResponse]
readPrec :: ReadPrec CreateFeatureGroupResponse
$creadPrec :: ReadPrec CreateFeatureGroupResponse
readList :: ReadS [CreateFeatureGroupResponse]
$creadList :: ReadS [CreateFeatureGroupResponse]
readsPrec :: Int -> ReadS CreateFeatureGroupResponse
$creadsPrec :: Int -> ReadS CreateFeatureGroupResponse
Prelude.Read, Int -> CreateFeatureGroupResponse -> ShowS
[CreateFeatureGroupResponse] -> ShowS
CreateFeatureGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFeatureGroupResponse] -> ShowS
$cshowList :: [CreateFeatureGroupResponse] -> ShowS
show :: CreateFeatureGroupResponse -> String
$cshow :: CreateFeatureGroupResponse -> String
showsPrec :: Int -> CreateFeatureGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateFeatureGroupResponse -> ShowS
Prelude.Show, forall x.
Rep CreateFeatureGroupResponse x -> CreateFeatureGroupResponse
forall x.
CreateFeatureGroupResponse -> Rep CreateFeatureGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateFeatureGroupResponse x -> CreateFeatureGroupResponse
$cfrom :: forall x.
CreateFeatureGroupResponse -> Rep CreateFeatureGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateFeatureGroupResponse' 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', 'createFeatureGroupResponse_httpStatus' - The response's http status code.
--
-- 'featureGroupArn', 'createFeatureGroupResponse_featureGroupArn' - The Amazon Resource Name (ARN) of the @FeatureGroup@. This is a unique
-- identifier for the feature group.
newCreateFeatureGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'featureGroupArn'
  Prelude.Text ->
  CreateFeatureGroupResponse
newCreateFeatureGroupResponse :: Int -> Text -> CreateFeatureGroupResponse
newCreateFeatureGroupResponse
  Int
pHttpStatus_
  Text
pFeatureGroupArn_ =
    CreateFeatureGroupResponse'
      { $sel:httpStatus:CreateFeatureGroupResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:featureGroupArn:CreateFeatureGroupResponse' :: Text
featureGroupArn = Text
pFeatureGroupArn_
      }

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

-- | The Amazon Resource Name (ARN) of the @FeatureGroup@. This is a unique
-- identifier for the feature group.
createFeatureGroupResponse_featureGroupArn :: Lens.Lens' CreateFeatureGroupResponse Prelude.Text
createFeatureGroupResponse_featureGroupArn :: Lens' CreateFeatureGroupResponse Text
createFeatureGroupResponse_featureGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFeatureGroupResponse' {Text
featureGroupArn :: Text
$sel:featureGroupArn:CreateFeatureGroupResponse' :: CreateFeatureGroupResponse -> Text
featureGroupArn} -> Text
featureGroupArn) (\s :: CreateFeatureGroupResponse
s@CreateFeatureGroupResponse' {} Text
a -> CreateFeatureGroupResponse
s {$sel:featureGroupArn:CreateFeatureGroupResponse' :: Text
featureGroupArn = Text
a} :: CreateFeatureGroupResponse)

instance Prelude.NFData CreateFeatureGroupResponse where
  rnf :: CreateFeatureGroupResponse -> ()
rnf CreateFeatureGroupResponse' {Int
Text
featureGroupArn :: Text
httpStatus :: Int
$sel:featureGroupArn:CreateFeatureGroupResponse' :: CreateFeatureGroupResponse -> Text
$sel:httpStatus:CreateFeatureGroupResponse' :: CreateFeatureGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupArn