{-# 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.IoTWireless.Types.UpdateFPorts
-- 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.IoTWireless.Types.UpdateFPorts where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTWireless.Types.ApplicationConfig
import Amazonka.IoTWireless.Types.Positioning
import qualified Amazonka.Prelude as Prelude

-- | Object for updating the FPorts information.
--
-- /See:/ 'newUpdateFPorts' smart constructor.
data UpdateFPorts = UpdateFPorts'
  { -- | LoRaWAN application, which can be used for geolocation by activating
    -- positioning.
    UpdateFPorts -> Maybe [ApplicationConfig]
applications :: Prelude.Maybe [ApplicationConfig],
    -- | Positioning FPorts for the ClockSync, Stream, and GNSS functions.
    UpdateFPorts -> Maybe Positioning
positioning :: Prelude.Maybe Positioning
  }
  deriving (UpdateFPorts -> UpdateFPorts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFPorts -> UpdateFPorts -> Bool
$c/= :: UpdateFPorts -> UpdateFPorts -> Bool
== :: UpdateFPorts -> UpdateFPorts -> Bool
$c== :: UpdateFPorts -> UpdateFPorts -> Bool
Prelude.Eq, ReadPrec [UpdateFPorts]
ReadPrec UpdateFPorts
Int -> ReadS UpdateFPorts
ReadS [UpdateFPorts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFPorts]
$creadListPrec :: ReadPrec [UpdateFPorts]
readPrec :: ReadPrec UpdateFPorts
$creadPrec :: ReadPrec UpdateFPorts
readList :: ReadS [UpdateFPorts]
$creadList :: ReadS [UpdateFPorts]
readsPrec :: Int -> ReadS UpdateFPorts
$creadsPrec :: Int -> ReadS UpdateFPorts
Prelude.Read, Int -> UpdateFPorts -> ShowS
[UpdateFPorts] -> ShowS
UpdateFPorts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFPorts] -> ShowS
$cshowList :: [UpdateFPorts] -> ShowS
show :: UpdateFPorts -> String
$cshow :: UpdateFPorts -> String
showsPrec :: Int -> UpdateFPorts -> ShowS
$cshowsPrec :: Int -> UpdateFPorts -> ShowS
Prelude.Show, forall x. Rep UpdateFPorts x -> UpdateFPorts
forall x. UpdateFPorts -> Rep UpdateFPorts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFPorts x -> UpdateFPorts
$cfrom :: forall x. UpdateFPorts -> Rep UpdateFPorts x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFPorts' 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:
--
-- 'applications', 'updateFPorts_applications' - LoRaWAN application, which can be used for geolocation by activating
-- positioning.
--
-- 'positioning', 'updateFPorts_positioning' - Positioning FPorts for the ClockSync, Stream, and GNSS functions.
newUpdateFPorts ::
  UpdateFPorts
newUpdateFPorts :: UpdateFPorts
newUpdateFPorts =
  UpdateFPorts'
    { $sel:applications:UpdateFPorts' :: Maybe [ApplicationConfig]
applications = forall a. Maybe a
Prelude.Nothing,
      $sel:positioning:UpdateFPorts' :: Maybe Positioning
positioning = forall a. Maybe a
Prelude.Nothing
    }

-- | LoRaWAN application, which can be used for geolocation by activating
-- positioning.
updateFPorts_applications :: Lens.Lens' UpdateFPorts (Prelude.Maybe [ApplicationConfig])
updateFPorts_applications :: Lens' UpdateFPorts (Maybe [ApplicationConfig])
updateFPorts_applications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFPorts' {Maybe [ApplicationConfig]
applications :: Maybe [ApplicationConfig]
$sel:applications:UpdateFPorts' :: UpdateFPorts -> Maybe [ApplicationConfig]
applications} -> Maybe [ApplicationConfig]
applications) (\s :: UpdateFPorts
s@UpdateFPorts' {} Maybe [ApplicationConfig]
a -> UpdateFPorts
s {$sel:applications:UpdateFPorts' :: Maybe [ApplicationConfig]
applications = Maybe [ApplicationConfig]
a} :: UpdateFPorts) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Positioning FPorts for the ClockSync, Stream, and GNSS functions.
updateFPorts_positioning :: Lens.Lens' UpdateFPorts (Prelude.Maybe Positioning)
updateFPorts_positioning :: Lens' UpdateFPorts (Maybe Positioning)
updateFPorts_positioning = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFPorts' {Maybe Positioning
positioning :: Maybe Positioning
$sel:positioning:UpdateFPorts' :: UpdateFPorts -> Maybe Positioning
positioning} -> Maybe Positioning
positioning) (\s :: UpdateFPorts
s@UpdateFPorts' {} Maybe Positioning
a -> UpdateFPorts
s {$sel:positioning:UpdateFPorts' :: Maybe Positioning
positioning = Maybe Positioning
a} :: UpdateFPorts)

instance Prelude.Hashable UpdateFPorts where
  hashWithSalt :: Int -> UpdateFPorts -> Int
hashWithSalt Int
_salt UpdateFPorts' {Maybe [ApplicationConfig]
Maybe Positioning
positioning :: Maybe Positioning
applications :: Maybe [ApplicationConfig]
$sel:positioning:UpdateFPorts' :: UpdateFPorts -> Maybe Positioning
$sel:applications:UpdateFPorts' :: UpdateFPorts -> Maybe [ApplicationConfig]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ApplicationConfig]
applications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Positioning
positioning

instance Prelude.NFData UpdateFPorts where
  rnf :: UpdateFPorts -> ()
rnf UpdateFPorts' {Maybe [ApplicationConfig]
Maybe Positioning
positioning :: Maybe Positioning
applications :: Maybe [ApplicationConfig]
$sel:positioning:UpdateFPorts' :: UpdateFPorts -> Maybe Positioning
$sel:applications:UpdateFPorts' :: UpdateFPorts -> Maybe [ApplicationConfig]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ApplicationConfig]
applications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Positioning
positioning

instance Data.ToJSON UpdateFPorts where
  toJSON :: UpdateFPorts -> Value
toJSON UpdateFPorts' {Maybe [ApplicationConfig]
Maybe Positioning
positioning :: Maybe Positioning
applications :: Maybe [ApplicationConfig]
$sel:positioning:UpdateFPorts' :: UpdateFPorts -> Maybe Positioning
$sel:applications:UpdateFPorts' :: UpdateFPorts -> Maybe [ApplicationConfig]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Applications" 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 [ApplicationConfig]
applications,
            (Key
"Positioning" 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 Positioning
positioning
          ]
      )