{-# 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.GetGeofence
-- 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 the geofence details from a geofence collection.
module Amazonka.Location.GetGeofence
  ( -- * Creating a Request
    GetGeofence (..),
    newGetGeofence,

    -- * Request Lenses
    getGeofence_collectionName,
    getGeofence_geofenceId,

    -- * Destructuring the Response
    GetGeofenceResponse (..),
    newGetGeofenceResponse,

    -- * Response Lenses
    getGeofenceResponse_httpStatus,
    getGeofenceResponse_createTime,
    getGeofenceResponse_geofenceId,
    getGeofenceResponse_geometry,
    getGeofenceResponse_status,
    getGeofenceResponse_updateTime,
  )
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:/ 'newGetGeofence' smart constructor.
data GetGeofence = GetGeofence'
  { -- | The geofence collection storing the target geofence.
    GetGeofence -> Text
collectionName :: Prelude.Text,
    -- | The geofence you\'re retrieving details for.
    GetGeofence -> Text
geofenceId :: Prelude.Text
  }
  deriving (GetGeofence -> GetGeofence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGeofence -> GetGeofence -> Bool
$c/= :: GetGeofence -> GetGeofence -> Bool
== :: GetGeofence -> GetGeofence -> Bool
$c== :: GetGeofence -> GetGeofence -> Bool
Prelude.Eq, ReadPrec [GetGeofence]
ReadPrec GetGeofence
Int -> ReadS GetGeofence
ReadS [GetGeofence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGeofence]
$creadListPrec :: ReadPrec [GetGeofence]
readPrec :: ReadPrec GetGeofence
$creadPrec :: ReadPrec GetGeofence
readList :: ReadS [GetGeofence]
$creadList :: ReadS [GetGeofence]
readsPrec :: Int -> ReadS GetGeofence
$creadsPrec :: Int -> ReadS GetGeofence
Prelude.Read, Int -> GetGeofence -> ShowS
[GetGeofence] -> ShowS
GetGeofence -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGeofence] -> ShowS
$cshowList :: [GetGeofence] -> ShowS
show :: GetGeofence -> String
$cshow :: GetGeofence -> String
showsPrec :: Int -> GetGeofence -> ShowS
$cshowsPrec :: Int -> GetGeofence -> ShowS
Prelude.Show, forall x. Rep GetGeofence x -> GetGeofence
forall x. GetGeofence -> Rep GetGeofence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGeofence x -> GetGeofence
$cfrom :: forall x. GetGeofence -> Rep GetGeofence x
Prelude.Generic)

-- |
-- Create a value of 'GetGeofence' 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:
--
-- 'collectionName', 'getGeofence_collectionName' - The geofence collection storing the target geofence.
--
-- 'geofenceId', 'getGeofence_geofenceId' - The geofence you\'re retrieving details for.
newGetGeofence ::
  -- | 'collectionName'
  Prelude.Text ->
  -- | 'geofenceId'
  Prelude.Text ->
  GetGeofence
newGetGeofence :: Text -> Text -> GetGeofence
newGetGeofence Text
pCollectionName_ Text
pGeofenceId_ =
  GetGeofence'
    { $sel:collectionName:GetGeofence' :: Text
collectionName = Text
pCollectionName_,
      $sel:geofenceId:GetGeofence' :: Text
geofenceId = Text
pGeofenceId_
    }

-- | The geofence collection storing the target geofence.
getGeofence_collectionName :: Lens.Lens' GetGeofence Prelude.Text
getGeofence_collectionName :: Lens' GetGeofence Text
getGeofence_collectionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofence' {Text
collectionName :: Text
$sel:collectionName:GetGeofence' :: GetGeofence -> Text
collectionName} -> Text
collectionName) (\s :: GetGeofence
s@GetGeofence' {} Text
a -> GetGeofence
s {$sel:collectionName:GetGeofence' :: Text
collectionName = Text
a} :: GetGeofence)

