{-# 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.Pinpoint.ListJourneys
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about the status, configuration, and other
-- settings for all the journeys that are associated with an application.
module Amazonka.Pinpoint.ListJourneys
  ( -- * Creating a Request
    ListJourneys (..),
    newListJourneys,

    -- * Request Lenses
    listJourneys_pageSize,
    listJourneys_token,
    listJourneys_applicationId,

    -- * Destructuring the Response
    ListJourneysResponse (..),
    newListJourneysResponse,

    -- * Response Lenses
    listJourneysResponse_httpStatus,
    listJourneysResponse_journeysResponse,
  )
where

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

-- | /See:/ 'newListJourneys' smart constructor.
data ListJourneys = ListJourneys'
  { -- | The maximum number of items to include in each page of a paginated
    -- response. This parameter is not supported for application, campaign, and
    -- journey metrics.
    ListJourneys -> Maybe Text
pageSize :: Prelude.Maybe Prelude.Text,
    -- | The NextToken string that specifies which page of results to return in a
    -- paginated response.
    ListJourneys -> Maybe Text
token :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    ListJourneys -> Text
applicationId :: Prelude.Text
  }
  deriving (ListJourneys -> ListJourneys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListJourneys -> ListJourneys -> Bool
$c/= :: ListJourneys -> ListJourneys -> Bool
== :: ListJourneys -> ListJourneys -> Bool
$c== :: ListJourneys -> ListJourneys -> Bool
Prelude.Eq, ReadPrec [ListJourneys]
ReadPrec ListJourneys
Int -> ReadS ListJourneys
ReadS [ListJourneys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListJourneys]
$creadListPrec :: ReadPrec [ListJourneys]
readPrec :: ReadPrec ListJourneys
$creadPrec :: ReadPrec ListJourneys
readList :: ReadS [ListJourneys]
$creadList :: ReadS [ListJourneys]
readsPrec :: Int -> ReadS ListJourneys
$creadsPrec :: Int -> ReadS ListJourneys
Prelude.Read, Int -> ListJourneys -> ShowS
[ListJourneys] -> ShowS
ListJourneys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListJourneys] -> ShowS
$cshowList :: [ListJourneys] -> ShowS
show :: ListJourneys -> String
$cshow :: ListJourneys -> String
showsPrec :: Int -> ListJourneys -> ShowS
$cshowsPrec :: Int -> ListJourneys -> ShowS
Prelude.Show, forall x. Rep ListJourneys x -> ListJourneys
forall x. ListJourneys -> Rep ListJourneys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListJourneys x -> ListJourneys
$cfrom :: forall x. ListJourneys -> Rep ListJourneys x
Prelude.Generic)

-- |
-- Create a value of 'ListJourneys' 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:
--
-- 'pageSize', 'listJourneys_pageSize' - The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
--
-- 'token', 'listJourneys_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
--
-- 'applicationId', 'listJourneys_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newListJourneys ::
  -- | 'applicationId'
  Prelude.Text ->
  ListJourneys
newListJourneys :: Text -> ListJourneys
newListJourneys Text
pApplicationId_ =
  ListJourneys'
    { $sel:pageSize:ListJourneys' :: Maybe Text
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:token:ListJourneys' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:ListJourneys' :: Text
applicationId = Text
pApplicationId_
    }

-- | The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
listJourneys_pageSize :: Lens.Lens' ListJourneys (Prelude.Maybe Prelude.Text)
listJourneys_pageSize :: Lens' ListJourneys (Maybe Text)
listJourneys_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJourneys' {Maybe Text
pageSize :: Maybe Text
$sel:pageSize:ListJourneys' :: ListJourneys -> Maybe Text
pageSize} -> Maybe Text
pageSize) (\s :: ListJourneys
s@ListJourneys' {} Maybe Text
a -> ListJourneys
s {$sel:pageSize:ListJourneys' :: Maybe Text
pageSize = Maybe Text
a} :: ListJourneys)

-- | The NextToken string that specifies which page of results to return in a
-- paginated response.
listJourneys_token :: Lens.Lens' ListJourneys (Prelude.Maybe Prelude.Text)
listJourneys_token :: Lens' ListJourneys (Maybe Text)
listJourneys_token = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJourneys' {Maybe Text
token :: Maybe Text
$sel:token:ListJourneys' :: ListJourneys -> Maybe Text
token} -> Maybe Text
token) (\s :: ListJourneys
s@ListJourneys' {} Maybe Text
a -> ListJourneys
s {$sel:token:ListJourneys' :: Maybe Text
token = Maybe Text
a} :: ListJourneys)

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
listJourneys_applicationId :: Lens.Lens' ListJourneys Prelude.Text
listJourneys_applicationId :: Lens' ListJourneys Text
listJourneys_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJourneys' {Text
applicationId :: Text
$sel:applicationId:ListJourneys' :: ListJourneys -> Text
applicationId} -> Text
applicationId) (\s :: ListJourneys
s@ListJourneys' {} Text
a -> ListJourneys
s {$sel:applicationId:ListJourneys' :: Text
applicationId = Text
a} :: ListJourneys)

instance Core.AWSRequest ListJourneys where
  type AWSResponse ListJourneys = ListJourneysResponse
  request :: (Service -> Service) -> ListJourneys -> Request ListJourneys
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 ListJourneys
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListJourneys)))
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 ->
          Int -> JourneysResponse -> ListJourneysResponse
ListJourneysResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable ListJourneys where
  hashWithSalt :: Int -> ListJourneys -> Int
hashWithSalt Int
_salt ListJourneys' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:ListJourneys' :: ListJourneys -> Text
$sel:token:ListJourneys' :: ListJourneys -> Maybe Text
$sel:pageSize:ListJourneys' :: ListJourneys -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
token
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

instance Prelude.NFData ListJourneys where
  rnf :: ListJourneys -> ()
rnf ListJourneys' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:ListJourneys' :: ListJourneys -> Text
$sel:token:ListJourneys' :: ListJourneys -> Maybe Text
$sel:pageSize:ListJourneys' :: ListJourneys -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
token
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId

instance Data.ToHeaders ListJourneys where
  toHeaders :: ListJourneys -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath ListJourneys where
  toPath :: ListJourneys -> ByteString
toPath ListJourneys' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:ListJourneys' :: ListJourneys -> Text
$sel:token:ListJourneys' :: ListJourneys -> Maybe Text
$sel:pageSize:ListJourneys' :: ListJourneys -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/apps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId, ByteString
"/journeys"]

instance Data.ToQuery ListJourneys where
  toQuery :: ListJourneys -> QueryString
toQuery ListJourneys' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:ListJourneys' :: ListJourneys -> Text
$sel:token:ListJourneys' :: ListJourneys -> Maybe Text
$sel:pageSize:ListJourneys' :: ListJourneys -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"page-size" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
pageSize, ByteString
"token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
token]

-- | /See:/ 'newListJourneysResponse' smart constructor.
data ListJourneysResponse = ListJourneysResponse'
  { -- | The response's http status code.
    ListJourneysResponse -> Int
httpStatus :: Prelude.Int,
    ListJourneysResponse -> JourneysResponse
journeysResponse :: JourneysResponse
  }
  deriving (ListJourneysResponse -> ListJourneysResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListJourneysResponse -> ListJourneysResponse -> Bool
$c/= :: ListJourneysResponse -> ListJourneysResponse -> Bool
== :: ListJourneysResponse -> ListJourneysResponse -> Bool
$c== :: ListJourneysResponse -> ListJourneysResponse -> Bool
Prelude.Eq, ReadPrec [ListJourneysResponse]
ReadPrec ListJourneysResponse
Int -> ReadS ListJourneysResponse
ReadS [ListJourneysResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListJourneysResponse]
$creadListPrec :: ReadPrec [ListJourneysResponse]
readPrec :: ReadPrec ListJourneysResponse
$creadPrec :: ReadPrec ListJourneysResponse
readList :: ReadS [ListJourneysResponse]
$creadList :: ReadS [ListJourneysResponse]
readsPrec :: Int -> ReadS ListJourneysResponse
$creadsPrec :: Int -> ReadS ListJourneysResponse
Prelude.Read, Int -> ListJourneysResponse -> ShowS
[ListJourneysResponse] -> ShowS
ListJourneysResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListJourneysResponse] -> ShowS
$cshowList :: [ListJourneysResponse] -> ShowS
show :: ListJourneysResponse -> String
$cshow :: ListJourneysResponse -> String
showsPrec :: Int -> ListJourneysResponse -> ShowS
$cshowsPrec :: Int -> ListJourneysResponse -> ShowS
Prelude.Show, forall x. Rep ListJourneysResponse x -> ListJourneysResponse
forall x. ListJourneysResponse -> Rep ListJourneysResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListJourneysResponse x -> ListJourneysResponse
$cfrom :: forall x. ListJourneysResponse -> Rep ListJourneysResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListJourneysResponse' 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:
--
-- 'httpStatus', 'listJourneysResponse_httpStatus' - The response's http status code.
--
-- 'journeysResponse', 'listJourneysResponse_journeysResponse' - Undocumented member.
newListJourneysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'journeysResponse'
  JourneysResponse ->
  ListJourneysResponse
newListJourneysResponse :: Int -> JourneysResponse -> ListJourneysResponse
newListJourneysResponse
  Int
pHttpStatus_
  JourneysResponse
pJourneysResponse_ =
    ListJourneysResponse'
      { $sel:httpStatus:ListJourneysResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:journeysResponse:ListJourneysResponse' :: JourneysResponse
journeysResponse = JourneysResponse
pJourneysResponse_
      }

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

-- | Undocumented member.
listJourneysResponse_journeysResponse :: Lens.Lens' ListJourneysResponse JourneysResponse
listJourneysResponse_journeysResponse :: Lens' ListJourneysResponse JourneysResponse
listJourneysResponse_journeysResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJourneysResponse' {JourneysResponse
journeysResponse :: JourneysResponse
$sel:journeysResponse:ListJourneysResponse' :: ListJourneysResponse -> JourneysResponse
journeysResponse} -> JourneysResponse
journeysResponse) (\s :: ListJourneysResponse
s@ListJourneysResponse' {} JourneysResponse
a -> ListJourneysResponse
s {$sel:journeysResponse:ListJourneysResponse' :: JourneysResponse
journeysResponse = JourneysResponse
a} :: ListJourneysResponse)

instance Prelude.NFData ListJourneysResponse where
  rnf :: ListJourneysResponse -> ()
rnf ListJourneysResponse' {Int
JourneysResponse
journeysResponse :: JourneysResponse
httpStatus :: Int
$sel:journeysResponse:ListJourneysResponse' :: ListJourneysResponse -> JourneysResponse
$sel:httpStatus:ListJourneysResponse' :: ListJourneysResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JourneysResponse
journeysResponse