{-# 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 #-}
module Amazonka.SageMaker.DescribeFeatureGroup
  ( 
    DescribeFeatureGroup (..),
    newDescribeFeatureGroup,
    
    describeFeatureGroup_nextToken,
    describeFeatureGroup_featureGroupName,
    
    DescribeFeatureGroupResponse (..),
    newDescribeFeatureGroupResponse,
    
    describeFeatureGroupResponse_description,
    describeFeatureGroupResponse_failureReason,
    describeFeatureGroupResponse_featureGroupStatus,
    describeFeatureGroupResponse_lastModifiedTime,
    describeFeatureGroupResponse_lastUpdateStatus,
    describeFeatureGroupResponse_offlineStoreConfig,
    describeFeatureGroupResponse_offlineStoreStatus,
    describeFeatureGroupResponse_onlineStoreConfig,
    describeFeatureGroupResponse_onlineStoreTotalSizeBytes,
    describeFeatureGroupResponse_roleArn,
    describeFeatureGroupResponse_httpStatus,
    describeFeatureGroupResponse_featureGroupArn,
    describeFeatureGroupResponse_featureGroupName,
    describeFeatureGroupResponse_recordIdentifierFeatureName,
    describeFeatureGroupResponse_eventTimeFeatureName,
    describeFeatureGroupResponse_featureDefinitions,
    describeFeatureGroupResponse_creationTime,
    describeFeatureGroupResponse_nextToken,
  )
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
data DescribeFeatureGroup = DescribeFeatureGroup'
  { 
    
    DescribeFeatureGroup -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    
    DescribeFeatureGroup -> Text
featureGroupName :: Prelude.Text
  }
  deriving (DescribeFeatureGroup -> DescribeFeatureGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFeatureGroup -> DescribeFeatureGroup -> Bool
$c/= :: DescribeFeatureGroup -> DescribeFeatureGroup -> Bool
== :: DescribeFeatureGroup -> DescribeFeatureGroup -> Bool
$c== :: DescribeFeatureGroup -> DescribeFeatureGroup -> Bool
Prelude.Eq, ReadPrec [DescribeFeatureGroup]
ReadPrec DescribeFeatureGroup
Int -> ReadS DescribeFeatureGroup
ReadS [DescribeFeatureGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFeatureGroup]
$creadListPrec :: ReadPrec [DescribeFeatureGroup]
readPrec :: ReadPrec DescribeFeatureGroup
$creadPrec :: ReadPrec DescribeFeatureGroup
readList :: ReadS [DescribeFeatureGroup]
$creadList :: ReadS [DescribeFeatureGroup]
readsPrec :: Int -> ReadS DescribeFeatureGroup
$creadsPrec :: Int -> ReadS DescribeFeatureGroup
Prelude.Read, Int -> DescribeFeatureGroup -> ShowS
[DescribeFeatureGroup] -> ShowS
DescribeFeatureGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFeatureGroup] -> ShowS
$cshowList :: [DescribeFeatureGroup] -> ShowS
show :: DescribeFeatureGroup -> String
$cshow :: DescribeFeatureGroup -> String
showsPrec :: Int -> DescribeFeatureGroup -> ShowS
$cshowsPrec :: Int -> DescribeFeatureGroup -> ShowS
Prelude.Show, forall x. Rep DescribeFeatureGroup x -> DescribeFeatureGroup
forall x. DescribeFeatureGroup -> Rep DescribeFeatureGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeFeatureGroup x -> DescribeFeatureGroup
$cfrom :: forall x. DescribeFeatureGroup -> Rep DescribeFeatureGroup x
Prelude.Generic)
newDescribeFeatureGroup ::
  
  Prelude.Text ->
  DescribeFeatureGroup
newDescribeFeatureGroup :: Text -> DescribeFeatureGroup
newDescribeFeatureGroup Text
pFeatureGroupName_ =
  DescribeFeatureGroup'
    { $sel:nextToken:DescribeFeatureGroup' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:featureGroupName:DescribeFeatureGroup' :: Text
featureGroupName = Text
pFeatureGroupName_
    }
