{-# 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.IoT.ListPolicyVersions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the versions of the specified policy and identifies the default
-- version.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ListPolicyVersions>
-- action.
module Amazonka.IoT.ListPolicyVersions
  ( -- * Creating a Request
    ListPolicyVersions (..),
    newListPolicyVersions,

    -- * Request Lenses
    listPolicyVersions_policyName,

    -- * Destructuring the Response
    ListPolicyVersionsResponse (..),
    newListPolicyVersionsResponse,

    -- * Response Lenses
    listPolicyVersionsResponse_policyVersions,
    listPolicyVersionsResponse_httpStatus,
  )
where

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

-- | The input for the ListPolicyVersions operation.
--
-- /See:/ 'newListPolicyVersions' smart constructor.
data ListPolicyVersions = ListPolicyVersions'
  { -- | The policy name.
    ListPolicyVersions -> Text
policyName :: Prelude.Text
  }
  deriving (ListPolicyVersions -> ListPolicyVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPolicyVersions -> ListPolicyVersions -> Bool
$c/= :: ListPolicyVersions -> ListPolicyVersions -> Bool
== :: ListPolicyVersions -> ListPolicyVersions -> Bool
$c== :: ListPolicyVersions -> ListPolicyVersions -> Bool
Prelude.Eq, ReadPrec [ListPolicyVersions]
ReadPrec ListPolicyVersions
Int -> ReadS ListPolicyVersions
ReadS [ListPolicyVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPolicyVersions]
$creadListPrec :: ReadPrec [ListPolicyVersions]
readPrec :: ReadPrec ListPolicyVersions
$creadPrec :: ReadPrec ListPolicyVersions
readList :: ReadS [ListPolicyVersions]
$creadList :: ReadS [ListPolicyVersions]
readsPrec :: Int -> ReadS ListPolicyVersions
$creadsPrec :: Int -> ReadS ListPolicyVersions
Prelude.Read, Int -> ListPolicyVersions -> ShowS
[ListPolicyVersions] -> ShowS
ListPolicyVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPolicyVersions] -> ShowS
$cshowList :: [ListPolicyVersions] -> ShowS
show :: ListPolicyVersions -> String
$cshow :: ListPolicyVersions -> String
showsPrec :: Int -> ListPolicyVersions -> ShowS
$cshowsPrec :: Int -> ListPolicyVersions -> ShowS
Prelude.Show, forall x. Rep ListPolicyVersions x -> ListPolicyVersions
forall x. ListPolicyVersions -> Rep ListPolicyVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPolicyVersions x -> ListPolicyVersions
$cfrom :: forall x. ListPolicyVersions -> Rep ListPolicyVersions x
Prelude.Generic)

-- |
-- Create a value of 'ListPolicyVersions' 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:
--
-- 'policyName', 'listPolicyVersions_policyName' - The policy name.
newListPolicyVersions ::
  -- | 'policyName'
  Prelude.Text ->
  ListPolicyVersions
newListPolicyVersions :: Text -> ListPolicyVersions
newListPolicyVersions Text
pPolicyName_ =
  ListPolicyVersions' {$sel:policyName:ListPolicyVersions' :: Text
policyName = Text
pPolicyName_}

-- | The policy name.
listPolicyVersions_policyName :: Lens.Lens' ListPolicyVersions Prelude.Text
listPolicyVersions_policyName :: Lens' ListPolicyVersions Text
listPolicyVersions_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPolicyVersions' {Text
policyName :: Text
$sel:policyName:ListPolicyVersions' :: ListPolicyVersions -> Text
policyName} -> Text
policyName) (\s :: ListPolicyVersions
s@ListPolicyVersions' {} Text
a -> ListPolicyVersions
s {$sel:policyName:ListPolicyVersions' :: Text
policyName = Text
a} :: ListPolicyVersions)

instance Core.AWSRequest ListPolicyVersions where
  type
    AWSResponse ListPolicyVersions =
      ListPolicyVersionsResponse
  request :: (Service -> Service)
-> ListPolicyVersions -> Request ListPolicyVersions
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 ListPolicyVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListPolicyVersions)))
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 [PolicyVersion] -> Int -> ListPolicyVersionsResponse
ListPolicyVersionsResponse'
            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
"policyVersions" 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 ListPolicyVersions where
  hashWithSalt :: Int -> ListPolicyVersions -> Int
hashWithSalt Int
_salt ListPolicyVersions' {Text
policyName :: Text
$sel:policyName:ListPolicyVersions' :: ListPolicyVersions -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName

instance Prelude.NFData ListPolicyVersions where
  rnf :: ListPolicyVersions -> ()
rnf ListPolicyVersions' {Text
policyName :: Text
$sel:policyName:ListPolicyVersions' :: ListPolicyVersions -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
policyName

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

instance Data.ToPath ListPolicyVersions where
  toPath :: ListPolicyVersions -> ByteString
toPath ListPolicyVersions' {Text
policyName :: Text
$sel:policyName:ListPolicyVersions' :: ListPolicyVersions -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyName, ByteString
"/version"]

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

-- | The output from the ListPolicyVersions operation.
--
-- /See:/ 'newListPolicyVersionsResponse' smart constructor.
data ListPolicyVersionsResponse = ListPolicyVersionsResponse'
  { -- | The policy versions.
    ListPolicyVersionsResponse -> Maybe [PolicyVersion]
policyVersions :: Prelude.Maybe [PolicyVersion],
    -- | The response's http status code.
    ListPolicyVersionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPolicyVersionsResponse -> ListPolicyVersionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPolicyVersionsResponse -> ListPolicyVersionsResponse -> Bool
$c/= :: ListPolicyVersionsResponse -> ListPolicyVersionsResponse -> Bool
== :: ListPolicyVersionsResponse -> ListPolicyVersionsResponse -> Bool
$c== :: ListPolicyVersionsResponse -> ListPolicyVersionsResponse -> Bool
Prelude.Eq, ReadPrec [ListPolicyVersionsResponse]
ReadPrec ListPolicyVersionsResponse
Int -> ReadS ListPolicyVersionsResponse
ReadS [ListPolicyVersionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPolicyVersionsResponse]
$creadListPrec :: ReadPrec [ListPolicyVersionsResponse]
readPrec :: ReadPrec ListPolicyVersionsResponse
$creadPrec :: ReadPrec ListPolicyVersionsResponse
readList :: ReadS [ListPolicyVersionsResponse]
$creadList :: ReadS [ListPolicyVersionsResponse]
readsPrec :: Int -> ReadS ListPolicyVersionsResponse
$creadsPrec :: Int -> ReadS ListPolicyVersionsResponse
Prelude.Read, Int -> ListPolicyVersionsResponse -> ShowS
[ListPolicyVersionsResponse] -> ShowS
ListPolicyVersionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPolicyVersionsResponse] -> ShowS
$cshowList :: [ListPolicyVersionsResponse] -> ShowS
show :: ListPolicyVersionsResponse -> String
$cshow :: ListPolicyVersionsResponse -> String
showsPrec :: Int -> ListPolicyVersionsResponse -> ShowS
$cshowsPrec :: Int -> ListPolicyVersionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListPolicyVersionsResponse x -> ListPolicyVersionsResponse
forall x.
ListPolicyVersionsResponse -> Rep ListPolicyVersionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPolicyVersionsResponse x -> ListPolicyVersionsResponse
$cfrom :: forall x.
ListPolicyVersionsResponse -> Rep ListPolicyVersionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPolicyVersionsResponse' 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:
--
-- 'policyVersions', 'listPolicyVersionsResponse_policyVersions' - The policy versions.
--
-- 'httpStatus', 'listPolicyVersionsResponse_httpStatus' - The response's http status code.
newListPolicyVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPolicyVersionsResponse
newListPolicyVersionsResponse :: Int -> ListPolicyVersionsResponse
newListPolicyVersionsResponse Int
pHttpStatus_ =
  ListPolicyVersionsResponse'
    { $sel:policyVersions:ListPolicyVersionsResponse' :: Maybe [PolicyVersion]
policyVersions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPolicyVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The policy versions.
listPolicyVersionsResponse_policyVersions :: Lens.Lens' ListPolicyVersionsResponse (Prelude.Maybe [PolicyVersion])
listPolicyVersionsResponse_policyVersions :: Lens' ListPolicyVersionsResponse (Maybe [PolicyVersion])
listPolicyVersionsResponse_policyVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPolicyVersionsResponse' {Maybe [PolicyVersion]
policyVersions :: Maybe [PolicyVersion]
$sel:policyVersions:ListPolicyVersionsResponse' :: ListPolicyVersionsResponse -> Maybe [PolicyVersion]
policyVersions} -> Maybe [PolicyVersion]
policyVersions) (\s :: ListPolicyVersionsResponse
s@ListPolicyVersionsResponse' {} Maybe [PolicyVersion]
a -> ListPolicyVersionsResponse
s {$sel:policyVersions:ListPolicyVersionsResponse' :: Maybe [PolicyVersion]
policyVersions = Maybe [PolicyVersion]
a} :: ListPolicyVersionsResponse) 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.
listPolicyVersionsResponse_httpStatus :: Lens.Lens' ListPolicyVersionsResponse Prelude.Int
listPolicyVersionsResponse_httpStatus :: Lens' ListPolicyVersionsResponse Int
listPolicyVersionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPolicyVersionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPolicyVersionsResponse' :: ListPolicyVersionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPolicyVersionsResponse
s@ListPolicyVersionsResponse' {} Int
a -> ListPolicyVersionsResponse
s {$sel:httpStatus:ListPolicyVersionsResponse' :: Int
httpStatus = Int
a} :: ListPolicyVersionsResponse)

instance Prelude.NFData ListPolicyVersionsResponse where
  rnf :: ListPolicyVersionsResponse -> ()
rnf ListPolicyVersionsResponse' {Int
Maybe [PolicyVersion]
httpStatus :: Int
policyVersions :: Maybe [PolicyVersion]
$sel:httpStatus:ListPolicyVersionsResponse' :: ListPolicyVersionsResponse -> Int
$sel:policyVersions:ListPolicyVersionsResponse' :: ListPolicyVersionsResponse -> Maybe [PolicyVersion]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [PolicyVersion]
policyVersions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus