{-# 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.Location.BatchDeleteDevicePositionHistory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the position history of one or more devices from a tracker
-- resource.
module Amazonka.Location.BatchDeleteDevicePositionHistory
  ( -- * Creating a Request
    BatchDeleteDevicePositionHistory (..),
    newBatchDeleteDevicePositionHistory,

    -- * Request Lenses
    batchDeleteDevicePositionHistory_deviceIds,
    batchDeleteDevicePositionHistory_trackerName,

    -- * Destructuring the Response
    BatchDeleteDevicePositionHistoryResponse (..),
    newBatchDeleteDevicePositionHistoryResponse,

    -- * Response Lenses
    batchDeleteDevicePositionHistoryResponse_httpStatus,
    batchDeleteDevicePositionHistoryResponse_errors,
  )
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

-- | /See:/ 'newBatchDeleteDevicePositionHistory' smart constructor.
data BatchDeleteDevicePositionHistory = BatchDeleteDevicePositionHistory'
  { -- | Devices whose position history you want to delete.
    --
    -- -   For example, for two devices: @“DeviceIds” : [DeviceId1,DeviceId2]@
    BatchDeleteDevicePositionHistory -> NonEmpty Text
deviceIds :: Prelude.NonEmpty Prelude.Text,
    -- | The name of the tracker resource to delete the device position history
    -- from.
    BatchDeleteDevicePositionHistory -> Text
trackerName :: Prelude.Text
  }
  deriving (BatchDeleteDevicePositionHistory
-> BatchDeleteDevicePositionHistory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDeleteDevicePositionHistory
-> BatchDeleteDevicePositionHistory -> Bool
$c/= :: BatchDeleteDevicePositionHistory
-> BatchDeleteDevicePositionHistory -> Bool
== :: BatchDeleteDevicePositionHistory
-> BatchDeleteDevicePositionHistory -> Bool
$c== :: BatchDeleteDevicePositionHistory
-> BatchDeleteDevicePositionHistory -> Bool
Prelude.Eq, ReadPrec [BatchDeleteDevicePositionHistory]
ReadPrec BatchDeleteDevicePositionHistory
Int -> ReadS BatchDeleteDevicePositionHistory
ReadS [BatchDeleteDevicePositionHistory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDeleteDevicePositionHistory]
$creadListPrec :: ReadPrec [BatchDeleteDevicePositionHistory]
readPrec :: ReadPrec BatchDeleteDevicePositionHistory
$creadPrec :: ReadPrec BatchDeleteDevicePositionHistory
readList :: ReadS [BatchDeleteDevicePositionHistory]
$creadList :: ReadS [BatchDeleteDevicePositionHistory]
readsPrec :: Int -> ReadS BatchDeleteDevicePositionHistory
$creadsPrec :: Int -> ReadS BatchDeleteDevicePositionHistory
Prelude.Read, Int -> BatchDeleteDevicePositionHistory -> ShowS
[BatchDeleteDevicePositionHistory] -> ShowS
BatchDeleteDevicePositionHistory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteDevicePositionHistory] -> ShowS
$cshowList :: [BatchDeleteDevicePositionHistory] -> ShowS
show :: BatchDeleteDevicePositionHistory -> String
$cshow :: BatchDeleteDevicePositionHistory -> String
showsPrec :: Int -> BatchDeleteDevicePositionHistory -> ShowS
$cshowsPrec :: Int -> BatchDeleteDevicePositionHistory -> ShowS
Prelude.Show, forall x.
Rep BatchDeleteDevicePositionHistory x
-> BatchDeleteDevicePositionHistory
forall x.
BatchDeleteDevicePositionHistory
-> Rep BatchDeleteDevicePositionHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDeleteDevicePositionHistory x
-> BatchDeleteDevicePositionHistory
$cfrom :: forall x.
BatchDeleteDevicePositionHistory
-> Rep BatchDeleteDevicePositionHistory x
Prelude.Generic)