-- | The geofence you\'re retrieving details for.
getGeofence_geofenceId :: Lens.Lens' GetGeofence Prelude.Text
getGeofence_geofenceId :: Lens' GetGeofence Text
getGeofence_geofenceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofence' {Text
geofenceId :: Text
$sel:geofenceId:GetGeofence' :: GetGeofence -> Text
geofenceId} -> Text
geofenceId) (\s :: GetGeofence
s@GetGeofence' {} Text
a -> GetGeofence
s {$sel:geofenceId:GetGeofence' :: Text
geofenceId = Text
a} :: GetGeofence)

instance Core.AWSRequest GetGeofence where
  type AWSResponse GetGeofence = GetGeofenceResponse
  request :: (Service -> Service) -> GetGeofence -> Request GetGeofence
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 GetGeofence
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetGeofence)))
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
-> ISO8601
-> Text
-> GeofenceGeometry
-> Text
-> ISO8601
-> GetGeofenceResponse
GetGeofenceResponse'
            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 a
Data..:> Key
"CreateTime")
            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
"GeofenceId")
            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
"Geometry")
            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
"Status")
            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
"UpdateTime")
      )

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

instance Prelude.NFData GetGeofence where
  rnf :: GetGeofence -> ()
rnf GetGeofence' {Text
geofenceId :: Text
collectionName :: Text
$sel:geofenceId:GetGeofence' :: GetGeofence -> Text
$sel:collectionName:GetGeofence' :: GetGeofence -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
collectionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
geofenceId

instance Data.ToHeaders GetGeofence where
  toHeaders :: GetGeofence -> 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 GetGeofence where
  toPath :: GetGeofence -> ByteString
toPath GetGeofence' {Text
geofenceId :: Text
collectionName :: Text
$sel:geofenceId:GetGeofence' :: GetGeofence -> Text
$sel:collectionName:GetGeofence' :: GetGeofence -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/geofencing/v0/collections/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
collectionName,
        ByteString
"/geofences/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
geofenceId
      ]

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

-- | /See:/ 'newGetGeofenceResponse' smart constructor.
data GetGeofenceResponse = GetGeofenceResponse'
  { -- | The response's http status code.
    GetGeofenceResponse -> Int
httpStatus :: Prelude.Int,
    -- | The timestamp for when the geofence collection was created in
    -- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
    -- format: @YYYY-MM-DDThh:mm:ss.sssZ@
    GetGeofenceResponse -> ISO8601
createTime :: Data.ISO8601,
    -- | The geofence identifier.
    GetGeofenceResponse -> Text
geofenceId :: Prelude.Text,
    -- | Contains the geofence geometry details describing a polygon or a circle.
    GetGeofenceResponse -> GeofenceGeometry
geometry :: GeofenceGeometry,
    -- | Identifies the state of the geofence. A geofence will hold one of the
    -- following states:
    --
    -- -   @ACTIVE@ — The geofence has been indexed by the system.
    --
    -- -   @PENDING@ — The geofence is being processed by the system.
    --
    -- -   @FAILED@ — The geofence failed to be indexed by the system.
    --
    -- -   @DELETED@ — The geofence has been deleted from the system index.
    --
    -- -   @DELETING@ — The geofence is being deleted from the system index.
    GetGeofenceResponse -> Text
status :: Prelude.Text,
    -- | The timestamp for when the geofence collection was last updated in
    -- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
    -- format: @YYYY-MM-DDThh:mm:ss.sssZ@
    GetGeofenceResponse -> ISO8601
updateTime :: Data.ISO8601
  }
  deriving (GetGeofenceResponse -> GetGeofenceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGeofenceResponse -> GetGeofenceResponse -> Bool
$c/= :: GetGeofenceResponse -> GetGeofenceResponse -> Bool
== :: GetGeofenceResponse -> GetGeofenceResponse -> Bool
$c== :: GetGeofenceResponse -> GetGeofenceResponse -> Bool
Prelude.Eq, Int -> GetGeofenceResponse -> ShowS
[GetGeofenceResponse] -> ShowS
GetGeofenceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGeofenceResponse] -> ShowS
$cshowList :: [GetGeofenceResponse] -> ShowS
show :: GetGeofenceResponse -> String
$cshow :: GetGeofenceResponse -> String
showsPrec :: Int -> GetGeofenceResponse -> ShowS
$cshowsPrec :: Int -> GetGeofenceResponse -> ShowS
Prelude.Show, forall x. Rep GetGeofenceResponse x -> GetGeofenceResponse
forall x. GetGeofenceResponse -> Rep GetGeofenceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGeofenceResponse x -> GetGeofenceResponse
$cfrom :: forall x. GetGeofenceResponse -> Rep GetGeofenceResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetGeofenceResponse' 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', 'getGeofenceResponse_httpStatus' - The response's http status code.
--
-- 'createTime', 'getGeofenceResponse_createTime' - The timestamp for when the geofence collection was created in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@
--
-- 'geofenceId', 'getGeofenceResponse_geofenceId' - The geofence identifier.
--
-- 'geometry', 'getGeofenceResponse_geometry' - Contains the geofence geometry details describing a polygon or a circle.
--
-- 'status', 'getGeofenceResponse_status' - Identifies the state of the geofence. A geofence will hold one of the
-- following states:
--
-- -   @ACTIVE@ — The geofence has been indexed by the system.
--
-- -   @PENDING@ — The geofence is being processed by the system.
--
-- -   @FAILED@ — The geofence failed to be indexed by the system.
--
-- -   @DELETED@ — The geofence has been deleted from the system index.
--
-- -   @DELETING@ — The geofence is being deleted from the system index.
--
-- 'updateTime', 'getGeofenceResponse_updateTime' - The timestamp for when the geofence collection was last updated in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@
newGetGeofenceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'createTime'
  Prelude.UTCTime ->
  -- | 'geofenceId'
  Prelude.Text ->
  -- | 'geometry'
  GeofenceGeometry ->
  -- | 'status'
  Prelude.Text ->
  -- | 'updateTime'
  Prelude.UTCTime ->
  GetGeofenceResponse
