{-# 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.IoTFleetWise.GetFleet
-- 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 a fleet.
module Amazonka.IoTFleetWise.GetFleet
  ( -- * Creating a Request
    GetFleet (..),
    newGetFleet,

    -- * Request Lenses
    getFleet_fleetId,

    -- * Destructuring the Response
    GetFleetResponse (..),
    newGetFleetResponse,

    -- * Response Lenses
    getFleetResponse_description,
    getFleetResponse_httpStatus,
    getFleetResponse_id,
    getFleetResponse_arn,
    getFleetResponse_signalCatalogArn,
    getFleetResponse_creationTime,
    getFleetResponse_lastModificationTime,
  )
where

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

-- | /See:/ 'newGetFleet' smart constructor.
data GetFleet = GetFleet'
  { -- | The ID of the fleet to retrieve information about.
    GetFleet -> Text
fleetId :: Prelude.Text
  }
  deriving (GetFleet -> GetFleet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFleet -> GetFleet -> Bool
$c/= :: GetFleet -> GetFleet -> Bool
== :: GetFleet -> GetFleet -> Bool
$c== :: GetFleet -> GetFleet -> Bool
Prelude.Eq, ReadPrec [GetFleet]
ReadPrec GetFleet
Int -> ReadS GetFleet
ReadS [GetFleet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFleet]
$creadListPrec :: ReadPrec [GetFleet]
readPrec :: ReadPrec GetFleet
$creadPrec :: ReadPrec GetFleet
readList :: ReadS [GetFleet]
$creadList :: ReadS [GetFleet]
readsPrec :: Int -> ReadS GetFleet
$creadsPrec :: Int -> ReadS GetFleet
Prelude.Read, Int -> GetFleet -> ShowS
[GetFleet] -> ShowS
GetFleet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFleet] -> ShowS
$cshowList :: [GetFleet] -> ShowS
show :: GetFleet -> String
$cshow :: GetFleet -> String
showsPrec :: Int -> GetFleet -> ShowS
$cshowsPrec :: Int -> GetFleet -> ShowS
Prelude.Show, forall x. Rep GetFleet x -> GetFleet
forall x. GetFleet -> Rep GetFleet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFleet x -> GetFleet
$cfrom :: forall x. GetFleet -> Rep GetFleet x
Prelude.Generic)

-- |
-- Create a value of 'GetFleet' 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:
--
-- 'fleetId', 'getFleet_fleetId' - The ID of the fleet to retrieve information about.
newGetFleet ::
  -- | 'fleetId'
  Prelude.Text ->
  GetFleet
newGetFleet :: Text -> GetFleet
newGetFleet Text
pFleetId_ =
  GetFleet' {$sel:fleetId:GetFleet' :: Text
fleetId = Text
pFleetId_}

-- | The ID of the fleet to retrieve information about.
getFleet_fleetId :: Lens.Lens' GetFleet Prelude.Text
getFleet_fleetId :: Lens' GetFleet Text
getFleet_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleet' {Text
fleetId :: Text
$sel:fleetId:GetFleet' :: GetFleet -> Text
fleetId} -> Text
fleetId) (\s :: GetFleet
s@GetFleet' {} Text
a -> GetFleet
s {$sel:fleetId:GetFleet' :: Text
fleetId = Text
a} :: GetFleet)

instance Core.AWSRequest GetFleet where
  type AWSResponse GetFleet = GetFleetResponse
  request :: (Service -> Service) -> GetFleet -> Request GetFleet
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 GetFleet
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFleet)))
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
-> Int
-> Text
-> Text
-> Text
-> POSIX
-> POSIX
-> GetFleetResponse
GetFleetResponse'
            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
"description")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"signalCatalogArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"creationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"lastModificationTime")
      )

instance Prelude.Hashable GetFleet where
  hashWithSalt :: Int -> GetFleet -> Int
hashWithSalt Int
_salt GetFleet' {Text
fleetId :: Text
$sel:fleetId:GetFleet' :: GetFleet -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId

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

instance Data.ToHeaders GetFleet where
  toHeaders :: GetFleet -> 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
"IoTAutobahnControlPlane.GetFleet" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetFleet where
  toJSON :: GetFleet -> Value
toJSON GetFleet' {Text
fleetId :: Text
$sel:fleetId:GetFleet' :: GetFleet -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"fleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetId)]
      )

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

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