describeFeatureGroup_nextToken :: Lens.Lens' DescribeFeatureGroup (Prelude.Maybe Prelude.Text)
describeFeatureGroup_nextToken :: Lens' DescribeFeatureGroup (Maybe Text)
describeFeatureGroup_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroup' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeFeatureGroup' :: DescribeFeatureGroup -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeFeatureGroup
s@DescribeFeatureGroup' {} Maybe Text
a -> DescribeFeatureGroup
s {$sel:nextToken:DescribeFeatureGroup' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeFeatureGroup)
describeFeatureGroup_featureGroupName :: Lens.Lens' DescribeFeatureGroup Prelude.Text
describeFeatureGroup_featureGroupName :: Lens' DescribeFeatureGroup Text
describeFeatureGroup_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroup' {Text
featureGroupName :: Text
$sel:featureGroupName:DescribeFeatureGroup' :: DescribeFeatureGroup -> Text
featureGroupName} -> Text
featureGroupName) (\s :: DescribeFeatureGroup
s@DescribeFeatureGroup' {} Text
a -> DescribeFeatureGroup
s {$sel:featureGroupName:DescribeFeatureGroup' :: Text
featureGroupName = Text
a} :: DescribeFeatureGroup)
instance Core.AWSRequest DescribeFeatureGroup where
  type
    AWSResponse DescribeFeatureGroup =
      DescribeFeatureGroupResponse
  request :: (Service -> Service)
-> DescribeFeatureGroup -> Request DescribeFeatureGroup
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 DescribeFeatureGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeFeatureGroup)))
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 Text
-> Maybe Text
-> Maybe FeatureGroupStatus
-> Maybe POSIX
-> Maybe LastUpdateStatus
-> Maybe OfflineStoreConfig
-> Maybe OfflineStoreStatus
-> Maybe OnlineStoreConfig
-> Maybe Integer
-> Maybe Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> NonEmpty FeatureDefinition
-> POSIX
-> Text
-> DescribeFeatureGroupResponse
DescribeFeatureGroupResponse'
            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
"Description")
            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
"FailureReason")
            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
"FeatureGroupStatus")
            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
"LastModifiedTime")
            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
"LastUpdateStatus")
            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
"OfflineStoreConfig")
            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
"OfflineStoreStatus")
            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
"OnlineStoreConfig")
            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
"OnlineStoreTotalSizeBytes")
            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
"RoleArn")
            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))
            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")
            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
"FeatureGroupName")
            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
"RecordIdentifierFeatureName")
            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
"EventTimeFeatureName")
            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
"FeatureDefinitions")
            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
"CreationTime")
            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
"NextToken")
      )
instance Prelude.Hashable DescribeFeatureGroup where
  hashWithSalt :: Int -> DescribeFeatureGroup -> Int
hashWithSalt Int
_salt DescribeFeatureGroup' {Maybe Text
Text
featureGroupName :: Text
nextToken :: Maybe Text
$sel:featureGroupName:DescribeFeatureGroup' :: DescribeFeatureGroup -> Text
$sel:nextToken:DescribeFeatureGroup' :: DescribeFeatureGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
featureGroupName
instance Prelude.NFData DescribeFeatureGroup where
  rnf :: DescribeFeatureGroup -> ()
rnf DescribeFeatureGroup' {Maybe Text
Text
featureGroupName :: Text
nextToken :: Maybe Text
$sel:featureGroupName:DescribeFeatureGroup' :: DescribeFeatureGroup -> Text
$sel:nextToken:DescribeFeatureGroup' :: DescribeFeatureGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupName
instance Data.ToHeaders DescribeFeatureGroup where
  toHeaders :: DescribeFeatureGroup -> 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.DescribeFeatureGroup" ::
                          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 DescribeFeatureGroup where
  toJSON :: DescribeFeatureGroup -> Value
toJSON DescribeFeatureGroup' {Maybe Text
Text
featureGroupName :: Text
nextToken :: Maybe Text
$sel:featureGroupName:DescribeFeatureGroup' :: DescribeFeatureGroup -> Text
$sel:nextToken:DescribeFeatureGroup' :: DescribeFeatureGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"FeatureGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
featureGroupName)
          ]
      )