-- |
-- Create a value of 'BatchDeleteDevicePositionHistory' 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:
--
-- 'deviceIds', 'batchDeleteDevicePositionHistory_deviceIds' - Devices whose position history you want to delete.
--
-- -   For example, for two devices: @“DeviceIds” : [DeviceId1,DeviceId2]@
--
-- 'trackerName', 'batchDeleteDevicePositionHistory_trackerName' - The name of the tracker resource to delete the device position history
-- from.
newBatchDeleteDevicePositionHistory ::
  -- | 'deviceIds'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'trackerName'
  Prelude.Text ->
  BatchDeleteDevicePositionHistory
newBatchDeleteDevicePositionHistory :: NonEmpty Text -> Text -> BatchDeleteDevicePositionHistory
newBatchDeleteDevicePositionHistory
  NonEmpty Text
pDeviceIds_
  Text
pTrackerName_ =
    BatchDeleteDevicePositionHistory'
      { $sel:deviceIds:BatchDeleteDevicePositionHistory' :: NonEmpty Text
deviceIds =
          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 Text
pDeviceIds_,
        $sel:trackerName:BatchDeleteDevicePositionHistory' :: Text
trackerName = Text
pTrackerName_
      }

-- | Devices whose position history you want to delete.
--
-- -   For example, for two devices: @“DeviceIds” : [DeviceId1,DeviceId2]@
batchDeleteDevicePositionHistory_deviceIds :: Lens.Lens' BatchDeleteDevicePositionHistory (Prelude.NonEmpty Prelude.Text)
batchDeleteDevicePositionHistory_deviceIds :: Lens' BatchDeleteDevicePositionHistory (NonEmpty Text)
batchDeleteDevicePositionHistory_deviceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDeleteDevicePositionHistory' {NonEmpty Text
deviceIds :: NonEmpty Text
$sel:deviceIds:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> NonEmpty Text
deviceIds} -> NonEmpty Text
deviceIds) (\s :: BatchDeleteDevicePositionHistory
s@BatchDeleteDevicePositionHistory' {} NonEmpty Text
a -> BatchDeleteDevicePositionHistory
s {$sel:deviceIds:BatchDeleteDevicePositionHistory' :: NonEmpty Text
deviceIds = NonEmpty Text
a} :: BatchDeleteDevicePositionHistory) 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

-- | The name of the tracker resource to delete the device position history
-- from.
batchDeleteDevicePositionHistory_trackerName :: Lens.Lens' BatchDeleteDevicePositionHistory Prelude.Text
batchDeleteDevicePositionHistory_trackerName :: Lens' BatchDeleteDevicePositionHistory Text
batchDeleteDevicePositionHistory_trackerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDeleteDevicePositionHistory' {Text
trackerName :: Text
$sel:trackerName:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> Text
trackerName} -> Text
trackerName) (\s :: BatchDeleteDevicePositionHistory
s@BatchDeleteDevicePositionHistory' {} Text
a -> BatchDeleteDevicePositionHistory
s {$sel:trackerName:BatchDeleteDevicePositionHistory' :: Text
trackerName = Text
a} :: BatchDeleteDevicePositionHistory)

instance
  Core.AWSRequest
    BatchDeleteDevicePositionHistory
  where
  type
    AWSResponse BatchDeleteDevicePositionHistory =
      BatchDeleteDevicePositionHistoryResponse
  request :: (Service -> Service)
-> BatchDeleteDevicePositionHistory
-> Request BatchDeleteDevicePositionHistory
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 BatchDeleteDevicePositionHistory
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse BatchDeleteDevicePositionHistory)))
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
-> [BatchDeleteDevicePositionHistoryError]
-> BatchDeleteDevicePositionHistoryResponse
BatchDeleteDevicePositionHistoryResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Errors" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance
  Prelude.Hashable
    BatchDeleteDevicePositionHistory
  where
  hashWithSalt :: Int -> BatchDeleteDevicePositionHistory -> Int
hashWithSalt
    Int
_salt
    BatchDeleteDevicePositionHistory' {NonEmpty Text