newGetGeofenceResponse :: Int
-> UTCTime
-> Text
-> GeofenceGeometry
-> Text
-> UTCTime
-> GetGeofenceResponse
newGetGeofenceResponse
  Int
pHttpStatus_
  UTCTime
pCreateTime_
  Text
pGeofenceId_
  GeofenceGeometry
pGeometry_
  Text
pStatus_
  UTCTime
pUpdateTime_ =
    GetGeofenceResponse'
      { $sel:httpStatus:GetGeofenceResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:createTime:GetGeofenceResponse' :: ISO8601
createTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreateTime_,
        $sel:geofenceId:GetGeofenceResponse' :: Text
geofenceId = Text
pGeofenceId_,
        $sel:geometry:GetGeofenceResponse' :: GeofenceGeometry
geometry = GeofenceGeometry
pGeometry_,
        $sel:status:GetGeofenceResponse' :: Text
status = Text
pStatus_,
        $sel:updateTime:GetGeofenceResponse' :: ISO8601
updateTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateTime_
      }

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

-- | The timestamp for when the geofence collection was created in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@
getGeofenceResponse_createTime :: Lens.Lens' GetGeofenceResponse Prelude.UTCTime
getGeofenceResponse_createTime :: Lens' GetGeofenceResponse UTCTime
getGeofenceResponse_createTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofenceResponse' {ISO8601
createTime :: ISO8601
$sel:createTime:GetGeofenceResponse' :: GetGeofenceResponse -> ISO8601
createTime} -> ISO8601
createTime) (\s :: GetGeofenceResponse
s@GetGeofenceResponse' {} ISO8601
a -> GetGeofenceResponse
s {$sel:createTime:GetGeofenceResponse' :: ISO8601
createTime = ISO8601
a} :: GetGeofenceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The geofence identifier.
getGeofenceResponse_geofenceId :: Lens.Lens' GetGeofenceResponse Prelude.Text
getGeofenceResponse_geofenceId :: Lens' GetGeofenceResponse Text
getGeofenceResponse_geofenceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofenceResponse' {Text
geofenceId :: Text
$sel:geofenceId:GetGeofenceResponse' :: GetGeofenceResponse -> Text
geofenceId} -> Text
geofenceId) (\s :: GetGeofenceResponse
s@GetGeofenceResponse' {} Text
a -> GetGeofenceResponse
s {$sel:geofenceId:GetGeofenceResponse' :: Text
geofenceId = Text
a} :: GetGeofenceResponse)

-- | Contains the geofence geometry details describing a polygon or a circle.
getGeofenceResponse_geometry :: Lens.Lens' GetGeofenceResponse GeofenceGeometry
getGeofenceResponse_geometry :: Lens' GetGeofenceResponse GeofenceGeometry
getGeofenceResponse_geometry = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofenceResponse' {GeofenceGeometry
geometry :: GeofenceGeometry
$sel:geometry:GetGeofenceResponse' :: GetGeofenceResponse -> GeofenceGeometry
geometry} -> GeofenceGeometry
geometry) (\s :: GetGeofenceResponse
s@GetGeofenceResponse' {} GeofenceGeometry
a -> GetGeofenceResponse
s {$sel:geometry:GetGeofenceResponse' :: GeofenceGeometry
geometry = GeofenceGeometry
a} :: GetGeofenceResponse)

-- | Identifies the state of the geofence. A geofence will hold one of the
-- following states:
--
-- -   @ACTIVE@ — The geofence has been indexed by the system.
--
-- -   @PENDING@ — The geofence is being processed by the system.
--
-- -   @FAILED@ — The geofence failed to be indexed by the system.
--
-- -   @DELETED@ — The geofence has been deleted from the system index.
--
-- -   @DELETING@ — The geofence is being deleted from the system index.
getGeofenceResponse_status :: Lens.Lens' GetGeofenceResponse Prelude.Text
getGeofenceResponse_status :: Lens' GetGeofenceResponse Text
getGeofenceResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofenceResponse' {Text
status :: Text
$sel:status:GetGeofenceResponse' :: GetGeofenceResponse -> Text
status} -> Text
status) (\s :: GetGeofenceResponse
s@GetGeofenceResponse' {} Text
a -> GetGeofenceResponse
s {$sel:status:GetGeofenceResponse' :: Text
status = Text
a} :: GetGeofenceResponse)

-- | The timestamp for when the geofence collection was last updated in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@
getGeofenceResponse_updateTime :: Lens.Lens' GetGeofenceResponse Prelude.UTCTime
getGeofenceResponse_updateTime :: Lens' GetGeofenceResponse UTCTime
getGeofenceResponse_updateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGeofenceResponse' {ISO8601
updateTime :: ISO8601
$sel:updateTime:GetGeofenceResponse' :: GetGeofenceResponse -> ISO8601
updateTime} -> ISO8601
updateTime) (\s :: GetGeofenceResponse
s@GetGeofenceResponse' {} ISO8601
a -> GetGeofenceResponse
s {$sel:updateTime:GetGeofenceResponse' :: ISO8601
updateTime = ISO8601
a} :: GetGeofenceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData GetGeofenceResponse where
  rnf :: GetGeofenceResponse -> ()
rnf GetGeofenceResponse' {Int
Text
ISO8601
GeofenceGeometry
updateTime :: ISO8601
status :: Text
geometry :: GeofenceGeometry
geofenceId :: Text
createTime :: ISO8601
httpStatus :: Int
$sel:updateTime:GetGeofenceResponse' :: GetGeofenceResponse -> ISO8601
$sel:status:GetGeofenceResponse' :: GetGeofenceResponse -> Text
$sel:geometry:GetGeofenceResponse' :: GetGeofenceResponse -> GeofenceGeometry
$sel:geofenceId:GetGeofenceResponse' :: GetGeofenceResponse -> Text
$sel:createTime:GetGeofenceResponse' :: GetGeofenceResponse -> ISO8601
$sel:httpStatus:GetGeofenceResponse' :: GetGeofenceResponse -> 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 ISO8601
createTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
geofenceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf GeofenceGeometry
geometry
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
updateTime