instance Data.ToPath DescribeFeatureGroup where
  toPath :: DescribeFeatureGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeFeatureGroup where
  toQuery :: DescribeFeatureGroup -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeFeatureGroupResponse = DescribeFeatureGroupResponse'
  { 
    DescribeFeatureGroupResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    
    
    
    
    
    
    DescribeFeatureGroupResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    
    DescribeFeatureGroupResponse -> Maybe FeatureGroupStatus
featureGroupStatus :: Prelude.Maybe FeatureGroupStatus,
    
    DescribeFeatureGroupResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    
    
    DescribeFeatureGroupResponse -> Maybe LastUpdateStatus
lastUpdateStatus :: Prelude.Maybe LastUpdateStatus,
    
    
    
    
    
    
    
    
    
    
    
    
    
    DescribeFeatureGroupResponse -> Maybe OfflineStoreConfig
offlineStoreConfig :: Prelude.Maybe OfflineStoreConfig,
    
    
    DescribeFeatureGroupResponse -> Maybe OfflineStoreStatus
offlineStoreStatus :: Prelude.Maybe OfflineStoreStatus,
    
    DescribeFeatureGroupResponse -> Maybe OnlineStoreConfig
onlineStoreConfig :: Prelude.Maybe OnlineStoreConfig,
    
    DescribeFeatureGroupResponse -> Maybe Integer
onlineStoreTotalSizeBytes :: Prelude.Maybe Prelude.Integer,
    
    
    DescribeFeatureGroupResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    
    DescribeFeatureGroupResponse -> Int
httpStatus :: Prelude.Int,
    
    DescribeFeatureGroupResponse -> Text
featureGroupArn :: Prelude.Text,
    
    DescribeFeatureGroupResponse -> Text
featureGroupName :: Prelude.Text,
    
    
    DescribeFeatureGroupResponse -> Text
recordIdentifierFeatureName :: Prelude.Text,
    
    
    
    
    
    
    DescribeFeatureGroupResponse -> Text
eventTimeFeatureName :: Prelude.Text,
    
    
    DescribeFeatureGroupResponse -> NonEmpty FeatureDefinition
featureDefinitions :: Prelude.NonEmpty FeatureDefinition,
    
    DescribeFeatureGroupResponse -> POSIX
creationTime :: Data.POSIX,
    
    
    DescribeFeatureGroupResponse -> Text
nextToken :: Prelude.Text
  }
  deriving (DescribeFeatureGroupResponse
-> DescribeFeatureGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFeatureGroupResponse
-> DescribeFeatureGroupResponse -> Bool
$c/= :: DescribeFeatureGroupResponse
-> DescribeFeatureGroupResponse -> Bool
== :: DescribeFeatureGroupResponse
-> DescribeFeatureGroupResponse -> Bool
$c== :: DescribeFeatureGroupResponse
-> DescribeFeatureGroupResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFeatureGroupResponse]
ReadPrec DescribeFeatureGroupResponse
Int -> ReadS DescribeFeatureGroupResponse
ReadS [DescribeFeatureGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFeatureGroupResponse]
$creadListPrec :: ReadPrec [DescribeFeatureGroupResponse]
readPrec :: ReadPrec DescribeFeatureGroupResponse
$creadPrec :: ReadPrec DescribeFeatureGroupResponse
readList :: ReadS [DescribeFeatureGroupResponse]
$creadList :: ReadS [DescribeFeatureGroupResponse]
readsPrec :: Int -> ReadS DescribeFeatureGroupResponse
$creadsPrec :: Int -> ReadS DescribeFeatureGroupResponse
Prelude.Read, Int -> DescribeFeatureGroupResponse -> ShowS
[DescribeFeatureGroupResponse] -> ShowS
DescribeFeatureGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFeatureGroupResponse] -> ShowS
$cshowList :: [DescribeFeatureGroupResponse] -> ShowS
show :: DescribeFeatureGroupResponse -> String
$cshow :: DescribeFeatureGroupResponse -> String
showsPrec :: Int -> DescribeFeatureGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeFeatureGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeFeatureGroupResponse x -> DescribeFeatureGroupResponse
forall x.
DescribeFeatureGroupResponse -> Rep DescribeFeatureGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFeatureGroupResponse x -> DescribeFeatureGroupResponse
$cfrom :: forall x.
DescribeFeatureGroupResponse -> Rep DescribeFeatureGroupResponse x
Prelude.Generic)
newDescribeFeatureGroupResponse ::
  
  Prelude.Int ->
  
  Prelude.Text ->
  
  Prelude.Text ->
  
  Prelude.Text ->
  
  Prelude.Text ->
  
  Prelude.NonEmpty FeatureDefinition ->
  
  Prelude.UTCTime ->
  
  Prelude.Text ->
  DescribeFeatureGroupResponse