Text
trackerName :: Text
deviceIds :: NonEmpty Text
$sel:trackerName:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> Text
$sel:deviceIds:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> NonEmpty Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
deviceIds
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
trackerName

instance
  Prelude.NFData
    BatchDeleteDevicePositionHistory
  where
  rnf :: BatchDeleteDevicePositionHistory -> ()
rnf BatchDeleteDevicePositionHistory' {NonEmpty Text
Text
trackerName :: Text
deviceIds :: NonEmpty Text
$sel:trackerName:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> Text
$sel:deviceIds:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> NonEmpty Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
deviceIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
trackerName

instance
  Data.ToHeaders
    BatchDeleteDevicePositionHistory
  where
  toHeaders :: BatchDeleteDevicePositionHistory -> 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.ToJSON BatchDeleteDevicePositionHistory where
  toJSON :: BatchDeleteDevicePositionHistory -> Value
toJSON BatchDeleteDevicePositionHistory' {NonEmpty Text
Text
trackerName :: Text
deviceIds :: NonEmpty Text
$sel:trackerName:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> Text
$sel:deviceIds:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> NonEmpty Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"DeviceIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
deviceIds)]
      )

instance Data.ToPath BatchDeleteDevicePositionHistory where
  toPath :: BatchDeleteDevicePositionHistory -> ByteString
toPath BatchDeleteDevicePositionHistory' {NonEmpty Text
Text
trackerName :: Text
deviceIds :: NonEmpty Text
$sel:trackerName:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> Text
$sel:deviceIds:BatchDeleteDevicePositionHistory' :: BatchDeleteDevicePositionHistory -> NonEmpty Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/tracking/v0/trackers/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
trackerName,
        ByteString
"/delete-positions"
      ]

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

-- | /See:/ 'newBatchDeleteDevicePositionHistoryResponse' smart constructor.
data BatchDeleteDevicePositionHistoryResponse = BatchDeleteDevicePositionHistoryResponse'
  { -- | The response's http status code.
    BatchDeleteDevicePositionHistoryResponse -> Int
httpStatus :: Prelude.Int,
    -- | Contains error details for each device history that failed to delete.
    BatchDeleteDevicePositionHistoryResponse
-> [BatchDeleteDevicePositionHistoryError]
errors :: [BatchDeleteDevicePositionHistoryError]
  }
  deriving (BatchDeleteDevicePositionHistoryResponse
-> BatchDeleteDevicePositionHistoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDeleteDevicePositionHistoryResponse
-> BatchDeleteDevicePositionHistoryResponse -> Bool
$c/= :: BatchDeleteDevicePositionHistoryResponse
-> BatchDeleteDevicePositionHistoryResponse -> Bool
== :: BatchDeleteDevicePositionHistoryResponse
-> BatchDeleteDevicePositionHistoryResponse -> Bool
$c== :: BatchDeleteDevicePositionHistoryResponse
-> BatchDeleteDevicePositionHistoryResponse -> Bool
Prelude.Eq, ReadPrec [BatchDeleteDevicePositionHistoryResponse]
ReadPrec BatchDeleteDevicePositionHistoryResponse
Int -> ReadS BatchDeleteDevicePositionHistoryResponse
ReadS [BatchDeleteDevicePositionHistoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDeleteDevicePositionHistoryResponse]
$creadListPrec :: ReadPrec [BatchDeleteDevicePositionHistoryResponse]
readPrec :: ReadPrec BatchDeleteDevicePositionHistoryResponse
$creadPrec :: ReadPrec BatchDeleteDevicePositionHistoryResponse
readList :: ReadS [BatchDeleteDevicePositionHistoryResponse]
$creadList :: ReadS [BatchDeleteDevicePositionHistoryResponse]
readsPrec :: Int -> ReadS BatchDeleteDevicePositionHistoryResponse
$creadsPrec :: Int -> ReadS BatchDeleteDevicePositionHistoryResponse
Prelude.Read, Int -> BatchDeleteDevicePositionHistoryResponse -> ShowS
[BatchDeleteDevicePositionHistoryResponse] -> ShowS
BatchDeleteDevicePositionHistoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteDevicePositionHistoryResponse] -> ShowS
$cshowList :: [BatchDeleteDevicePositionHistoryResponse] -> ShowS
show :: BatchDeleteDevicePositionHistoryResponse -> String
$cshow :: BatchDeleteDevicePositionHistoryResponse -> String
showsPrec :: Int -> BatchDeleteDevicePositionHistoryResponse -> ShowS
$cshowsPrec :: Int -> BatchDeleteDevicePositionHistoryResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDeleteDevicePositionHistoryResponse x
-> BatchDeleteDevicePositionHistoryResponse
forall x.
BatchDeleteDevicePositionHistoryResponse
-> Rep BatchDeleteDevicePositionHistoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDeleteDevicePositionHistoryResponse x
-> BatchDeleteDevicePositionHistoryResponse
$cfrom :: forall x.
BatchDeleteDevicePositionHistoryResponse
-> Rep BatchDeleteDevicePositionHistoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchDeleteDevicePositionHistoryResponse' 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', 'batchDeleteDevicePositionHistoryResponse_httpStatus' - The response's http status code.
--
-- 'errors', 'batchDeleteDevicePositionHistoryResponse_errors' - Contains error details for each device history that failed to delete.
newBatchDeleteDevicePositionHistoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchDeleteDevicePositionHistoryResponse
newBatchDeleteDevicePositionHistoryResponse :: Int -> BatchDeleteDevicePositionHistoryResponse
newBatchDeleteDevicePositionHistoryResponse
  Int