-- | /See:/ 'newGetFleetResponse' smart constructor.
data GetFleetResponse = GetFleetResponse'
  { -- | A brief description of the fleet.
    GetFleetResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetFleetResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the fleet.
    GetFleetResponse -> Text
id :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the fleet.
    GetFleetResponse -> Text
arn :: Prelude.Text,
    -- | The ARN of a signal catalog associated with the fleet.
    GetFleetResponse -> Text
signalCatalogArn :: Prelude.Text,
    -- | The time the fleet was created in seconds since epoch (January 1, 1970
    -- at midnight UTC time).
    GetFleetResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The time the fleet was last updated, in seconds since epoch (January 1,
    -- 1970 at midnight UTC time).
    GetFleetResponse -> POSIX
lastModificationTime :: Data.POSIX
  }
  deriving (GetFleetResponse -> GetFleetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFleetResponse -> GetFleetResponse -> Bool
$c/= :: GetFleetResponse -> GetFleetResponse -> Bool
== :: GetFleetResponse -> GetFleetResponse -> Bool
$c== :: GetFleetResponse -> GetFleetResponse -> Bool
Prelude.Eq, ReadPrec [GetFleetResponse]
ReadPrec GetFleetResponse
Int -> ReadS GetFleetResponse
ReadS [GetFleetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFleetResponse]
$creadListPrec :: ReadPrec [GetFleetResponse]
readPrec :: ReadPrec GetFleetResponse
$creadPrec :: ReadPrec GetFleetResponse
readList :: ReadS [GetFleetResponse]
$creadList :: ReadS [GetFleetResponse]
readsPrec :: Int -> ReadS GetFleetResponse
$creadsPrec :: Int -> ReadS GetFleetResponse
Prelude.Read, Int -> GetFleetResponse -> ShowS
[GetFleetResponse] -> ShowS
GetFleetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFleetResponse] -> ShowS
$cshowList :: [GetFleetResponse] -> ShowS
show :: GetFleetResponse -> String
$cshow :: GetFleetResponse -> String
showsPrec :: Int -> GetFleetResponse -> ShowS
$cshowsPrec :: Int -> GetFleetResponse -> ShowS
Prelude.Show, forall x. Rep GetFleetResponse x -> GetFleetResponse
forall x. GetFleetResponse -> Rep GetFleetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFleetResponse x -> GetFleetResponse
$cfrom :: forall x. GetFleetResponse -> Rep GetFleetResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFleetResponse' 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:
--
-- 'description', 'getFleetResponse_description' - A brief description of the fleet.
--
-- 'httpStatus', 'getFleetResponse_httpStatus' - The response's http status code.
--
-- 'id', 'getFleetResponse_id' - The ID of the fleet.
--
-- 'arn', 'getFleetResponse_arn' - The Amazon Resource Name (ARN) of the fleet.
--
-- 'signalCatalogArn', 'getFleetResponse_signalCatalogArn' - The ARN of a signal catalog associated with the fleet.
--
-- 'creationTime', 'getFleetResponse_creationTime' - The time the fleet was created in seconds since epoch (January 1, 1970
-- at midnight UTC time).
--
-- 'lastModificationTime', 'getFleetResponse_lastModificationTime' - The time the fleet was last updated, in seconds since epoch (January 1,
-- 1970 at midnight UTC time).
newGetFleetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'id'
  Prelude.Text ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'signalCatalogArn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModificationTime'
  Prelude.UTCTime ->
  GetFleetResponse
newGetFleetResponse :: Int
-> Text -> Text -> Text -> UTCTime -> UTCTime -> GetFleetResponse
newGetFleetResponse
  Int
pHttpStatus_
  Text
pId_
  Text
pArn_
  Text
pSignalCatalogArn_
  UTCTime
pCreationTime_
  UTCTime
pLastModificationTime_ =
    GetFleetResponse'
      { $sel:description:GetFleetResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetFleetResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:id:GetFleetResponse' :: Text
id = Text
pId_,
        $sel:arn:GetFleetResponse' :: Text
arn = Text
pArn_,
        $sel:signalCatalogArn:GetFleetResponse' :: Text
signalCatalogArn = Text
pSignalCatalogArn_,
        $sel:creationTime:GetFleetResponse' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModificationTime:GetFleetResponse' :: POSIX
lastModificationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModificationTime_
      }

