{-# 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.SSM.GetParametersByPath
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieve information about one or more parameters in a specific
-- hierarchy.
--
-- Request results are returned on a best-effort basis. If you specify
-- @MaxResults@ in the request, the response includes information up to the
-- limit specified. The number of items returned, however, can be between
-- zero and the value of @MaxResults@. If the service reaches an internal
-- limit while processing the results, it stops the operation and returns
-- the matching values up to that point and a @NextToken@. You can specify
-- the @NextToken@ in a subsequent call to get the next set of results.
--
-- This operation returns paginated results.
module Amazonka.SSM.GetParametersByPath
  ( -- * Creating a Request
    GetParametersByPath (..),
    newGetParametersByPath,

    -- * Request Lenses
    getParametersByPath_maxResults,
    getParametersByPath_nextToken,
    getParametersByPath_parameterFilters,
    getParametersByPath_recursive,
    getParametersByPath_withDecryption,
    getParametersByPath_path,

    -- * Destructuring the Response
    GetParametersByPathResponse (..),
    newGetParametersByPathResponse,

    -- * Response Lenses
    getParametersByPathResponse_nextToken,
    getParametersByPathResponse_parameters,
    getParametersByPathResponse_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.SSM.Types

-- | /See:/ 'newGetParametersByPath' smart constructor.
data GetParametersByPath = GetParametersByPath'
  { -- | The maximum number of items to return for this call. The call also
    -- returns a token that you can specify in a subsequent call to get the
    -- next set of results.
    GetParametersByPath -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to start the list. Use this token to get the next set of
    -- results.
    GetParametersByPath -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Filters to limit the request results.
    --
    -- The following @Key@ values are supported for @GetParametersByPath@:
    -- @Type@, @KeyId@, and @Label@.
    --
    -- The following @Key@ values aren\'t supported for @GetParametersByPath@:
    -- @tag@, @DataType@, @Name@, @Path@, and @Tier@.
    GetParametersByPath -> Maybe [ParameterStringFilter]
parameterFilters :: Prelude.Maybe [ParameterStringFilter],
    -- | Retrieve all parameters within a hierarchy.
    --
    -- If a user has access to a path, then the user can access all levels of
    -- that path. For example, if a user has permission to access path @\/a@,
    -- then the user can also access @\/a\/b@. Even if a user has explicitly
    -- been denied access in IAM for parameter @\/a\/b@, they can still call
    -- the GetParametersByPath API operation recursively for @\/a@ and view
    -- @\/a\/b@.
    GetParametersByPath -> Maybe Bool
recursive :: Prelude.Maybe Prelude.Bool,
    -- | Retrieve all parameters in a hierarchy with their value decrypted.
    GetParametersByPath -> Maybe Bool
withDecryption :: Prelude.Maybe Prelude.Bool,
    -- | The hierarchy for the parameter. Hierarchies start with a forward slash
    -- (\/). The hierarchy is the parameter name except the last part of the
    -- parameter. For the API call to succeed, the last part of the parameter
    -- name can\'t be in the path. A parameter name hierarchy can have a
    -- maximum of 15 levels. Here is an example of a hierarchy:
    -- @\/Finance\/Prod\/IAD\/WinServ2016\/license33 @
    GetParametersByPath -> Text
path :: Prelude.Text
  }
  deriving (GetParametersByPath -> GetParametersByPath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParametersByPath -> GetParametersByPath -> Bool
$c/= :: GetParametersByPath -> GetParametersByPath -> Bool
== :: GetParametersByPath -> GetParametersByPath -> Bool
$c== :: GetParametersByPath -> GetParametersByPath -> Bool
Prelude.Eq, ReadPrec [GetParametersByPath]
ReadPrec GetParametersByPath
Int -> ReadS GetParametersByPath
ReadS [GetParametersByPath]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetParametersByPath]
$creadListPrec :: ReadPrec [GetParametersByPath]
readPrec :: ReadPrec GetParametersByPath
$creadPrec :: ReadPrec GetParametersByPath
readList :: ReadS [GetParametersByPath]
$creadList :: ReadS [GetParametersByPath]
readsPrec :: Int -> ReadS GetParametersByPath
$creadsPrec :: Int -> ReadS GetParametersByPath
Prelude.Read, Int -> GetParametersByPath -> ShowS
[GetParametersByPath] -> ShowS
GetParametersByPath -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParametersByPath] -> ShowS
$cshowList :: [GetParametersByPath] -> ShowS
show :: GetParametersByPath -> String
$cshow :: GetParametersByPath -> String
showsPrec :: Int -> GetParametersByPath -> ShowS
$cshowsPrec :: Int -> GetParametersByPath -> ShowS
Prelude.Show, forall x. Rep GetParametersByPath x -> GetParametersByPath
forall x. GetParametersByPath -> Rep GetParametersByPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetParametersByPath x -> GetParametersByPath
$cfrom :: forall x. GetParametersByPath -> Rep GetParametersByPath x
Prelude.Generic)

