{-# 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 #-}
module Amazonka.Location.GetDevicePosition
(
GetDevicePosition (..),
newGetDevicePosition,
getDevicePosition_deviceId,
getDevicePosition_trackerName,
GetDevicePositionResponse (..),
newGetDevicePositionResponse,
getDevicePositionResponse_accuracy,
getDevicePositionResponse_deviceId,
getDevicePositionResponse_positionProperties,
getDevicePositionResponse_httpStatus,
getDevicePositionResponse_position,
getDevicePositionResponse_receivedTime,
getDevicePositionResponse_sampleTime,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Location.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data GetDevicePosition = GetDevicePosition'
{
GetDevicePosition -> Text
deviceId :: Prelude.Text,
GetDevicePosition -> Text
trackerName :: Prelude.Text
}
deriving (GetDevicePosition -> GetDevicePosition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDevicePosition -> GetDevicePosition -> Bool
$c/= :: GetDevicePosition -> GetDevicePosition -> Bool
== :: GetDevicePosition -> GetDevicePosition -> Bool
$c== :: GetDevicePosition -> GetDevicePosition -> Bool
Prelude.Eq, ReadPrec [GetDevicePosition]
ReadPrec GetDevicePosition
Int -> ReadS GetDevicePosition
ReadS [GetDevicePosition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDevicePosition]
$creadListPrec :: ReadPrec [GetDevicePosition]
readPrec :: ReadPrec GetDevicePosition
$creadPrec :: ReadPrec GetDevicePosition
readList :: ReadS [GetDevicePosition]
$creadList :: ReadS [GetDevicePosition]
readsPrec :: Int -> ReadS GetDevicePosition
$creadsPrec :: Int -> ReadS GetDevicePosition
Prelude.Read, Int -> GetDevicePosition -> ShowS
[GetDevicePosition] -> ShowS
GetDevicePosition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDevicePosition] -> ShowS
$cshowList :: [GetDevicePosition] -> ShowS
show :: GetDevicePosition -> String
$cshow :: GetDevicePosition -> String
showsPrec :: Int -> GetDevicePosition -> ShowS
$cshowsPrec :: Int -> GetDevicePosition -> ShowS
Prelude.Show, forall x. Rep GetDevicePosition x -> GetDevicePosition
forall x. GetDevicePosition -> Rep GetDevicePosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDevicePosition x -> GetDevicePosition
$cfrom :: forall x. GetDevicePosition -> Rep GetDevicePosition x
Prelude.Generic)
newGetDevicePosition ::
Prelude.Text ->
Prelude.Text ->
GetDevicePosition
newGetDevicePosition :: Text -> Text -> GetDevicePosition
newGetDevicePosition Text
pDeviceId_ Text
pTrackerName_ =
GetDevicePosition'
{ $sel:deviceId:GetDevicePosition' :: Text
deviceId = Text
pDeviceId_,
$sel:trackerName:GetDevicePosition' :: Text
trackerName = Text
pTrackerName_
}
getDevicePosition_deviceId :: Lens.Lens' GetDevicePosition Prelude.Text
getDevicePosition_deviceId :: Lens' GetDevicePosition Text
getDevicePosition_deviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePosition' {Text
deviceId :: Text
$sel:deviceId:GetDevicePosition' :: GetDevicePosition -> Text
deviceId} -> Text
deviceId) (\s :: GetDevicePosition
s@GetDevicePosition' {} Text
a -> GetDevicePosition
s {$sel:deviceId:GetDevicePosition' :: Text
deviceId = Text
a} :: GetDevicePosition)
getDevicePosition_trackerName :: Lens.Lens' GetDevicePosition Prelude.Text
getDevicePosition_trackerName :: Lens' GetDevicePosition Text
getDevicePosition_trackerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePosition' {Text
trackerName :: Text
$sel:trackerName:GetDevicePosition' :: GetDevicePosition -> Text
trackerName} -> Text
trackerName) (\s :: GetDevicePosition
s@GetDevicePosition' {} Text
a -> GetDevicePosition
s {$sel:trackerName:GetDevicePosition' :: Text
trackerName = Text
a} :: GetDevicePosition)
instance Core.AWSRequest GetDevicePosition where
type
AWSResponse GetDevicePosition =
GetDevicePositionResponse
request :: (Service -> Service)
-> GetDevicePosition -> Request GetDevicePosition
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 GetDevicePosition
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse GetDevicePosition)))
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 PositionalAccuracy
-> Maybe Text
-> Maybe (Sensitive (HashMap Text Text))
-> Int
-> Sensitive (NonEmpty Double)
-> ISO8601
-> ISO8601
-> GetDevicePositionResponse
GetDevicePositionResponse'
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
"Accuracy")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DeviceId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PositionProperties"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
)
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
"Position")
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
"ReceivedTime")
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
"SampleTime")
)
instance Prelude.Hashable GetDevicePosition where
hashWithSalt :: Int -> GetDevicePosition -> Int
hashWithSalt Int
_salt GetDevicePosition' {Text
trackerName :: Text
deviceId :: Text
$sel:trackerName:GetDevicePosition' :: GetDevicePosition -> Text
$sel:deviceId:GetDevicePosition' :: GetDevicePosition -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deviceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
trackerName
instance Prelude.NFData GetDevicePosition where
rnf :: GetDevicePosition -> ()
rnf GetDevicePosition' {Text
trackerName :: Text
deviceId :: Text
$sel:trackerName:GetDevicePosition' :: GetDevicePosition -> Text
$sel:deviceId:GetDevicePosition' :: GetDevicePosition -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
deviceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
trackerName
instance Data.ToHeaders GetDevicePosition where
toHeaders :: GetDevicePosition -> 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 GetDevicePosition where
toPath :: GetDevicePosition -> ByteString
toPath GetDevicePosition' {Text
trackerName :: Text
deviceId :: Text
$sel:trackerName:GetDevicePosition' :: GetDevicePosition -> Text
$sel:deviceId:GetDevicePosition' :: GetDevicePosition -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/tracking/v0/trackers/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
trackerName,
ByteString
"/devices/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
deviceId,
ByteString
"/positions/latest"
]
instance Data.ToQuery GetDevicePosition where
toQuery :: GetDevicePosition -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetDevicePositionResponse = GetDevicePositionResponse'
{
GetDevicePositionResponse -> Maybe PositionalAccuracy
accuracy :: Prelude.Maybe PositionalAccuracy,
GetDevicePositionResponse -> Maybe Text
deviceId :: Prelude.Maybe Prelude.Text,
GetDevicePositionResponse -> Maybe (Sensitive (HashMap Text Text))
positionProperties :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
GetDevicePositionResponse -> Int
httpStatus :: Prelude.Int,
GetDevicePositionResponse -> Sensitive (NonEmpty Double)
position :: Data.Sensitive (Prelude.NonEmpty Prelude.Double),
GetDevicePositionResponse -> ISO8601
receivedTime :: Data.ISO8601,
GetDevicePositionResponse -> ISO8601
sampleTime :: Data.ISO8601
}
deriving (GetDevicePositionResponse -> GetDevicePositionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDevicePositionResponse -> GetDevicePositionResponse -> Bool
$c/= :: GetDevicePositionResponse -> GetDevicePositionResponse -> Bool
== :: GetDevicePositionResponse -> GetDevicePositionResponse -> Bool
$c== :: GetDevicePositionResponse -> GetDevicePositionResponse -> Bool
Prelude.Eq, Int -> GetDevicePositionResponse -> ShowS
[GetDevicePositionResponse] -> ShowS
GetDevicePositionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDevicePositionResponse] -> ShowS
$cshowList :: [GetDevicePositionResponse] -> ShowS
show :: GetDevicePositionResponse -> String
$cshow :: GetDevicePositionResponse -> String
showsPrec :: Int -> GetDevicePositionResponse -> ShowS
$cshowsPrec :: Int -> GetDevicePositionResponse -> ShowS
Prelude.Show, forall x.
Rep GetDevicePositionResponse x -> GetDevicePositionResponse
forall x.
GetDevicePositionResponse -> Rep GetDevicePositionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDevicePositionResponse x -> GetDevicePositionResponse
$cfrom :: forall x.
GetDevicePositionResponse -> Rep GetDevicePositionResponse x
Prelude.Generic)
newGetDevicePositionResponse ::
Prelude.Int ->
Prelude.NonEmpty Prelude.Double ->
Prelude.UTCTime ->
Prelude.UTCTime ->
GetDevicePositionResponse
newGetDevicePositionResponse :: Int
-> NonEmpty Double
-> UTCTime
-> UTCTime
-> GetDevicePositionResponse
newGetDevicePositionResponse
Int
pHttpStatus_
NonEmpty Double
pPosition_
UTCTime
pReceivedTime_
UTCTime
pSampleTime_ =
GetDevicePositionResponse'
{ $sel:accuracy:GetDevicePositionResponse' :: Maybe PositionalAccuracy
accuracy =
forall a. Maybe a
Prelude.Nothing,
$sel:deviceId:GetDevicePositionResponse' :: Maybe Text
deviceId = forall a. Maybe a
Prelude.Nothing,
$sel:positionProperties:GetDevicePositionResponse' :: Maybe (Sensitive (HashMap Text Text))
positionProperties = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetDevicePositionResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:position:GetDevicePositionResponse' :: Sensitive (NonEmpty Double)
position =
forall a. Iso' (Sensitive a) a
Data._Sensitive
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
forall t b. AReview t b -> b -> t
Lens.# NonEmpty Double
pPosition_,
$sel:receivedTime:GetDevicePositionResponse' :: ISO8601
receivedTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pReceivedTime_,
$sel:sampleTime:GetDevicePositionResponse' :: ISO8601
sampleTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pSampleTime_
}
getDevicePositionResponse_accuracy :: Lens.Lens' GetDevicePositionResponse (Prelude.Maybe PositionalAccuracy)
getDevicePositionResponse_accuracy :: Lens' GetDevicePositionResponse (Maybe PositionalAccuracy)
getDevicePositionResponse_accuracy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {Maybe PositionalAccuracy
accuracy :: Maybe PositionalAccuracy
$sel:accuracy:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe PositionalAccuracy
accuracy} -> Maybe PositionalAccuracy
accuracy) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} Maybe PositionalAccuracy
a -> GetDevicePositionResponse
s {$sel:accuracy:GetDevicePositionResponse' :: Maybe PositionalAccuracy
accuracy = Maybe PositionalAccuracy
a} :: GetDevicePositionResponse)
getDevicePositionResponse_deviceId :: Lens.Lens' GetDevicePositionResponse (Prelude.Maybe Prelude.Text)
getDevicePositionResponse_deviceId :: Lens' GetDevicePositionResponse (Maybe Text)
getDevicePositionResponse_deviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {Maybe Text
deviceId :: Maybe Text
$sel:deviceId:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe Text
deviceId} -> Maybe Text
deviceId) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} Maybe Text
a -> GetDevicePositionResponse
s {$sel:deviceId:GetDevicePositionResponse' :: Maybe Text
deviceId = Maybe Text
a} :: GetDevicePositionResponse)
getDevicePositionResponse_positionProperties :: Lens.Lens' GetDevicePositionResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getDevicePositionResponse_positionProperties :: Lens' GetDevicePositionResponse (Maybe (HashMap Text Text))
getDevicePositionResponse_positionProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {Maybe (Sensitive (HashMap Text Text))
positionProperties :: Maybe (Sensitive (HashMap Text Text))
$sel:positionProperties:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe (Sensitive (HashMap Text Text))
positionProperties} -> Maybe (Sensitive (HashMap Text Text))
positionProperties) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetDevicePositionResponse
s {$sel:positionProperties:GetDevicePositionResponse' :: Maybe (Sensitive (HashMap Text Text))
positionProperties = Maybe (Sensitive (HashMap Text Text))
a} :: GetDevicePositionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)
getDevicePositionResponse_httpStatus :: Lens.Lens' GetDevicePositionResponse Prelude.Int
getDevicePositionResponse_httpStatus :: Lens' GetDevicePositionResponse Int
getDevicePositionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetDevicePositionResponse' :: GetDevicePositionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} Int
a -> GetDevicePositionResponse
s {$sel:httpStatus:GetDevicePositionResponse' :: Int
httpStatus = Int
a} :: GetDevicePositionResponse)
getDevicePositionResponse_position :: Lens.Lens' GetDevicePositionResponse (Prelude.NonEmpty Prelude.Double)
getDevicePositionResponse_position :: Lens' GetDevicePositionResponse (NonEmpty Double)
getDevicePositionResponse_position = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {Sensitive (NonEmpty Double)
position :: Sensitive (NonEmpty Double)
$sel:position:GetDevicePositionResponse' :: GetDevicePositionResponse -> Sensitive (NonEmpty Double)
position} -> Sensitive (NonEmpty Double)
position) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} Sensitive (NonEmpty Double)
a -> GetDevicePositionResponse
s {$sel:position:GetDevicePositionResponse' :: Sensitive (NonEmpty Double)
position = Sensitive (NonEmpty Double)
a} :: GetDevicePositionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
getDevicePositionResponse_receivedTime :: Lens.Lens' GetDevicePositionResponse Prelude.UTCTime
getDevicePositionResponse_receivedTime :: Lens' GetDevicePositionResponse UTCTime
getDevicePositionResponse_receivedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {ISO8601
receivedTime :: ISO8601
$sel:receivedTime:GetDevicePositionResponse' :: GetDevicePositionResponse -> ISO8601
receivedTime} -> ISO8601
receivedTime) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} ISO8601
a -> GetDevicePositionResponse
s {$sel:receivedTime:GetDevicePositionResponse' :: ISO8601
receivedTime = ISO8601
a} :: GetDevicePositionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
getDevicePositionResponse_sampleTime :: Lens.Lens' GetDevicePositionResponse Prelude.UTCTime
getDevicePositionResponse_sampleTime :: Lens' GetDevicePositionResponse UTCTime
getDevicePositionResponse_sampleTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDevicePositionResponse' {ISO8601
sampleTime :: ISO8601
$sel:sampleTime:GetDevicePositionResponse' :: GetDevicePositionResponse -> ISO8601
sampleTime} -> ISO8601
sampleTime) (\s :: GetDevicePositionResponse
s@GetDevicePositionResponse' {} ISO8601
a -> GetDevicePositionResponse
s {$sel:sampleTime:GetDevicePositionResponse' :: ISO8601
sampleTime = ISO8601
a} :: GetDevicePositionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
instance Prelude.NFData GetDevicePositionResponse where
rnf :: GetDevicePositionResponse -> ()
rnf GetDevicePositionResponse' {Int
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe PositionalAccuracy
Sensitive (NonEmpty Double)
ISO8601
sampleTime :: ISO8601
receivedTime :: ISO8601
position :: Sensitive (NonEmpty Double)
httpStatus :: Int
positionProperties :: Maybe (Sensitive (HashMap Text Text))
deviceId :: Maybe Text
accuracy :: Maybe PositionalAccuracy
$sel:sampleTime:GetDevicePositionResponse' :: GetDevicePositionResponse -> ISO8601
$sel:receivedTime:GetDevicePositionResponse' :: GetDevicePositionResponse -> ISO8601
$sel:position:GetDevicePositionResponse' :: GetDevicePositionResponse -> Sensitive (NonEmpty Double)
$sel:httpStatus:GetDevicePositionResponse' :: GetDevicePositionResponse -> Int
$sel:positionProperties:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe (Sensitive (HashMap Text Text))
$sel:deviceId:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe Text
$sel:accuracy:GetDevicePositionResponse' :: GetDevicePositionResponse -> Maybe PositionalAccuracy
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe PositionalAccuracy
accuracy
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deviceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
positionProperties
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 Sensitive (NonEmpty Double)
position
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
receivedTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
sampleTime