pHttpStatus_ =
    BatchDeleteDevicePositionHistoryResponse'
      { $sel:httpStatus:BatchDeleteDevicePositionHistoryResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:errors:BatchDeleteDevicePositionHistoryResponse' :: [BatchDeleteDevicePositionHistoryError]
errors = forall a. Monoid a => a
Prelude.mempty
      }

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

-- | Contains error details for each device history that failed to delete.
batchDeleteDevicePositionHistoryResponse_errors :: Lens.Lens' BatchDeleteDevicePositionHistoryResponse [BatchDeleteDevicePositionHistoryError]
batchDeleteDevicePositionHistoryResponse_errors :: Lens'
  BatchDeleteDevicePositionHistoryResponse
  [BatchDeleteDevicePositionHistoryError]
batchDeleteDevicePositionHistoryResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDeleteDevicePositionHistoryResponse' {[BatchDeleteDevicePositionHistoryError]
errors :: [BatchDeleteDevicePositionHistoryError]
$sel:errors:BatchDeleteDevicePositionHistoryResponse' :: BatchDeleteDevicePositionHistoryResponse
-> [BatchDeleteDevicePositionHistoryError]
errors} -> [BatchDeleteDevicePositionHistoryError]
errors) (\s :: BatchDeleteDevicePositionHistoryResponse
s@BatchDeleteDevicePositionHistoryResponse' {} [BatchDeleteDevicePositionHistoryError]
a -> BatchDeleteDevicePositionHistoryResponse
s {$sel:errors:BatchDeleteDevicePositionHistoryResponse' :: [BatchDeleteDevicePositionHistoryError]
errors = [BatchDeleteDevicePositionHistoryError]
a} :: BatchDeleteDevicePositionHistoryResponse) 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

instance
  Prelude.NFData
    BatchDeleteDevicePositionHistoryResponse
  where
  rnf :: BatchDeleteDevicePositionHistoryResponse -> ()
rnf BatchDeleteDevicePositionHistoryResponse' {Int
[BatchDeleteDevicePositionHistoryError]
errors :: [BatchDeleteDevicePositionHistoryError]
httpStatus :: Int
$sel:errors:BatchDeleteDevicePositionHistoryResponse' :: BatchDeleteDevicePositionHistoryResponse
-> [BatchDeleteDevicePositionHistoryError]
$sel:httpStatus:BatchDeleteDevicePositionHistoryResponse' :: BatchDeleteDevicePositionHistoryResponse -> 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 [BatchDeleteDevicePositionHistoryError]
errors