{-# 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.EFS.DescribeFileSystems
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the description of a specific Amazon EFS file system if either
-- the file system @CreationToken@ or the @FileSystemId@ is provided.
-- Otherwise, it returns descriptions of all file systems owned by the
-- caller\'s Amazon Web Services account in the Amazon Web Services Region
-- of the endpoint that you\'re calling.
--
-- When retrieving all file system descriptions, you can optionally specify
-- the @MaxItems@ parameter to limit the number of descriptions in a
-- response. Currently, this number is automatically set to 10. If more
-- file system descriptions remain, Amazon EFS returns a @NextMarker@, an
-- opaque token, in the response. In this case, you should send a
-- subsequent request with the @Marker@ request parameter set to the value
-- of @NextMarker@.
--
-- To retrieve a list of your file system descriptions, this operation is
-- used in an iterative process, where @DescribeFileSystems@ is called
-- first without the @Marker@ and then the operation continues to call it
-- with the @Marker@ parameter set to the value of the @NextMarker@ from
-- the previous response until the response has no @NextMarker@.
--
-- The order of file systems returned in the response of one
-- @DescribeFileSystems@ call and the order of file systems returned across
-- the responses of a multi-call iteration is unspecified.
--
-- This operation requires permissions for the
-- @elasticfilesystem:DescribeFileSystems@ action.
--
-- This operation returns paginated results.
module Amazonka.EFS.DescribeFileSystems
  ( -- * Creating a Request
    DescribeFileSystems (..),
    newDescribeFileSystems,

    -- * Request Lenses
    describeFileSystems_creationToken,
    describeFileSystems_fileSystemId,
    describeFileSystems_marker,
    describeFileSystems_maxItems,

    -- * Destructuring the Response
    DescribeFileSystemsResponse (..),
    newDescribeFileSystemsResponse,

    -- * Response Lenses
    describeFileSystemsResponse_fileSystems,
    describeFileSystemsResponse_marker,
    describeFileSystemsResponse_nextMarker,
    describeFileSystemsResponse_httpStatus,
  )
where

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

-- |
--
-- /See:/ 'newDescribeFileSystems' smart constructor.
data DescribeFileSystems = DescribeFileSystems'
  { -- | (Optional) Restricts the list to the file system with this creation
    -- token (String). You specify a creation token when you create an Amazon
    -- EFS file system.
    DescribeFileSystems -> Maybe Text
creationToken :: Prelude.Maybe Prelude.Text,
    -- | (Optional) ID of the file system whose description you want to retrieve
    -- (String).
    DescribeFileSystems -> Maybe Text
fileSystemId :: Prelude.Maybe Prelude.Text,
    -- | (Optional) Opaque pagination token returned from a previous
    -- @DescribeFileSystems@ operation (String). If present, specifies to
    -- continue the list from where the returning call had left off.
    DescribeFileSystems -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | (Optional) Specifies the maximum number of file systems to return in the
    -- response (integer). This number is automatically set to 100. The
    -- response is paginated at 100 per page if you have more than 100 file
    -- systems.
    DescribeFileSystems -> Maybe Natural
maxItems :: Prelude.Maybe Prelude.Natural
  }
  deriving (DescribeFileSystems -> DescribeFileSystems -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFileSystems -> DescribeFileSystems -> Bool
$c/= :: DescribeFileSystems -> DescribeFileSystems -> Bool
== :: DescribeFileSystems -> DescribeFileSystems -> Bool
$c== :: DescribeFileSystems -> DescribeFileSystems -> Bool
Prelude.Eq, ReadPrec [DescribeFileSystems]
ReadPrec DescribeFileSystems
Int -> ReadS DescribeFileSystems
ReadS [DescribeFileSystems]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFileSystems]
$creadListPrec :: ReadPrec [DescribeFileSystems]
readPrec :: ReadPrec DescribeFileSystems
$creadPrec :: ReadPrec DescribeFileSystems
readList :: ReadS [DescribeFileSystems]
$creadList :: ReadS [DescribeFileSystems]
readsPrec :: Int -> ReadS DescribeFileSystems
$creadsPrec :: Int -> ReadS DescribeFileSystems
Prelude.Read, Int -> DescribeFileSystems -> ShowS
[DescribeFileSystems] -> ShowS
DescribeFileSystems -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFileSystems] -> ShowS
$cshowList :: [DescribeFileSystems] -> ShowS
show :: DescribeFileSystems -> String
$cshow :: DescribeFileSystems -> String
showsPrec :: Int -> DescribeFileSystems -> ShowS
$cshowsPrec :: Int -> DescribeFileSystems -> ShowS
Prelude.Show, forall x. Rep DescribeFileSystems x -> DescribeFileSystems
forall x. DescribeFileSystems -> Rep DescribeFileSystems x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeFileSystems x -> DescribeFileSystems
$cfrom :: forall x. DescribeFileSystems -> Rep DescribeFileSystems x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFileSystems' 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:
--
-- 'creationToken', 'describeFileSystems_creationToken' - (Optional) Restricts the list to the file system with this creation
-- token (String). You specify a creation token when you create an Amazon
-- EFS file system.
--
-- 'fileSystemId', 'describeFileSystems_fileSystemId' - (Optional) ID of the file system whose description you want to retrieve
-- (String).
--
-- 'marker', 'describeFileSystems_marker' - (Optional) Opaque pagination token returned from a previous
-- @DescribeFileSystems@ operation (String). If present, specifies to
-- continue the list from where the returning call had left off.
--
-- 'maxItems', 'describeFileSystems_maxItems' - (Optional) Specifies the maximum number of file systems to return in the
-- response (integer). This number is automatically set to 100. The
-- response is paginated at 100 per page if you have more than 100 file
-- systems.
newDescribeFileSystems ::
  DescribeFileSystems
newDescribeFileSystems :: DescribeFileSystems
newDescribeFileSystems =
  DescribeFileSystems'
    { $sel:creationToken:DescribeFileSystems' :: Maybe Text
creationToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemId:DescribeFileSystems' :: Maybe Text
fileSystemId = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeFileSystems' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:DescribeFileSystems' :: Maybe Natural
maxItems = forall a. Maybe a
Prelude.Nothing
    }

-- | (Optional) Restricts the list to the file system with this creation
-- token (String). You specify a creation token when you create an Amazon
-- EFS file system.
describeFileSystems_creationToken :: Lens.Lens' DescribeFileSystems (Prelude.Maybe Prelude.Text)
describeFileSystems_creationToken :: Lens' DescribeFileSystems (Maybe Text)
describeFileSystems_creationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystems' {Maybe Text
creationToken :: Maybe Text
$sel:creationToken:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
creationToken} -> Maybe Text
creationToken) (\s :: DescribeFileSystems
s@DescribeFileSystems' {} Maybe Text
a -> DescribeFileSystems
s {$sel:creationToken:DescribeFileSystems' :: Maybe Text
creationToken = Maybe Text
a} :: DescribeFileSystems)

-- | (Optional) ID of the file system whose description you want to retrieve
-- (String).
describeFileSystems_fileSystemId :: Lens.Lens' DescribeFileSystems (Prelude.Maybe Prelude.Text)
describeFileSystems_fileSystemId :: Lens' DescribeFileSystems (Maybe Text)
describeFileSystems_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystems' {Maybe Text
fileSystemId :: Maybe Text
$sel:fileSystemId:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
fileSystemId} -> Maybe Text
fileSystemId) (\s :: DescribeFileSystems
s@DescribeFileSystems' {} Maybe Text
a -> DescribeFileSystems
s {$sel:fileSystemId:DescribeFileSystems' :: Maybe Text
fileSystemId = Maybe Text
a} :: DescribeFileSystems)

-- | (Optional) Opaque pagination token returned from a previous
-- @DescribeFileSystems@ operation (String). If present, specifies to
-- continue the list from where the returning call had left off.
describeFileSystems_marker :: Lens.Lens' DescribeFileSystems (Prelude.Maybe Prelude.Text)
describeFileSystems_marker :: Lens' DescribeFileSystems (Maybe Text)
describeFileSystems_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystems' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeFileSystems
s@DescribeFileSystems' {} Maybe Text
a -> DescribeFileSystems
s {$sel:marker:DescribeFileSystems' :: Maybe Text
marker = Maybe Text
a} :: DescribeFileSystems)

-- | (Optional) Specifies the maximum number of file systems to return in the
-- response (integer). This number is automatically set to 100. The
-- response is paginated at 100 per page if you have more than 100 file
-- systems.
describeFileSystems_maxItems :: Lens.Lens' DescribeFileSystems (Prelude.Maybe Prelude.Natural)
describeFileSystems_maxItems :: Lens' DescribeFileSystems (Maybe Natural)
describeFileSystems_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystems' {Maybe Natural
maxItems :: Maybe Natural
$sel:maxItems:DescribeFileSystems' :: DescribeFileSystems -> Maybe Natural
maxItems} -> Maybe Natural
maxItems) (\s :: DescribeFileSystems
s@DescribeFileSystems' {} Maybe Natural
a -> DescribeFileSystems
s {$sel:maxItems:DescribeFileSystems' :: Maybe Natural
maxItems = Maybe Natural
a} :: DescribeFileSystems)

instance Core.AWSPager DescribeFileSystems where
  page :: DescribeFileSystems
-> AWSResponse DescribeFileSystems -> Maybe DescribeFileSystems
page DescribeFileSystems
rq AWSResponse DescribeFileSystems
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeFileSystems
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeFileSystemsResponse (Maybe Text)
describeFileSystemsResponse_nextMarker
            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 DescribeFileSystems
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeFileSystemsResponse (Maybe [FileSystemDescription])
describeFileSystemsResponse_fileSystems
            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.$ DescribeFileSystems
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeFileSystems (Maybe Text)
describeFileSystems_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeFileSystems
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeFileSystemsResponse (Maybe Text)
describeFileSystemsResponse_nextMarker
          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 DescribeFileSystems where
  type
    AWSResponse DescribeFileSystems =
      DescribeFileSystemsResponse
  request :: (Service -> Service)
-> DescribeFileSystems -> Request DescribeFileSystems
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeFileSystems
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeFileSystems)))
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 [FileSystemDescription]
-> Maybe Text -> Maybe Text -> Int -> DescribeFileSystemsResponse
DescribeFileSystemsResponse'
            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
"FileSystems" 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
"Marker")
            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
"NextMarker")
            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 DescribeFileSystems where
  hashWithSalt :: Int -> DescribeFileSystems -> Int
hashWithSalt Int
_salt DescribeFileSystems' {Maybe Natural
Maybe Text
maxItems :: Maybe Natural
marker :: Maybe Text
fileSystemId :: Maybe Text
creationToken :: Maybe Text
$sel:maxItems:DescribeFileSystems' :: DescribeFileSystems -> Maybe Natural
$sel:marker:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:fileSystemId:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:creationToken:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
creationToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxItems

instance Prelude.NFData DescribeFileSystems where
  rnf :: DescribeFileSystems -> ()
rnf DescribeFileSystems' {Maybe Natural
Maybe Text
maxItems :: Maybe Natural
marker :: Maybe Text
fileSystemId :: Maybe Text
creationToken :: Maybe Text
$sel:maxItems:DescribeFileSystems' :: DescribeFileSystems -> Maybe Natural
$sel:marker:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:fileSystemId:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:creationToken:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxItems

instance Data.ToHeaders DescribeFileSystems where
  toHeaders :: DescribeFileSystems -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DescribeFileSystems where
  toPath :: DescribeFileSystems -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2015-02-01/file-systems"

instance Data.ToQuery DescribeFileSystems where
  toQuery :: DescribeFileSystems -> QueryString
toQuery DescribeFileSystems' {Maybe Natural
Maybe Text
maxItems :: Maybe Natural
marker :: Maybe Text
fileSystemId :: Maybe Text
creationToken :: Maybe Text
$sel:maxItems:DescribeFileSystems' :: DescribeFileSystems -> Maybe Natural
$sel:marker:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:fileSystemId:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
$sel:creationToken:DescribeFileSystems' :: DescribeFileSystems -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"CreationToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
creationToken,
        ByteString
"FileSystemId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
fileSystemId,
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxItems
      ]

-- | /See:/ 'newDescribeFileSystemsResponse' smart constructor.
data DescribeFileSystemsResponse = DescribeFileSystemsResponse'
  { -- | An array of file system descriptions.
    DescribeFileSystemsResponse -> Maybe [FileSystemDescription]
fileSystems :: Prelude.Maybe [FileSystemDescription],
    -- | Present if provided by caller in the request (String).
    DescribeFileSystemsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | Present if there are more file systems than returned in the response
    -- (String). You can use the @NextMarker@ in the subsequent request to
    -- fetch the descriptions.
    DescribeFileSystemsResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeFileSystemsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeFileSystemsResponse -> DescribeFileSystemsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFileSystemsResponse -> DescribeFileSystemsResponse -> Bool
$c/= :: DescribeFileSystemsResponse -> DescribeFileSystemsResponse -> Bool
== :: DescribeFileSystemsResponse -> DescribeFileSystemsResponse -> Bool
$c== :: DescribeFileSystemsResponse -> DescribeFileSystemsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFileSystemsResponse]
ReadPrec DescribeFileSystemsResponse
Int -> ReadS DescribeFileSystemsResponse
ReadS [DescribeFileSystemsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFileSystemsResponse]
$creadListPrec :: ReadPrec [DescribeFileSystemsResponse]
readPrec :: ReadPrec DescribeFileSystemsResponse
$creadPrec :: ReadPrec DescribeFileSystemsResponse
readList :: ReadS [DescribeFileSystemsResponse]
$creadList :: ReadS [DescribeFileSystemsResponse]
readsPrec :: Int -> ReadS DescribeFileSystemsResponse
$creadsPrec :: Int -> ReadS DescribeFileSystemsResponse
Prelude.Read, Int -> DescribeFileSystemsResponse -> ShowS
[DescribeFileSystemsResponse] -> ShowS
DescribeFileSystemsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFileSystemsResponse] -> ShowS
$cshowList :: [DescribeFileSystemsResponse] -> ShowS
show :: DescribeFileSystemsResponse -> String
$cshow :: DescribeFileSystemsResponse -> String
showsPrec :: Int -> DescribeFileSystemsResponse -> ShowS
$cshowsPrec :: Int -> DescribeFileSystemsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeFileSystemsResponse x -> DescribeFileSystemsResponse
forall x.
DescribeFileSystemsResponse -> Rep DescribeFileSystemsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFileSystemsResponse x -> DescribeFileSystemsResponse
$cfrom :: forall x.
DescribeFileSystemsResponse -> Rep DescribeFileSystemsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFileSystemsResponse' 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:
--
-- 'fileSystems', 'describeFileSystemsResponse_fileSystems' - An array of file system descriptions.
--
-- 'marker', 'describeFileSystemsResponse_marker' - Present if provided by caller in the request (String).
--
-- 'nextMarker', 'describeFileSystemsResponse_nextMarker' - Present if there are more file systems than returned in the response
-- (String). You can use the @NextMarker@ in the subsequent request to
-- fetch the descriptions.
--
-- 'httpStatus', 'describeFileSystemsResponse_httpStatus' - The response's http status code.
newDescribeFileSystemsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeFileSystemsResponse
newDescribeFileSystemsResponse :: Int -> DescribeFileSystemsResponse
newDescribeFileSystemsResponse Int
pHttpStatus_ =
  DescribeFileSystemsResponse'
    { $sel:fileSystems:DescribeFileSystemsResponse' :: Maybe [FileSystemDescription]
fileSystems =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeFileSystemsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:DescribeFileSystemsResponse' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeFileSystemsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of file system descriptions.
describeFileSystemsResponse_fileSystems :: Lens.Lens' DescribeFileSystemsResponse (Prelude.Maybe [FileSystemDescription])
describeFileSystemsResponse_fileSystems :: Lens' DescribeFileSystemsResponse (Maybe [FileSystemDescription])
describeFileSystemsResponse_fileSystems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystemsResponse' {Maybe [FileSystemDescription]
fileSystems :: Maybe [FileSystemDescription]
$sel:fileSystems:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe [FileSystemDescription]
fileSystems} -> Maybe [FileSystemDescription]
fileSystems) (\s :: DescribeFileSystemsResponse
s@DescribeFileSystemsResponse' {} Maybe [FileSystemDescription]
a -> DescribeFileSystemsResponse
s {$sel:fileSystems:DescribeFileSystemsResponse' :: Maybe [FileSystemDescription]
fileSystems = Maybe [FileSystemDescription]
a} :: DescribeFileSystemsResponse) 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

-- | Present if provided by caller in the request (String).
describeFileSystemsResponse_marker :: Lens.Lens' DescribeFileSystemsResponse (Prelude.Maybe Prelude.Text)
describeFileSystemsResponse_marker :: Lens' DescribeFileSystemsResponse (Maybe Text)
describeFileSystemsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystemsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeFileSystemsResponse
s@DescribeFileSystemsResponse' {} Maybe Text
a -> DescribeFileSystemsResponse
s {$sel:marker:DescribeFileSystemsResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeFileSystemsResponse)

-- | Present if there are more file systems than returned in the response
-- (String). You can use the @NextMarker@ in the subsequent request to
-- fetch the descriptions.
describeFileSystemsResponse_nextMarker :: Lens.Lens' DescribeFileSystemsResponse (Prelude.Maybe Prelude.Text)
describeFileSystemsResponse_nextMarker :: Lens' DescribeFileSystemsResponse (Maybe Text)
describeFileSystemsResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFileSystemsResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: DescribeFileSystemsResponse
s@DescribeFileSystemsResponse' {} Maybe Text
a -> DescribeFileSystemsResponse
s {$sel:nextMarker:DescribeFileSystemsResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: DescribeFileSystemsResponse)

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

instance Prelude.NFData DescribeFileSystemsResponse where
  rnf :: DescribeFileSystemsResponse -> ()
rnf DescribeFileSystemsResponse' {Int
Maybe [FileSystemDescription]
Maybe Text
httpStatus :: Int
nextMarker :: Maybe Text
marker :: Maybe Text
fileSystems :: Maybe [FileSystemDescription]
$sel:httpStatus:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Int
$sel:nextMarker:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe Text
$sel:marker:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe Text
$sel:fileSystems:DescribeFileSystemsResponse' :: DescribeFileSystemsResponse -> Maybe [FileSystemDescription]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FileSystemDescription]
fileSystems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus