{-# 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 #-}
module Amazonka.IoTSiteWise.Types.AssetPropertyValue where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTSiteWise.Types.Quality
import Amazonka.IoTSiteWise.Types.TimeInNanos
import Amazonka.IoTSiteWise.Types.Variant
import qualified Amazonka.Prelude as Prelude
data AssetPropertyValue = AssetPropertyValue'
{
AssetPropertyValue -> Maybe Quality
quality :: Prelude.Maybe Quality,
AssetPropertyValue -> Variant
value :: Variant,
AssetPropertyValue -> TimeInNanos
timestamp :: TimeInNanos
}
deriving (AssetPropertyValue -> AssetPropertyValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssetPropertyValue -> AssetPropertyValue -> Bool
$c/= :: AssetPropertyValue -> AssetPropertyValue -> Bool
== :: AssetPropertyValue -> AssetPropertyValue -> Bool
$c== :: AssetPropertyValue -> AssetPropertyValue -> Bool
Prelude.Eq, ReadPrec [AssetPropertyValue]
ReadPrec AssetPropertyValue
Int -> ReadS AssetPropertyValue
ReadS [AssetPropertyValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssetPropertyValue]
$creadListPrec :: ReadPrec [AssetPropertyValue]
readPrec :: ReadPrec AssetPropertyValue
$creadPrec :: ReadPrec AssetPropertyValue
readList :: ReadS [AssetPropertyValue]
$creadList :: ReadS [AssetPropertyValue]
readsPrec :: Int -> ReadS AssetPropertyValue
$creadsPrec :: Int -> ReadS AssetPropertyValue
Prelude.Read, Int -> AssetPropertyValue -> ShowS
[AssetPropertyValue] -> ShowS
AssetPropertyValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssetPropertyValue] -> ShowS
$cshowList :: [AssetPropertyValue] -> ShowS
show :: AssetPropertyValue -> String
$cshow :: AssetPropertyValue -> String
showsPrec :: Int -> AssetPropertyValue -> ShowS
$cshowsPrec :: Int -> AssetPropertyValue -> ShowS
Prelude.Show, forall x. Rep AssetPropertyValue x -> AssetPropertyValue
forall x. AssetPropertyValue -> Rep AssetPropertyValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssetPropertyValue x -> AssetPropertyValue
$cfrom :: forall x. AssetPropertyValue -> Rep AssetPropertyValue x
Prelude.Generic)
newAssetPropertyValue ::
Variant ->
TimeInNanos ->
AssetPropertyValue
newAssetPropertyValue :: Variant -> TimeInNanos -> AssetPropertyValue
newAssetPropertyValue Variant
pValue_ TimeInNanos
pTimestamp_ =
AssetPropertyValue'
{ $sel:quality:AssetPropertyValue' :: Maybe Quality
quality = forall a. Maybe a
Prelude.Nothing,
$sel:value:AssetPropertyValue' :: Variant
value = Variant
pValue_,
$sel:timestamp:AssetPropertyValue' :: TimeInNanos
timestamp = TimeInNanos
pTimestamp_
}
assetPropertyValue_quality :: Lens.Lens' AssetPropertyValue (Prelude.Maybe Quality)
assetPropertyValue_quality :: Lens' AssetPropertyValue (Maybe Quality)
assetPropertyValue_quality = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetPropertyValue' {Maybe Quality
quality :: Maybe Quality
$sel:quality:AssetPropertyValue' :: AssetPropertyValue -> Maybe Quality
quality} -> Maybe Quality
quality) (\s :: AssetPropertyValue
s@AssetPropertyValue' {} Maybe Quality
a -> AssetPropertyValue
s {$sel:quality:AssetPropertyValue' :: Maybe Quality
quality = Maybe Quality
a} :: AssetPropertyValue)
assetPropertyValue_value :: Lens.Lens' AssetPropertyValue Variant
assetPropertyValue_value :: Lens' AssetPropertyValue Variant
assetPropertyValue_value = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetPropertyValue' {Variant
value :: Variant
$sel:value:AssetPropertyValue' :: AssetPropertyValue -> Variant
value} -> Variant
value) (\s :: AssetPropertyValue
s@AssetPropertyValue' {} Variant
a -> AssetPropertyValue
s {$sel:value:AssetPropertyValue' :: Variant
value = Variant
a} :: AssetPropertyValue)
assetPropertyValue_timestamp :: Lens.Lens' AssetPropertyValue TimeInNanos
assetPropertyValue_timestamp :: Lens' AssetPropertyValue TimeInNanos
assetPropertyValue_timestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetPropertyValue' {TimeInNanos
timestamp :: TimeInNanos
$sel:timestamp:AssetPropertyValue' :: AssetPropertyValue -> TimeInNanos
timestamp} -> TimeInNanos
timestamp) (\s :: AssetPropertyValue
s@AssetPropertyValue' {} TimeInNanos
a -> AssetPropertyValue
s {$sel:timestamp:AssetPropertyValue' :: TimeInNanos
timestamp = TimeInNanos
a} :: AssetPropertyValue)
instance Data.FromJSON AssetPropertyValue where
parseJSON :: Value -> Parser AssetPropertyValue
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"AssetPropertyValue"
( \Object
x ->
Maybe Quality -> Variant -> TimeInNanos -> AssetPropertyValue
AssetPropertyValue'
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
"quality")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"value")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"timestamp")
)
instance Prelude.Hashable AssetPropertyValue where
hashWithSalt :: Int -> AssetPropertyValue -> Int
hashWithSalt Int
_salt AssetPropertyValue' {Maybe Quality
TimeInNanos
Variant
timestamp :: TimeInNanos
value :: Variant
quality :: Maybe Quality
$sel:timestamp:AssetPropertyValue' :: AssetPropertyValue -> TimeInNanos
$sel:value:AssetPropertyValue' :: AssetPropertyValue -> Variant
$sel:quality:AssetPropertyValue' :: AssetPropertyValue -> Maybe Quality
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Quality
quality
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Variant
value
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TimeInNanos
timestamp
instance Prelude.NFData AssetPropertyValue where
rnf :: AssetPropertyValue -> ()
rnf AssetPropertyValue' {Maybe Quality
TimeInNanos
Variant
timestamp :: TimeInNanos
value :: Variant
quality :: Maybe Quality
$sel:timestamp:AssetPropertyValue' :: AssetPropertyValue -> TimeInNanos
$sel:value:AssetPropertyValue' :: AssetPropertyValue -> Variant
$sel:quality:AssetPropertyValue' :: AssetPropertyValue -> Maybe Quality
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Quality
quality
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Variant
value
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimeInNanos
timestamp
instance Data.ToJSON AssetPropertyValue where
toJSON :: AssetPropertyValue -> Value
toJSON AssetPropertyValue' {Maybe Quality
TimeInNanos
Variant
timestamp :: TimeInNanos
value :: Variant
quality :: Maybe Quality
$sel:timestamp:AssetPropertyValue' :: AssetPropertyValue -> TimeInNanos
$sel:value:AssetPropertyValue' :: AssetPropertyValue -> Variant
$sel:quality:AssetPropertyValue' :: AssetPropertyValue -> Maybe Quality
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"quality" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Quality
quality,
forall a. a -> Maybe a
Prelude.Just (Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Variant
value),
forall a. a -> Maybe a
Prelude.Just (Key
"timestamp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TimeInNanos
timestamp)
]
)