{-# 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.GetJourney
-- 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 a journey.
module Amazonka.Pinpoint.GetJourney
  ( -- * Creating a Request
    GetJourney (..),
    newGetJourney,

    -- * Request Lenses
    getJourney_journeyId,
    getJourney_applicationId,

    -- * Destructuring the Response
    GetJourneyResponse (..),
    newGetJourneyResponse,

    -- * Response Lenses
    getJourneyResponse_httpStatus,
    getJourneyResponse_journeyResponse,
  )
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:/ 'newGetJourney' smart constructor.
data GetJourney = GetJourney'
  { -- | The unique identifier for the journey.
    GetJourney -> Text
journeyId :: Prelude.Text,
    -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    GetJourney -> Text
applicationId :: Prelude.Text
  }
  deriving (GetJourney -> GetJourney -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJourney -> GetJourney -> Bool
$c/= :: GetJourney -> GetJourney -> Bool
== :: GetJourney -> GetJourney -> Bool
$c== :: GetJourney -> GetJourney -> Bool
Prelude.Eq, ReadPrec [GetJourney]
ReadPrec GetJourney
Int -> ReadS GetJourney
ReadS [GetJourney]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJourney]
$creadListPrec :: ReadPrec [GetJourney]
readPrec :: ReadPrec GetJourney
$creadPrec :: ReadPrec GetJourney
readList :: ReadS [GetJourney]
$creadList :: ReadS [GetJourney]
readsPrec :: Int -> ReadS GetJourney
$creadsPrec :: Int -> ReadS GetJourney
Prelude.Read, Int -> GetJourney -> ShowS
[GetJourney] -> ShowS
GetJourney -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJourney] -> ShowS
$cshowList :: [GetJourney] -> ShowS
show :: GetJourney -> String
$cshow :: GetJourney -> String
showsPrec :: Int -> GetJourney -> ShowS
$cshowsPrec :: Int -> GetJourney -> ShowS
Prelude.Show, forall x. Rep GetJourney x -> GetJourney
forall x. GetJourney -> Rep GetJourney x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJourney x -> GetJourney
$cfrom :: forall x. GetJourney -> Rep GetJourney x
Prelude.Generic)

-- |
-- Create a value of 'GetJourney' 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:
--
-- 'journeyId', 'getJourney_journeyId' - The unique identifier for the journey.
--
-- 'applicationId', 'getJourney_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newGetJourney ::
  -- | 'journeyId'
  Prelude.Text ->
  -- | 'applicationId'
  Prelude.Text ->
  GetJourney
newGetJourney :: Text -> Text -> GetJourney
newGetJourney Text
pJourneyId_ Text
pApplicationId_ =
  GetJourney'
    { $sel:journeyId:GetJourney' :: Text
journeyId = Text
pJourneyId_,
      $sel:applicationId:GetJourney' :: Text
applicationId = Text
pApplicationId_
    }

-- | The unique identifier for the journey.
getJourney_journeyId :: Lens.Lens' GetJourney Prelude.Text
getJourney_journeyId :: Lens' GetJourney Text
getJourney_journeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJourney' {Text
journeyId :: Text
$sel:journeyId:GetJourney' :: GetJourney -> Text
journeyId} -> Text
journeyId) (\s :: GetJourney
s@GetJourney' {} Text
a -> GetJourney
s {$sel:journeyId:GetJourney' :: Text
journeyId = Text
a} :: GetJourney)

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

instance Core.AWSRequest GetJourney where
  type AWSResponse GetJourney = GetJourneyResponse
  request :: (Service -> Service) -> GetJourney -> Request GetJourney
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 GetJourney
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJourney)))
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 -> JourneyResponse -> GetJourneyResponse
GetJourneyResponse'
            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 GetJourney where
  hashWithSalt :: Int -> GetJourney -> Int
hashWithSalt Int
_salt GetJourney' {Text
applicationId :: Text
journeyId :: Text
$sel:applicationId:GetJourney' :: GetJourney -> Text
$sel:journeyId:GetJourney' :: GetJourney -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
journeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

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

instance Data.ToHeaders GetJourney where
  toHeaders :: GetJourney -> 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 GetJourney where
  toPath :: GetJourney -> ByteString
toPath GetJourney' {Text
applicationId :: Text
journeyId :: Text
$sel:applicationId:GetJourney' :: GetJourney -> Text
$sel:journeyId:GetJourney' :: GetJourney -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/journeys/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
journeyId
      ]

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

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

-- |
-- Create a value of 'GetJourneyResponse' 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', 'getJourneyResponse_httpStatus' - The response's http status code.
--
-- 'journeyResponse', 'getJourneyResponse_journeyResponse' - Undocumented member.
newGetJourneyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'journeyResponse'
  JourneyResponse ->
  GetJourneyResponse
newGetJourneyResponse :: Int -> JourneyResponse -> GetJourneyResponse
newGetJourneyResponse Int
pHttpStatus_ JourneyResponse
pJourneyResponse_ =
  GetJourneyResponse'
    { $sel:httpStatus:GetJourneyResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:journeyResponse:GetJourneyResponse' :: JourneyResponse
journeyResponse = JourneyResponse
pJourneyResponse_
    }

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

-- | Undocumented member.
getJourneyResponse_journeyResponse :: Lens.Lens' GetJourneyResponse JourneyResponse
getJourneyResponse_journeyResponse :: Lens' GetJourneyResponse JourneyResponse
getJourneyResponse_journeyResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJourneyResponse' {JourneyResponse
journeyResponse :: JourneyResponse
$sel:journeyResponse:GetJourneyResponse' :: GetJourneyResponse -> JourneyResponse
journeyResponse} -> JourneyResponse
journeyResponse) (\s :: GetJourneyResponse
s@GetJourneyResponse' {} JourneyResponse
a -> GetJourneyResponse
s {$sel:journeyResponse:GetJourneyResponse' :: JourneyResponse
journeyResponse = JourneyResponse
a} :: GetJourneyResponse)

instance Prelude.NFData GetJourneyResponse where
  rnf :: GetJourneyResponse -> ()
rnf GetJourneyResponse' {Int
JourneyResponse
journeyResponse :: JourneyResponse
httpStatus :: Int
$sel:journeyResponse:GetJourneyResponse' :: GetJourneyResponse -> JourneyResponse
$sel:httpStatus:GetJourneyResponse' :: GetJourneyResponse -> 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 JourneyResponse
journeyResponse