-- | A brief description of the fleet.
getFleetResponse_description :: Lens.Lens' GetFleetResponse (Prelude.Maybe Prelude.Text)
getFleetResponse_description :: Lens' GetFleetResponse (Maybe Text)
getFleetResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetFleetResponse' :: GetFleetResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetFleetResponse
s@GetFleetResponse' {} Maybe Text
a -> GetFleetResponse
s {$sel:description:GetFleetResponse' :: Maybe Text
description = Maybe Text
a} :: GetFleetResponse)

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

-- | The ID of the fleet.
getFleetResponse_id :: Lens.Lens' GetFleetResponse Prelude.Text
getFleetResponse_id :: Lens' GetFleetResponse Text
getFleetResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {Text
id :: Text
$sel:id:GetFleetResponse' :: GetFleetResponse -> Text
id} -> Text
id) (\s :: GetFleetResponse
s@GetFleetResponse' {} Text
a -> GetFleetResponse
s {$sel:id:GetFleetResponse' :: Text
id = Text
a} :: GetFleetResponse)

-- | The Amazon Resource Name (ARN) of the fleet.
getFleetResponse_arn :: Lens.Lens' GetFleetResponse Prelude.Text
getFleetResponse_arn :: Lens' GetFleetResponse Text
getFleetResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {Text
arn :: Text
$sel:arn:GetFleetResponse' :: GetFleetResponse -> Text
arn} -> Text
arn) (\s :: GetFleetResponse
s@GetFleetResponse' {} Text
a -> GetFleetResponse
s {$sel:arn:GetFleetResponse' :: Text
arn = Text
a} :: GetFleetResponse)

-- | The ARN of a signal catalog associated with the fleet.
getFleetResponse_signalCatalogArn :: Lens.Lens' GetFleetResponse Prelude.Text
getFleetResponse_signalCatalogArn :: Lens' GetFleetResponse Text
getFleetResponse_signalCatalogArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {Text
signalCatalogArn :: Text
$sel:signalCatalogArn:GetFleetResponse' :: GetFleetResponse -> Text
signalCatalogArn} -> Text
signalCatalogArn) (\s :: GetFleetResponse
s@GetFleetResponse' {} Text
a -> GetFleetResponse
s {$sel:signalCatalogArn:GetFleetResponse' :: Text
signalCatalogArn = Text
a} :: GetFleetResponse)

-- | The time the fleet was created in seconds since epoch (January 1, 1970
-- at midnight UTC time).
getFleetResponse_creationTime :: Lens.Lens' GetFleetResponse Prelude.UTCTime
getFleetResponse_creationTime :: Lens' GetFleetResponse UTCTime
getFleetResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:GetFleetResponse' :: GetFleetResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: GetFleetResponse
s@GetFleetResponse' {} POSIX
a -> GetFleetResponse
s {$sel:creationTime:GetFleetResponse' :: POSIX
creationTime = POSIX
a} :: GetFleetResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time the fleet was last updated, in seconds since epoch (January 1,
-- 1970 at midnight UTC time).
getFleetResponse_lastModificationTime :: Lens.Lens' GetFleetResponse Prelude.UTCTime
getFleetResponse_lastModificationTime :: Lens' GetFleetResponse UTCTime
getFleetResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFleetResponse' {POSIX
lastModificationTime :: POSIX
$sel:lastModificationTime:GetFleetResponse' :: GetFleetResponse -> POSIX
lastModificationTime} -> POSIX
lastModificationTime) (\s :: GetFleetResponse
s@GetFleetResponse' {} POSIX
a -> GetFleetResponse
s {$sel:lastModificationTime:GetFleetResponse' :: POSIX
lastModificationTime = POSIX
a} :: GetFleetResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData GetFleetResponse where
  rnf :: GetFleetResponse -> ()
rnf GetFleetResponse' {Int
Maybe Text
Text
POSIX
lastModificationTime :: POSIX
creationTime :: POSIX
signalCatalogArn :: Text
arn :: Text
id :: Text
httpStatus :: Int
description :: Maybe Text
$sel:lastModificationTime:GetFleetResponse' :: GetFleetResponse -> POSIX
$sel:creationTime:GetFleetResponse' :: GetFleetResponse -> POSIX
$sel:signalCatalogArn:GetFleetResponse' :: GetFleetResponse -> Text
$sel:arn:GetFleetResponse' :: GetFleetResponse -> Text
$sel:id:GetFleetResponse' :: GetFleetResponse -> Text
$sel:httpStatus:GetFleetResponse' :: GetFleetResponse -> Int
$sel:description:GetFleetResponse' :: GetFleetResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
signalCatalogArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModificationTime