{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.VehicleStatus
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.IoTFleetWise.Types.VehicleStatus 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.VehicleState
import qualified Amazonka.Prelude as Prelude

-- | Information about the state of a vehicle and how it relates to the
-- status of a campaign.
--
-- /See:/ 'newVehicleStatus' smart constructor.
data VehicleStatus = VehicleStatus'
  { -- | The name of a campaign.
    VehicleStatus -> Maybe Text
campaignName :: Prelude.Maybe Prelude.Text,
    -- | The state of a vehicle, which can be one of the following:
    --
    -- -   @CREATED@ - Amazon Web Services IoT FleetWise sucessfully created
    --     the vehicle.
    --
    -- -   @READY@ - The vehicle is ready to receive a campaign deployment.
    --
    -- -   @HEALTHY@ - A campaign deployment was delivered to the vehicle.
    --
    -- -   @SUSPENDED@ - A campaign associated with the vehicle was suspended
    --     and data collection was paused.
    --
    -- -   @DELETING@ - Amazon Web Services IoT FleetWise is removing a
    --     campaign from the vehicle.
    VehicleStatus -> Maybe VehicleState
status :: Prelude.Maybe VehicleState,
    -- | The unique ID of the vehicle.
    VehicleStatus -> Maybe Text
vehicleName :: Prelude.Maybe Prelude.Text
  }
  deriving (VehicleStatus -> VehicleStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VehicleStatus -> VehicleStatus -> Bool
$c/= :: VehicleStatus -> VehicleStatus -> Bool
== :: VehicleStatus -> VehicleStatus -> Bool
$c== :: VehicleStatus -> VehicleStatus -> Bool
Prelude.Eq, ReadPrec [VehicleStatus]
ReadPrec VehicleStatus
Int -> ReadS VehicleStatus
ReadS [VehicleStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VehicleStatus]
$creadListPrec :: ReadPrec [VehicleStatus]
readPrec :: ReadPrec VehicleStatus
$creadPrec :: ReadPrec VehicleStatus
readList :: ReadS [VehicleStatus]
$creadList :: ReadS [VehicleStatus]
readsPrec :: Int -> ReadS VehicleStatus
$creadsPrec :: Int -> ReadS VehicleStatus
Prelude.Read, Int -> VehicleStatus -> ShowS
[VehicleStatus] -> ShowS
VehicleStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VehicleStatus] -> ShowS
$cshowList :: [VehicleStatus] -> ShowS
show :: VehicleStatus -> String
$cshow :: VehicleStatus -> String
showsPrec :: Int -> VehicleStatus -> ShowS
$cshowsPrec :: Int -> VehicleStatus -> ShowS
Prelude.Show, forall x. Rep VehicleStatus x -> VehicleStatus
forall x. VehicleStatus -> Rep VehicleStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VehicleStatus x -> VehicleStatus
$cfrom :: forall x. VehicleStatus -> Rep VehicleStatus x
Prelude.Generic)

-- |
-- Create a value of 'VehicleStatus' 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:
--
-- 'campaignName', 'vehicleStatus_campaignName' - The name of a campaign.
--
-- 'status', 'vehicleStatus_status' - The state of a vehicle, which can be one of the following:
--
-- -   @CREATED@ - Amazon Web Services IoT FleetWise sucessfully created
--     the vehicle.
--
-- -   @READY@ - The vehicle is ready to receive a campaign deployment.
--
-- -   @HEALTHY@ - A campaign deployment was delivered to the vehicle.
--
-- -   @SUSPENDED@ - A campaign associated with the vehicle was suspended
--     and data collection was paused.
--
-- -   @DELETING@ - Amazon Web Services IoT FleetWise is removing a
--     campaign from the vehicle.
--
-- 'vehicleName', 'vehicleStatus_vehicleName' - The unique ID of the vehicle.
newVehicleStatus ::
  VehicleStatus
newVehicleStatus :: VehicleStatus
newVehicleStatus =
  VehicleStatus'
    { $sel:campaignName:VehicleStatus' :: Maybe Text
campaignName = forall a. Maybe a
Prelude.Nothing,
      $sel:status:VehicleStatus' :: Maybe VehicleState
status = forall a. Maybe a
Prelude.Nothing,
      $sel:vehicleName:VehicleStatus' :: Maybe Text
vehicleName = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of a campaign.
vehicleStatus_campaignName :: Lens.Lens' VehicleStatus (Prelude.Maybe Prelude.Text)
vehicleStatus_campaignName :: Lens' VehicleStatus (Maybe Text)
vehicleStatus_campaignName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VehicleStatus' {Maybe Text
campaignName :: Maybe Text
$sel:campaignName:VehicleStatus' :: VehicleStatus -> Maybe Text
campaignName} -> Maybe Text
campaignName) (\s :: VehicleStatus
s@VehicleStatus' {} Maybe Text
a -> VehicleStatus
s {$sel:campaignName:VehicleStatus' :: Maybe Text
campaignName = Maybe Text
a} :: VehicleStatus)

-- | The state of a vehicle, which can be one of the following:
--
-- -   @CREATED@ - Amazon Web Services IoT FleetWise sucessfully created
--     the vehicle.
--
-- -   @READY@ - The vehicle is ready to receive a campaign deployment.
--
-- -   @HEALTHY@ - A campaign deployment was delivered to the vehicle.
--
-- -   @SUSPENDED@ - A campaign associated with the vehicle was suspended
--     and data collection was paused.
--
-- -   @DELETING@ - Amazon Web Services IoT FleetWise is removing a
--     campaign from the vehicle.
vehicleStatus_status :: Lens.Lens' VehicleStatus (Prelude.Maybe VehicleState)
vehicleStatus_status :: Lens' VehicleStatus (Maybe VehicleState)
vehicleStatus_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VehicleStatus' {Maybe VehicleState
status :: Maybe VehicleState
$sel:status:VehicleStatus' :: VehicleStatus -> Maybe VehicleState
status} -> Maybe VehicleState
status) (\s :: VehicleStatus
s@VehicleStatus' {} Maybe VehicleState
a -> VehicleStatus
s {$sel:status:VehicleStatus' :: Maybe VehicleState
status = Maybe VehicleState
a} :: VehicleStatus)

-- | The unique ID of the vehicle.
vehicleStatus_vehicleName :: Lens.Lens' VehicleStatus (Prelude.Maybe Prelude.Text)
vehicleStatus_vehicleName :: Lens' VehicleStatus (Maybe Text)
vehicleStatus_vehicleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VehicleStatus' {Maybe Text
vehicleName :: Maybe Text
$sel:vehicleName:VehicleStatus' :: VehicleStatus -> Maybe Text
vehicleName} -> Maybe Text
vehicleName) (\s :: VehicleStatus
s@VehicleStatus' {} Maybe Text
a -> VehicleStatus
s {$sel:vehicleName:VehicleStatus' :: Maybe Text
vehicleName = Maybe Text
a} :: VehicleStatus)

instance Data.FromJSON VehicleStatus where
  parseJSON :: Value -> Parser VehicleStatus
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"VehicleStatus"
      ( \Object
x ->
          Maybe Text -> Maybe VehicleState -> Maybe Text -> VehicleStatus
VehicleStatus'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"campaignName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"vehicleName")
      )

instance Prelude.Hashable VehicleStatus where
  hashWithSalt :: Int -> VehicleStatus -> Int
hashWithSalt Int
_salt VehicleStatus' {Maybe Text
Maybe VehicleState
vehicleName :: Maybe Text
status :: Maybe VehicleState
campaignName :: Maybe Text
$sel:vehicleName:VehicleStatus' :: VehicleStatus -> Maybe Text
$sel:status:VehicleStatus' :: VehicleStatus -> Maybe VehicleState
$sel:campaignName:VehicleStatus' :: VehicleStatus -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
campaignName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VehicleState
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vehicleName

instance Prelude.NFData VehicleStatus where
  rnf :: VehicleStatus -> ()
rnf VehicleStatus' {Maybe Text
Maybe VehicleState
vehicleName :: Maybe Text
status :: Maybe VehicleState
campaignName :: Maybe Text
$sel:vehicleName:VehicleStatus' :: VehicleStatus -> Maybe Text
$sel:status:VehicleStatus' :: VehicleStatus -> Maybe VehicleState
$sel:campaignName:VehicleStatus' :: VehicleStatus -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
campaignName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VehicleState
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vehicleName