-- |
-- Create a value of 'GetParametersByPath' 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:
--
-- 'maxResults', 'getParametersByPath_maxResults' - The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
--
-- 'nextToken', 'getParametersByPath_nextToken' - A token to start the list. Use this token to get the next set of
-- results.
--
-- 'parameterFilters', 'getParametersByPath_parameterFilters' - Filters to limit the request results.
--
-- The following @Key@ values are supported for @GetParametersByPath@:
-- @Type@, @KeyId@, and @Label@.
--
-- The following @Key@ values aren\'t supported for @GetParametersByPath@:
-- @tag@, @DataType@, @Name@, @Path@, and @Tier@.
--
-- 'recursive', 'getParametersByPath_recursive' - Retrieve all parameters within a hierarchy.
--
-- If a user has access to a path, then the user can access all levels of
-- that path. For example, if a user has permission to access path @\/a@,
-- then the user can also access @\/a\/b@. Even if a user has explicitly
-- been denied access in IAM for parameter @\/a\/b@, they can still call
-- the GetParametersByPath API operation recursively for @\/a@ and view
-- @\/a\/b@.
--
-- 'withDecryption', 'getParametersByPath_withDecryption' - Retrieve all parameters in a hierarchy with their value decrypted.
--
-- 'path', 'getParametersByPath_path' - The hierarchy for the parameter. Hierarchies start with a forward slash
-- (\/). The hierarchy is the parameter name except the last part of the
-- parameter. For the API call to succeed, the last part of the parameter
-- name can\'t be in the path. A parameter name hierarchy can have a
-- maximum of 15 levels. Here is an example of a hierarchy:
-- @\/Finance\/Prod\/IAD\/WinServ2016\/license33 @
newGetParametersByPath ::
  -- | 'path'
  Prelude.Text ->
  GetParametersByPath
newGetParametersByPath :: Text -> GetParametersByPath
newGetParametersByPath Text
pPath_ =
  GetParametersByPath'
    { $sel:maxResults:GetParametersByPath' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetParametersByPath' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:parameterFilters:GetParametersByPath' :: Maybe [ParameterStringFilter]
parameterFilters = forall a. Maybe a
Prelude.Nothing,
      $sel:recursive:GetParametersByPath' :: Maybe Bool
recursive = forall a. Maybe a
Prelude.Nothing,
      $sel:withDecryption:GetParametersByPath' :: Maybe Bool
withDecryption = forall a. Maybe a
Prelude.Nothing,
      $sel:path:GetParametersByPath' :: Text
path = Text
pPath_
    }

-- | The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
getParametersByPath_maxResults :: Lens.Lens' GetParametersByPath (Prelude.Maybe Prelude.Natural)
getParametersByPath_maxResults :: Lens' GetParametersByPath (Maybe Natural)
getParametersByPath_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetParametersByPath' :: GetParametersByPath -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetParametersByPath
s@GetParametersByPath' {} Maybe Natural
a -> GetParametersByPath
s {$sel:maxResults:GetParametersByPath' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetParametersByPath)

-- | A token to start the list. Use this token to get the next set of
-- results.
getParametersByPath_nextToken :: Lens.Lens' GetParametersByPath (Prelude.Maybe Prelude.Text)
getParametersByPath_nextToken :: Lens' GetParametersByPath (Maybe Text)
getParametersByPath_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetParametersByPath' :: GetParametersByPath -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetParametersByPath
s@GetParametersByPath' {} Maybe Text
a -> GetParametersByPath
s {$sel:nextToken:GetParametersByPath' :: Maybe Text
nextToken = Maybe Text
a} :: GetParametersByPath)

-- | Filters to limit the request results.
--
-- The following @Key@ values are supported for @GetParametersByPath@:
-- @Type@, @KeyId@, and @Label@.
--
-- The following @Key@ values aren\'t supported for @GetParametersByPath@:
-- @tag@, @DataType@, @Name@, @Path@, and @Tier@.
getParametersByPath_parameterFilters :: Lens.Lens' GetParametersByPath (Prelude.Maybe [ParameterStringFilter])
getParametersByPath_parameterFilters :: Lens' GetParametersByPath (Maybe [ParameterStringFilter])
getParametersByPath_parameterFilters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Maybe [ParameterStringFilter]
parameterFilters :: Maybe [ParameterStringFilter]
$sel:parameterFilters:GetParametersByPath' :: GetParametersByPath -> Maybe [ParameterStringFilter]
parameterFilters} -> Maybe [ParameterStringFilter]
parameterFilters) (\s :: GetParametersByPath
s@GetParametersByPath' {} Maybe [ParameterStringFilter]
a -> GetParametersByPath
s {$sel:parameterFilters:GetParametersByPath' :: Maybe [ParameterStringFilter]
parameterFilters = Maybe [ParameterStringFilter]
a} :: GetParametersByPath) 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

-- | Retrieve all parameters within a hierarchy.
--
-- If a user has access to a path, then the user can access all levels of
-- that path. For example, if a user has permission to access path @\/a@,
-- then the user can also access @\/a\/b@. Even if a user has explicitly
-- been denied access in IAM for parameter @\/a\/b@, they can still call
-- the GetParametersByPath API operation recursively for @\/a@ and view
-- @\/a\/b@.
getParametersByPath_recursive :: Lens.Lens' GetParametersByPath (Prelude.Maybe Prelude.Bool)
getParametersByPath_recursive :: Lens' GetParametersByPath (Maybe Bool)
getParametersByPath_recursive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Maybe Bool
recursive :: Maybe Bool
$sel:recursive:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
recursive} -> Maybe Bool
recursive) (\s :: GetParametersByPath
s@GetParametersByPath' {} Maybe Bool
a -> GetParametersByPath
s {$sel:recursive:GetParametersByPath' :: Maybe Bool
recursive = Maybe Bool
a} :: GetParametersByPath)

-- | Retrieve all parameters in a hierarchy with their value decrypted.
getParametersByPath_withDecryption :: Lens.Lens' GetParametersByPath (Prelude.Maybe Prelude.Bool)
getParametersByPath_withDecryption :: Lens' GetParametersByPath (Maybe Bool)
getParametersByPath_withDecryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Maybe Bool
withDecryption :: Maybe Bool
$sel:withDecryption:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
withDecryption} -> Maybe Bool
withDecryption) (\s :: GetParametersByPath
s@GetParametersByPath' {} Maybe Bool
a -> GetParametersByPath
s {$sel:withDecryption:GetParametersByPath' :: Maybe Bool
withDecryption = Maybe Bool
a} :: GetParametersByPath)

-- | The hierarchy for the parameter. Hierarchies start with a forward slash
-- (\/). The hierarchy is the parameter name except the last part of the
-- parameter. For the API call to succeed, the last part of the parameter
-- name can\'t be in the path. A parameter name hierarchy can have a
-- maximum of 15 levels. Here is an example of a hierarchy:
-- @\/Finance\/Prod\/IAD\/WinServ2016\/license33 @
getParametersByPath_path :: Lens.Lens' GetParametersByPath Prelude.Text
getParametersByPath_path :: Lens' GetParametersByPath Text
getParametersByPath_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPath' {Text
path :: Text
$sel:path:GetParametersByPath' :: GetParametersByPath -> Text
path} -> Text
path) (\s :: GetParametersByPath
s@GetParametersByPath' {} Text
a -> GetParametersByPath
s {$sel:path:GetParametersByPath' :: Text
path = Text
a} :: GetParametersByPath)

instance Core.AWSPager GetParametersByPath where
  page :: GetParametersByPath
-> AWSResponse GetParametersByPath -> Maybe GetParametersByPath
page GetParametersByPath
rq AWSResponse GetParametersByPath
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetParametersByPath
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetParametersByPathResponse (Maybe Text)
getParametersByPathResponse_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 GetParametersByPath
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetParametersByPathResponse (Maybe [Parameter])
getParametersByPathResponse_parameters
            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.$ GetParametersByPath
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetParametersByPath (Maybe Text)
getParametersByPath_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetParametersByPath
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetParametersByPathResponse (Maybe Text)
getParametersByPathResponse_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 GetParametersByPath where
  type
    AWSResponse GetParametersByPath =
      GetParametersByPathResponse
  request :: (Service -> Service)
-> GetParametersByPath -> Request GetParametersByPath
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 GetParametersByPath
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetParametersByPath)))
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 [Parameter] -> Int -> GetParametersByPathResponse
GetParametersByPathResponse'
            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
"NextToken")
            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
"Parameters" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetParametersByPath where
  hashWithSalt :: Int -> GetParametersByPath -> Int
hashWithSalt Int
_salt GetParametersByPath' {Maybe Bool
Maybe Natural
Maybe [ParameterStringFilter]
Maybe Text
Text
path :: Text
withDecryption :: Maybe Bool
recursive :: Maybe Bool
parameterFilters :: Maybe [ParameterStringFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:GetParametersByPath' :: GetParametersByPath -> Text
$sel:withDecryption:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:recursive:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:parameterFilters:GetParametersByPath' :: GetParametersByPath -> Maybe [ParameterStringFilter]
$sel:nextToken:GetParametersByPath' :: GetParametersByPath -> Maybe Text
$sel:maxResults:GetParametersByPath' :: GetParametersByPath -> Maybe Natural
..} =
    Int
_salt
      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 [ParameterStringFilter]
parameterFilters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
recursive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
withDecryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
path

instance Prelude.NFData GetParametersByPath where
  rnf :: GetParametersByPath -> ()
rnf GetParametersByPath' {Maybe Bool
Maybe Natural
Maybe [ParameterStringFilter]
Maybe Text
Text
path :: Text
withDecryption :: Maybe Bool
recursive :: Maybe Bool
parameterFilters :: Maybe [ParameterStringFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:GetParametersByPath' :: GetParametersByPath -> Text
$sel:withDecryption:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:recursive:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:parameterFilters:GetParametersByPath' :: GetParametersByPath -> Maybe [ParameterStringFilter]
$sel:nextToken:GetParametersByPath' :: GetParametersByPath -> Maybe Text
$sel:maxResults:GetParametersByPath' :: GetParametersByPath -> Maybe Natural
..} =
    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 [ParameterStringFilter]
parameterFilters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
recursive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
withDecryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
path

instance Data.ToHeaders GetParametersByPath where
  toHeaders :: GetParametersByPath -> 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
"AmazonSSM.GetParametersByPath" ::
                          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 GetParametersByPath where
  toJSON :: GetParametersByPath -> Value
toJSON GetParametersByPath' {Maybe Bool
Maybe Natural
Maybe [ParameterStringFilter]
Maybe Text
Text
path :: Text
withDecryption :: Maybe Bool
recursive :: Maybe Bool
parameterFilters :: Maybe [ParameterStringFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:GetParametersByPath' :: GetParametersByPath -> Text
$sel:withDecryption:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:recursive:GetParametersByPath' :: GetParametersByPath -> Maybe Bool
$sel:parameterFilters:GetParametersByPath' :: GetParametersByPath -> Maybe [ParameterStringFilter]
$sel:nextToken:GetParametersByPath' :: GetParametersByPath -> Maybe Text
$sel:maxResults:GetParametersByPath' :: GetParametersByPath -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"ParameterFilters" 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 [ParameterStringFilter]
parameterFilters,
            (Key
"Recursive" 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 Bool
recursive,
            (Key
"WithDecryption" 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 Bool
withDecryption,
            forall a. a -> Maybe a
Prelude.Just (Key
"Path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
path)
          ]
      )

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

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

-- | /See:/ 'newGetParametersByPathResponse' smart constructor.
data GetParametersByPathResponse = GetParametersByPathResponse'
  { -- | The token for the next set of items to return. Use this token to get the
    -- next set of results.
    GetParametersByPathResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of parameters found in the specified hierarchy.
    GetParametersByPathResponse -> Maybe [Parameter]
parameters :: Prelude.Maybe [Parameter],
    -- | The response's http status code.
    GetParametersByPathResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetParametersByPathResponse -> GetParametersByPathResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParametersByPathResponse -> GetParametersByPathResponse -> Bool
$c/= :: GetParametersByPathResponse -> GetParametersByPathResponse -> Bool
== :: GetParametersByPathResponse -> GetParametersByPathResponse -> Bool
$c== :: GetParametersByPathResponse -> GetParametersByPathResponse -> Bool
Prelude.Eq, Int -> GetParametersByPathResponse -> ShowS
[GetParametersByPathResponse] -> ShowS
GetParametersByPathResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParametersByPathResponse] -> ShowS
$cshowList :: [GetParametersByPathResponse] -> ShowS
show :: GetParametersByPathResponse -> String
$cshow :: GetParametersByPathResponse -> String
showsPrec :: Int -> GetParametersByPathResponse -> ShowS
$cshowsPrec :: Int -> GetParametersByPathResponse -> ShowS
Prelude.Show, forall x.
Rep GetParametersByPathResponse x -> GetParametersByPathResponse
forall x.
GetParametersByPathResponse -> Rep GetParametersByPathResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetParametersByPathResponse x -> GetParametersByPathResponse
$cfrom :: forall x.
GetParametersByPathResponse -> Rep GetParametersByPathResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetParametersByPathResponse' 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:
--
-- 'nextToken', 'getParametersByPathResponse_nextToken' - The token for the next set of items to return. Use this token to get the
-- next set of results.
--
-- 'parameters', 'getParametersByPathResponse_parameters' - A list of parameters found in the specified hierarchy.
--
-- 'httpStatus', 'getParametersByPathResponse_httpStatus' - The response's http status code.
newGetParametersByPathResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetParametersByPathResponse
newGetParametersByPathResponse :: Int -> GetParametersByPathResponse
newGetParametersByPathResponse Int
pHttpStatus_ =
  GetParametersByPathResponse'
    { $sel:nextToken:GetParametersByPathResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:parameters:GetParametersByPathResponse' :: Maybe [Parameter]
parameters = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetParametersByPathResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token for the next set of items to return. Use this token to get the
-- next set of results.
getParametersByPathResponse_nextToken :: Lens.Lens' GetParametersByPathResponse (Prelude.Maybe Prelude.Text)
getParametersByPathResponse_nextToken :: Lens' GetParametersByPathResponse (Maybe Text)
getParametersByPathResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPathResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetParametersByPathResponse' :: GetParametersByPathResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetParametersByPathResponse
s@GetParametersByPathResponse' {} Maybe Text
a -> GetParametersByPathResponse
s {$sel:nextToken:GetParametersByPathResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetParametersByPathResponse)

-- | A list of parameters found in the specified hierarchy.
getParametersByPathResponse_parameters :: Lens.Lens' GetParametersByPathResponse (Prelude.Maybe [Parameter])
getParametersByPathResponse_parameters :: Lens' GetParametersByPathResponse (Maybe [Parameter])
getParametersByPathResponse_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetParametersByPathResponse' {Maybe [Parameter]
parameters :: Maybe [Parameter]
$sel:parameters:GetParametersByPathResponse' :: GetParametersByPathResponse -> Maybe [Parameter]
parameters} -> Maybe [Parameter]
parameters) (\s :: GetParametersByPathResponse
s@GetParametersByPathResponse' {} Maybe [Parameter]
a -> GetParametersByPathResponse
s {$sel:parameters:GetParametersByPathResponse' :: Maybe [Parameter]
parameters = Maybe [Parameter]
a} :: GetParametersByPathResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetParametersByPathResponse where
  rnf :: GetParametersByPathResponse -> ()
rnf GetParametersByPathResponse' {Int
Maybe [Parameter]
Maybe Text
httpStatus :: Int
parameters :: Maybe [Parameter]
nextToken :: Maybe Text
$sel:httpStatus:GetParametersByPathResponse' :: GetParametersByPathResponse -> Int
$sel:parameters:GetParametersByPathResponse' :: GetParametersByPathResponse -> Maybe [Parameter]
$sel:nextToken:GetParametersByPathResponse' :: GetParametersByPathResponse -> 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 Maybe [Parameter]
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus