{-# 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.ListLineageGroups
  ( 
    ListLineageGroups (..),
    newListLineageGroups,
    
    listLineageGroups_createdAfter,
    listLineageGroups_createdBefore,
    listLineageGroups_maxResults,
    listLineageGroups_nextToken,
    listLineageGroups_sortBy,
    listLineageGroups_sortOrder,
    
    ListLineageGroupsResponse (..),
    newListLineageGroupsResponse,
    
    listLineageGroupsResponse_lineageGroupSummaries,
    listLineageGroupsResponse_nextToken,
    listLineageGroupsResponse_httpStatus,
  )
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMaker.Types
data ListLineageGroups = ListLineageGroups'
  { 
    
    ListLineageGroups -> Maybe POSIX
createdAfter :: Prelude.Maybe Data.POSIX,
    
    
    ListLineageGroups -> Maybe POSIX
createdBefore :: Prelude.Maybe Data.POSIX,
    
    
    ListLineageGroups -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    
    
    ListLineageGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    
    
    ListLineageGroups -> Maybe SortLineageGroupsBy
sortBy :: Prelude.Maybe SortLineageGroupsBy,
    
    ListLineageGroups -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder
  }
  deriving (ListLineageGroups -> ListLineageGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLineageGroups -> ListLineageGroups -> Bool
$c/= :: ListLineageGroups -> ListLineageGroups -> Bool
== :: ListLineageGroups -> ListLineageGroups -> Bool
$c== :: ListLineageGroups -> ListLineageGroups -> Bool
Prelude.Eq, ReadPrec [ListLineageGroups]
ReadPrec ListLineageGroups
Int -> ReadS ListLineageGroups
ReadS [ListLineageGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLineageGroups]
$creadListPrec :: ReadPrec [ListLineageGroups]
readPrec :: ReadPrec ListLineageGroups
$creadPrec :: ReadPrec ListLineageGroups
readList :: ReadS [ListLineageGroups]
$creadList :: ReadS [ListLineageGroups]
readsPrec :: Int -> ReadS ListLineageGroups
$creadsPrec :: Int -> ReadS ListLineageGroups
Prelude.Read, Int -> ListLineageGroups -> ShowS
[ListLineageGroups] -> ShowS
ListLineageGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLineageGroups] -> ShowS
$cshowList :: [ListLineageGroups] -> ShowS
show :: ListLineageGroups -> String
$cshow :: ListLineageGroups -> String
showsPrec :: Int -> ListLineageGroups -> ShowS
$cshowsPrec :: Int -> ListLineageGroups -> ShowS
Prelude.Show, forall x. Rep ListLineageGroups x -> ListLineageGroups
forall x. ListLineageGroups -> Rep ListLineageGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLineageGroups x -> ListLineageGroups
$cfrom :: forall x. ListLineageGroups -> Rep ListLineageGroups x
Prelude.Generic)
newListLineageGroups ::
  ListLineageGroups
newListLineageGroups :: ListLineageGroups
newListLineageGroups =
  ListLineageGroups'
    { $sel:createdAfter:ListLineageGroups' :: Maybe POSIX
createdAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBefore:ListLineageGroups' :: Maybe POSIX
createdBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListLineageGroups' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLineageGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListLineageGroups' :: Maybe SortLineageGroupsBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListLineageGroups' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing
    }
listLineageGroups_createdAfter :: Lens.Lens' ListLineageGroups (Prelude.Maybe Prelude.UTCTime)
listLineageGroups_createdAfter :: Lens' ListLineageGroups (Maybe UTCTime)
listLineageGroups_createdAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe POSIX
createdAfter :: Maybe POSIX
$sel:createdAfter:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
createdAfter} -> Maybe POSIX
createdAfter) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe POSIX
a -> ListLineageGroups
s {$sel:createdAfter:ListLineageGroups' :: Maybe POSIX
createdAfter = Maybe POSIX
a} :: ListLineageGroups) 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
listLineageGroups_createdBefore :: Lens.Lens' ListLineageGroups (Prelude.Maybe Prelude.UTCTime)
listLineageGroups_createdBefore :: Lens' ListLineageGroups (Maybe UTCTime)
listLineageGroups_createdBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe POSIX
createdBefore :: Maybe POSIX
$sel:createdBefore:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
createdBefore} -> Maybe POSIX
createdBefore) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe POSIX
a -> ListLineageGroups
s {$sel:createdBefore:ListLineageGroups' :: Maybe POSIX
createdBefore = Maybe POSIX
a} :: ListLineageGroups) 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
listLineageGroups_maxResults :: Lens.Lens' ListLineageGroups (Prelude.Maybe Prelude.Natural)
listLineageGroups_maxResults :: Lens' ListLineageGroups (Maybe Natural)
listLineageGroups_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListLineageGroups' :: ListLineageGroups -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe Natural
a -> ListLineageGroups
s {$sel:maxResults:ListLineageGroups' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListLineageGroups)
listLineageGroups_nextToken :: Lens.Lens' ListLineageGroups (Prelude.Maybe Prelude.Text)
listLineageGroups_nextToken :: Lens' ListLineageGroups (Maybe Text)
listLineageGroups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLineageGroups' :: ListLineageGroups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe Text
a -> ListLineageGroups
s {$sel:nextToken:ListLineageGroups' :: Maybe Text
nextToken = Maybe Text
a} :: ListLineageGroups)
listLineageGroups_sortBy :: Lens.Lens' ListLineageGroups (Prelude.Maybe SortLineageGroupsBy)
listLineageGroups_sortBy :: Lens' ListLineageGroups (Maybe SortLineageGroupsBy)
listLineageGroups_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe SortLineageGroupsBy
sortBy :: Maybe SortLineageGroupsBy
$sel:sortBy:ListLineageGroups' :: ListLineageGroups -> Maybe SortLineageGroupsBy
sortBy} -> Maybe SortLineageGroupsBy
sortBy) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe SortLineageGroupsBy
a -> ListLineageGroups
s {$sel:sortBy:ListLineageGroups' :: Maybe SortLineageGroupsBy
sortBy = Maybe SortLineageGroupsBy
a} :: ListLineageGroups)
listLineageGroups_sortOrder :: Lens.Lens' ListLineageGroups (Prelude.Maybe SortOrder)
listLineageGroups_sortOrder :: Lens' ListLineageGroups (Maybe SortOrder)
listLineageGroups_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroups' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListLineageGroups' :: ListLineageGroups -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListLineageGroups
s@ListLineageGroups' {} Maybe SortOrder
a -> ListLineageGroups
s {$sel:sortOrder:ListLineageGroups' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListLineageGroups)
instance Core.AWSPager ListLineageGroups where
  page :: ListLineageGroups
-> AWSResponse ListLineageGroups -> Maybe ListLineageGroups
page ListLineageGroups
rq AWSResponse ListLineageGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListLineageGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLineageGroupsResponse (Maybe Text)
listLineageGroupsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListLineageGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLineageGroupsResponse (Maybe [LineageGroupSummary])
listLineageGroupsResponse_lineageGroupSummaries
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListLineageGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListLineageGroups (Maybe Text)
listLineageGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListLineageGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLineageGroupsResponse (Maybe Text)
listLineageGroupsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest ListLineageGroups where
  type
    AWSResponse ListLineageGroups =
      ListLineageGroupsResponse
  request :: (Service -> Service)
-> ListLineageGroups -> Request ListLineageGroups
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 ListLineageGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListLineageGroups)))
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 [LineageGroupSummary]
-> Maybe Text -> Int -> ListLineageGroupsResponse
ListLineageGroupsResponse'
            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
"LineageGroupSummaries"
                            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
"NextToken")
            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 ListLineageGroups where
  hashWithSalt :: Int -> ListLineageGroups -> Int
hashWithSalt Int
_salt ListLineageGroups' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortLineageGroupsBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortLineageGroupsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:sortOrder:ListLineageGroups' :: ListLineageGroups -> Maybe SortOrder
$sel:sortBy:ListLineageGroups' :: ListLineageGroups -> Maybe SortLineageGroupsBy
$sel:nextToken:ListLineageGroups' :: ListLineageGroups -> Maybe Text
$sel:maxResults:ListLineageGroups' :: ListLineageGroups -> Maybe Natural
$sel:createdBefore:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
$sel:createdAfter:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortLineageGroupsBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
instance Prelude.NFData ListLineageGroups where
  rnf :: ListLineageGroups -> ()
rnf ListLineageGroups' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortLineageGroupsBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortLineageGroupsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:sortOrder:ListLineageGroups' :: ListLineageGroups -> Maybe SortOrder
$sel:sortBy:ListLineageGroups' :: ListLineageGroups -> Maybe SortLineageGroupsBy
$sel:nextToken:ListLineageGroups' :: ListLineageGroups -> Maybe Text
$sel:maxResults:ListLineageGroups' :: ListLineageGroups -> Maybe Natural
$sel:createdBefore:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
$sel:createdAfter:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe SortLineageGroupsBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortOrder
sortOrder
instance Data.ToHeaders ListLineageGroups where
  toHeaders :: ListLineageGroups -> 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.ListLineageGroups" ::
                          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 ListLineageGroups where
  toJSON :: ListLineageGroups -> Value
toJSON ListLineageGroups' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortLineageGroupsBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortLineageGroupsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:sortOrder:ListLineageGroups' :: ListLineageGroups -> Maybe SortOrder
$sel:sortBy:ListLineageGroups' :: ListLineageGroups -> Maybe SortLineageGroupsBy
$sel:nextToken:ListLineageGroups' :: ListLineageGroups -> Maybe Text
$sel:maxResults:ListLineageGroups' :: ListLineageGroups -> Maybe Natural
$sel:createdBefore:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
$sel:createdAfter:ListLineageGroups' :: ListLineageGroups -> Maybe POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CreatedAfter" 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 POSIX
createdAfter,
            (Key
"CreatedBefore" 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 POSIX
createdBefore,
            (Key
"MaxResults" 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 Natural
maxResults,
            (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,
            (Key
"SortBy" 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 SortLineageGroupsBy
sortBy,
            (Key
"SortOrder" 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 SortOrder
sortOrder
          ]
      )
instance Data.ToPath ListLineageGroups where
  toPath :: ListLineageGroups -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListLineageGroups where
  toQuery :: ListLineageGroups -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListLineageGroupsResponse = ListLineageGroupsResponse'
  { 
    ListLineageGroupsResponse -> Maybe [LineageGroupSummary]
lineageGroupSummaries :: Prelude.Maybe [LineageGroupSummary],
    
    
    ListLineageGroupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    
    ListLineageGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLineageGroupsResponse -> ListLineageGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLineageGroupsResponse -> ListLineageGroupsResponse -> Bool
$c/= :: ListLineageGroupsResponse -> ListLineageGroupsResponse -> Bool
== :: ListLineageGroupsResponse -> ListLineageGroupsResponse -> Bool
$c== :: ListLineageGroupsResponse -> ListLineageGroupsResponse -> Bool
Prelude.Eq, ReadPrec [ListLineageGroupsResponse]
ReadPrec ListLineageGroupsResponse
Int -> ReadS ListLineageGroupsResponse
ReadS [ListLineageGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLineageGroupsResponse]
$creadListPrec :: ReadPrec [ListLineageGroupsResponse]
readPrec :: ReadPrec ListLineageGroupsResponse
$creadPrec :: ReadPrec ListLineageGroupsResponse
readList :: ReadS [ListLineageGroupsResponse]
$creadList :: ReadS [ListLineageGroupsResponse]
readsPrec :: Int -> ReadS ListLineageGroupsResponse
$creadsPrec :: Int -> ReadS ListLineageGroupsResponse
Prelude.Read, Int -> ListLineageGroupsResponse -> ShowS
[ListLineageGroupsResponse] -> ShowS
ListLineageGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLineageGroupsResponse] -> ShowS
$cshowList :: [ListLineageGroupsResponse] -> ShowS
show :: ListLineageGroupsResponse -> String
$cshow :: ListLineageGroupsResponse -> String
showsPrec :: Int -> ListLineageGroupsResponse -> ShowS
$cshowsPrec :: Int -> ListLineageGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep ListLineageGroupsResponse x -> ListLineageGroupsResponse
forall x.
ListLineageGroupsResponse -> Rep ListLineageGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListLineageGroupsResponse x -> ListLineageGroupsResponse
$cfrom :: forall x.
ListLineageGroupsResponse -> Rep ListLineageGroupsResponse x
Prelude.Generic)
newListLineageGroupsResponse ::
  
  Prelude.Int ->
  ListLineageGroupsResponse
newListLineageGroupsResponse :: Int -> ListLineageGroupsResponse
newListLineageGroupsResponse Int
pHttpStatus_ =
  ListLineageGroupsResponse'
    { $sel:lineageGroupSummaries:ListLineageGroupsResponse' :: Maybe [LineageGroupSummary]
lineageGroupSummaries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLineageGroupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLineageGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }
listLineageGroupsResponse_lineageGroupSummaries :: Lens.Lens' ListLineageGroupsResponse (Prelude.Maybe [LineageGroupSummary])
listLineageGroupsResponse_lineageGroupSummaries :: Lens' ListLineageGroupsResponse (Maybe [LineageGroupSummary])
listLineageGroupsResponse_lineageGroupSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroupsResponse' {Maybe [LineageGroupSummary]
lineageGroupSummaries :: Maybe [LineageGroupSummary]
$sel:lineageGroupSummaries:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Maybe [LineageGroupSummary]
lineageGroupSummaries} -> Maybe [LineageGroupSummary]
lineageGroupSummaries) (\s :: ListLineageGroupsResponse
s@ListLineageGroupsResponse' {} Maybe [LineageGroupSummary]
a -> ListLineageGroupsResponse
s {$sel:lineageGroupSummaries:ListLineageGroupsResponse' :: Maybe [LineageGroupSummary]
lineageGroupSummaries = Maybe [LineageGroupSummary]
a} :: ListLineageGroupsResponse) 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
listLineageGroupsResponse_nextToken :: Lens.Lens' ListLineageGroupsResponse (Prelude.Maybe Prelude.Text)
listLineageGroupsResponse_nextToken :: Lens' ListLineageGroupsResponse (Maybe Text)
listLineageGroupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListLineageGroupsResponse
s@ListLineageGroupsResponse' {} Maybe Text
a -> ListLineageGroupsResponse
s {$sel:nextToken:ListLineageGroupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListLineageGroupsResponse)
listLineageGroupsResponse_httpStatus :: Lens.Lens' ListLineageGroupsResponse Prelude.Int
listLineageGroupsResponse_httpStatus :: Lens' ListLineageGroupsResponse Int
listLineageGroupsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLineageGroupsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListLineageGroupsResponse
s@ListLineageGroupsResponse' {} Int
a -> ListLineageGroupsResponse
s {$sel:httpStatus:ListLineageGroupsResponse' :: Int
httpStatus = Int
a} :: ListLineageGroupsResponse)
instance Prelude.NFData ListLineageGroupsResponse where
  rnf :: ListLineageGroupsResponse -> ()
rnf ListLineageGroupsResponse' {Int
Maybe [LineageGroupSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
lineageGroupSummaries :: Maybe [LineageGroupSummary]
$sel:httpStatus:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Int
$sel:nextToken:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Maybe Text
$sel:lineageGroupSummaries:ListLineageGroupsResponse' :: ListLineageGroupsResponse -> Maybe [LineageGroupSummary]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LineageGroupSummary]
lineageGroupSummaries
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Int
httpStatus