newDescribeFeatureGroupResponse :: Int
-> Text
-> Text
-> Text
-> Text
-> NonEmpty FeatureDefinition
-> UTCTime
-> Text
-> DescribeFeatureGroupResponse
newDescribeFeatureGroupResponse
  Int
pHttpStatus_
  Text
pFeatureGroupArn_
  Text
pFeatureGroupName_
  Text
pRecordIdentifierFeatureName_
  Text
pEventTimeFeatureName_
  NonEmpty FeatureDefinition
pFeatureDefinitions_
  UTCTime
pCreationTime_
  Text
pNextToken_ =
    DescribeFeatureGroupResponse'
      { $sel:description:DescribeFeatureGroupResponse' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:DescribeFeatureGroupResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:featureGroupStatus:DescribeFeatureGroupResponse' :: Maybe FeatureGroupStatus
featureGroupStatus = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedTime:DescribeFeatureGroupResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:lastUpdateStatus:DescribeFeatureGroupResponse' :: Maybe LastUpdateStatus
lastUpdateStatus = forall a. Maybe a
Prelude.Nothing,
        $sel:offlineStoreConfig:DescribeFeatureGroupResponse' :: Maybe OfflineStoreConfig
offlineStoreConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:offlineStoreStatus:DescribeFeatureGroupResponse' :: Maybe OfflineStoreStatus
offlineStoreStatus = forall a. Maybe a
Prelude.Nothing,
        $sel:onlineStoreConfig:DescribeFeatureGroupResponse' :: Maybe OnlineStoreConfig
onlineStoreConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:onlineStoreTotalSizeBytes:DescribeFeatureGroupResponse' :: Maybe Integer
onlineStoreTotalSizeBytes = forall a. Maybe a
Prelude.Nothing,
        $sel:roleArn:DescribeFeatureGroupResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeFeatureGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:featureGroupArn:DescribeFeatureGroupResponse' :: Text
featureGroupArn = Text
pFeatureGroupArn_,
        $sel:featureGroupName:DescribeFeatureGroupResponse' :: Text
featureGroupName = Text
pFeatureGroupName_,
        $sel:recordIdentifierFeatureName:DescribeFeatureGroupResponse' :: Text
recordIdentifierFeatureName =
          Text
pRecordIdentifierFeatureName_,
        $sel:eventTimeFeatureName:DescribeFeatureGroupResponse' :: Text
eventTimeFeatureName = Text
pEventTimeFeatureName_,
        $sel:featureDefinitions:DescribeFeatureGroupResponse' :: 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_,
        $sel:creationTime:DescribeFeatureGroupResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:nextToken:DescribeFeatureGroupResponse' :: Text
nextToken = Text
pNextToken_
      }
describeFeatureGroupResponse_description :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe Prelude.Text)
describeFeatureGroupResponse_description :: Lens' DescribeFeatureGroupResponse (Maybe Text)
describeFeatureGroupResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe Text
a -> DescribeFeatureGroupResponse
s {$sel:description:DescribeFeatureGroupResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_failureReason :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe Prelude.Text)
describeFeatureGroupResponse_failureReason :: Lens' DescribeFeatureGroupResponse (Maybe Text)
describeFeatureGroupResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe Text
a -> DescribeFeatureGroupResponse
s {$sel:failureReason:DescribeFeatureGroupResponse' :: Maybe Text
failureReason = Maybe Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_featureGroupStatus :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe FeatureGroupStatus)
describeFeatureGroupResponse_featureGroupStatus :: Lens' DescribeFeatureGroupResponse (Maybe FeatureGroupStatus)
describeFeatureGroupResponse_featureGroupStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe FeatureGroupStatus
featureGroupStatus :: Maybe FeatureGroupStatus
$sel:featureGroupStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe FeatureGroupStatus
featureGroupStatus} -> Maybe FeatureGroupStatus
featureGroupStatus) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe FeatureGroupStatus
a -> DescribeFeatureGroupResponse
s {$sel:featureGroupStatus:DescribeFeatureGroupResponse' :: Maybe FeatureGroupStatus
featureGroupStatus = Maybe FeatureGroupStatus
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_lastModifiedTime :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe Prelude.UTCTime)
describeFeatureGroupResponse_lastModifiedTime :: Lens' DescribeFeatureGroupResponse (Maybe UTCTime)
describeFeatureGroupResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe POSIX
a -> DescribeFeatureGroupResponse
s {$sel:lastModifiedTime:DescribeFeatureGroupResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeFeatureGroupResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time
describeFeatureGroupResponse_lastUpdateStatus :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe LastUpdateStatus)
describeFeatureGroupResponse_lastUpdateStatus :: Lens' DescribeFeatureGroupResponse (Maybe LastUpdateStatus)
describeFeatureGroupResponse_lastUpdateStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe LastUpdateStatus
lastUpdateStatus :: Maybe LastUpdateStatus
$sel:lastUpdateStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe LastUpdateStatus
lastUpdateStatus} -> Maybe LastUpdateStatus
lastUpdateStatus) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe LastUpdateStatus
a -> DescribeFeatureGroupResponse
s {$sel:lastUpdateStatus:DescribeFeatureGroupResponse' :: Maybe LastUpdateStatus
lastUpdateStatus = Maybe LastUpdateStatus
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_offlineStoreConfig :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe OfflineStoreConfig)
describeFeatureGroupResponse_offlineStoreConfig :: Lens' DescribeFeatureGroupResponse (Maybe OfflineStoreConfig)
describeFeatureGroupResponse_offlineStoreConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe OfflineStoreConfig
offlineStoreConfig :: Maybe OfflineStoreConfig
$sel:offlineStoreConfig:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OfflineStoreConfig
offlineStoreConfig} -> Maybe OfflineStoreConfig
offlineStoreConfig) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe OfflineStoreConfig
a -> DescribeFeatureGroupResponse
s {$sel:offlineStoreConfig:DescribeFeatureGroupResponse' :: Maybe OfflineStoreConfig
offlineStoreConfig = Maybe OfflineStoreConfig
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_offlineStoreStatus :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe OfflineStoreStatus)
describeFeatureGroupResponse_offlineStoreStatus :: Lens' DescribeFeatureGroupResponse (Maybe OfflineStoreStatus)
describeFeatureGroupResponse_offlineStoreStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe OfflineStoreStatus
offlineStoreStatus :: Maybe OfflineStoreStatus
$sel:offlineStoreStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OfflineStoreStatus
offlineStoreStatus} -> Maybe OfflineStoreStatus
offlineStoreStatus) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe OfflineStoreStatus
a -> DescribeFeatureGroupResponse
s {$sel:offlineStoreStatus:DescribeFeatureGroupResponse' :: Maybe OfflineStoreStatus
offlineStoreStatus = Maybe OfflineStoreStatus
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_onlineStoreConfig :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe OnlineStoreConfig)
describeFeatureGroupResponse_onlineStoreConfig :: Lens' DescribeFeatureGroupResponse (Maybe OnlineStoreConfig)
describeFeatureGroupResponse_onlineStoreConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe OnlineStoreConfig
onlineStoreConfig :: Maybe OnlineStoreConfig
$sel:onlineStoreConfig:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OnlineStoreConfig
onlineStoreConfig} -> Maybe OnlineStoreConfig
onlineStoreConfig) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe OnlineStoreConfig
a -> DescribeFeatureGroupResponse
s {$sel:onlineStoreConfig:DescribeFeatureGroupResponse' :: Maybe OnlineStoreConfig
onlineStoreConfig = Maybe OnlineStoreConfig
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_onlineStoreTotalSizeBytes :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe Prelude.Integer)
describeFeatureGroupResponse_onlineStoreTotalSizeBytes :: Lens' DescribeFeatureGroupResponse (Maybe Integer)
describeFeatureGroupResponse_onlineStoreTotalSizeBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe Integer
onlineStoreTotalSizeBytes :: Maybe Integer
$sel:onlineStoreTotalSizeBytes:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Integer
onlineStoreTotalSizeBytes} -> Maybe Integer
onlineStoreTotalSizeBytes) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe Integer
a -> DescribeFeatureGroupResponse
s {$sel:onlineStoreTotalSizeBytes:DescribeFeatureGroupResponse' :: Maybe Integer
onlineStoreTotalSizeBytes = Maybe Integer
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_roleArn :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.Maybe Prelude.Text)
describeFeatureGroupResponse_roleArn :: Lens' DescribeFeatureGroupResponse (Maybe Text)
describeFeatureGroupResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Maybe Text
a -> DescribeFeatureGroupResponse
s {$sel:roleArn:DescribeFeatureGroupResponse' :: Maybe Text
roleArn = Maybe Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_httpStatus :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Int
describeFeatureGroupResponse_httpStatus :: Lens' DescribeFeatureGroupResponse Int
describeFeatureGroupResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Int
a -> DescribeFeatureGroupResponse
s {$sel:httpStatus:DescribeFeatureGroupResponse' :: Int
httpStatus = Int
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_featureGroupArn :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Text
describeFeatureGroupResponse_featureGroupArn :: Lens' DescribeFeatureGroupResponse Text
describeFeatureGroupResponse_featureGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Text
featureGroupArn :: Text
$sel:featureGroupArn:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
featureGroupArn} -> Text
featureGroupArn) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Text
a -> DescribeFeatureGroupResponse
s {$sel:featureGroupArn:DescribeFeatureGroupResponse' :: Text
featureGroupArn = Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_featureGroupName :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Text
describeFeatureGroupResponse_featureGroupName :: Lens' DescribeFeatureGroupResponse Text
describeFeatureGroupResponse_featureGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Text
featureGroupName :: Text
$sel:featureGroupName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
featureGroupName} -> Text
featureGroupName) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Text
a -> DescribeFeatureGroupResponse
s {$sel:featureGroupName:DescribeFeatureGroupResponse' :: Text
featureGroupName = Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_recordIdentifierFeatureName :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Text
describeFeatureGroupResponse_recordIdentifierFeatureName :: Lens' DescribeFeatureGroupResponse Text
describeFeatureGroupResponse_recordIdentifierFeatureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Text
recordIdentifierFeatureName :: Text
$sel:recordIdentifierFeatureName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
recordIdentifierFeatureName} -> Text
recordIdentifierFeatureName) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Text
a -> DescribeFeatureGroupResponse
s {$sel:recordIdentifierFeatureName:DescribeFeatureGroupResponse' :: Text
recordIdentifierFeatureName = Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_eventTimeFeatureName :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Text
describeFeatureGroupResponse_eventTimeFeatureName :: Lens' DescribeFeatureGroupResponse Text
describeFeatureGroupResponse_eventTimeFeatureName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Text
eventTimeFeatureName :: Text
$sel:eventTimeFeatureName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
eventTimeFeatureName} -> Text
eventTimeFeatureName) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Text
a -> DescribeFeatureGroupResponse
s {$sel:eventTimeFeatureName:DescribeFeatureGroupResponse' :: Text
eventTimeFeatureName = Text
a} :: DescribeFeatureGroupResponse)
describeFeatureGroupResponse_featureDefinitions :: Lens.Lens' DescribeFeatureGroupResponse (Prelude.NonEmpty FeatureDefinition)
describeFeatureGroupResponse_featureDefinitions :: Lens' DescribeFeatureGroupResponse (NonEmpty FeatureDefinition)
describeFeatureGroupResponse_featureDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {NonEmpty FeatureDefinition
featureDefinitions :: NonEmpty FeatureDefinition
$sel:featureDefinitions:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> NonEmpty FeatureDefinition
featureDefinitions} -> NonEmpty FeatureDefinition
featureDefinitions) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} NonEmpty FeatureDefinition
a -> DescribeFeatureGroupResponse
s {$sel:featureDefinitions:DescribeFeatureGroupResponse' :: NonEmpty FeatureDefinition
featureDefinitions = NonEmpty FeatureDefinition
a} :: DescribeFeatureGroupResponse) 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
describeFeatureGroupResponse_creationTime :: Lens.Lens' DescribeFeatureGroupResponse Prelude.UTCTime
describeFeatureGroupResponse_creationTime :: Lens' DescribeFeatureGroupResponse UTCTime
describeFeatureGroupResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} POSIX
a -> DescribeFeatureGroupResponse
s {$sel:creationTime:DescribeFeatureGroupResponse' :: POSIX
creationTime = POSIX
a} :: DescribeFeatureGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
describeFeatureGroupResponse_nextToken :: Lens.Lens' DescribeFeatureGroupResponse Prelude.Text
describeFeatureGroupResponse_nextToken :: Lens' DescribeFeatureGroupResponse Text
describeFeatureGroupResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFeatureGroupResponse' {Text
nextToken :: Text
$sel:nextToken:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
nextToken} -> Text
nextToken) (\s :: DescribeFeatureGroupResponse
s@DescribeFeatureGroupResponse' {} Text
a -> DescribeFeatureGroupResponse
s {$sel:nextToken:DescribeFeatureGroupResponse' :: Text
nextToken = Text
a} :: DescribeFeatureGroupResponse)
instance Prelude.NFData DescribeFeatureGroupResponse where
  rnf :: DescribeFeatureGroupResponse -> ()
rnf DescribeFeatureGroupResponse' {Int
Maybe Integer
Maybe Text
Maybe POSIX
Maybe FeatureGroupStatus
Maybe LastUpdateStatus
Maybe OfflineStoreStatus
Maybe OnlineStoreConfig
Maybe OfflineStoreConfig
NonEmpty FeatureDefinition
Text
POSIX
nextToken :: Text
creationTime :: POSIX
featureDefinitions :: NonEmpty FeatureDefinition
eventTimeFeatureName :: Text
recordIdentifierFeatureName :: Text
featureGroupName :: Text
featureGroupArn :: Text
httpStatus :: Int
roleArn :: Maybe Text
onlineStoreTotalSizeBytes :: Maybe Integer
onlineStoreConfig :: Maybe OnlineStoreConfig
offlineStoreStatus :: Maybe OfflineStoreStatus
offlineStoreConfig :: Maybe OfflineStoreConfig
lastUpdateStatus :: Maybe LastUpdateStatus
lastModifiedTime :: Maybe POSIX
featureGroupStatus :: Maybe FeatureGroupStatus
failureReason :: Maybe Text
description :: Maybe Text
$sel:nextToken:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
$sel:creationTime:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> POSIX
$sel:featureDefinitions:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> NonEmpty FeatureDefinition
$sel:eventTimeFeatureName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
$sel:recordIdentifierFeatureName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
$sel:featureGroupName:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
$sel:featureGroupArn:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Text
$sel:httpStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Int
$sel:roleArn:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Text
$sel:onlineStoreTotalSizeBytes:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Integer
$sel:onlineStoreConfig:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OnlineStoreConfig
$sel:offlineStoreStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OfflineStoreStatus
$sel:offlineStoreConfig:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe OfflineStoreConfig
$sel:lastUpdateStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe LastUpdateStatus
$sel:lastModifiedTime:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe POSIX
$sel:featureGroupStatus:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe FeatureGroupStatus
$sel:failureReason:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> Maybe Text
$sel:description:DescribeFeatureGroupResponse' :: DescribeFeatureGroupResponse -> 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 Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FeatureGroupStatus
featureGroupStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LastUpdateStatus
lastUpdateStatus
      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 OfflineStoreStatus
offlineStoreStatus
      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 Integer
onlineStoreTotalSizeBytes
      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 Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
featureGroupArn
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
nextToken