{-# 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.LteLocalId
-- 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.LteLocalId where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | LTE local identification (local ID) information.
--
-- /See:/ 'newLteLocalId' smart constructor.
data LteLocalId = LteLocalId'
  { -- | Physical cell ID.
    LteLocalId -> Natural
pci :: Prelude.Natural,
    -- | Evolved universal terrestrial radio access (E-UTRA) absolute radio
    -- frequency channel number (FCN).
    LteLocalId -> Natural
earfcn :: Prelude.Natural
  }
  deriving (LteLocalId -> LteLocalId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LteLocalId -> LteLocalId -> Bool
$c/= :: LteLocalId -> LteLocalId -> Bool
== :: LteLocalId -> LteLocalId -> Bool
$c== :: LteLocalId -> LteLocalId -> Bool
Prelude.Eq, ReadPrec [LteLocalId]
ReadPrec LteLocalId
Int -> ReadS LteLocalId
ReadS [LteLocalId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LteLocalId]
$creadListPrec :: ReadPrec [LteLocalId]
readPrec :: ReadPrec LteLocalId
$creadPrec :: ReadPrec LteLocalId
readList :: ReadS [LteLocalId]
$creadList :: ReadS [LteLocalId]
readsPrec :: Int -> ReadS LteLocalId
$creadsPrec :: Int -> ReadS LteLocalId
Prelude.Read, Int -> LteLocalId -> ShowS
[LteLocalId] -> ShowS
LteLocalId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LteLocalId] -> ShowS
$cshowList :: [LteLocalId] -> ShowS
show :: LteLocalId -> String
$cshow :: LteLocalId -> String
showsPrec :: Int -> LteLocalId -> ShowS
$cshowsPrec :: Int -> LteLocalId -> ShowS
Prelude.Show, forall x. Rep LteLocalId x -> LteLocalId
forall x. LteLocalId -> Rep LteLocalId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LteLocalId x -> LteLocalId
$cfrom :: forall x. LteLocalId -> Rep LteLocalId x
Prelude.Generic)

-- |
-- Create a value of 'LteLocalId' 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:
--
-- 'pci', 'lteLocalId_pci' - Physical cell ID.
--
-- 'earfcn', 'lteLocalId_earfcn' - Evolved universal terrestrial radio access (E-UTRA) absolute radio
-- frequency channel number (FCN).
newLteLocalId ::
  -- | 'pci'
  Prelude.Natural ->
  -- | 'earfcn'
  Prelude.Natural ->
  LteLocalId
newLteLocalId :: Natural -> Natural -> LteLocalId
newLteLocalId Natural
pPci_ Natural
pEarfcn_ =
  LteLocalId' {$sel:pci:LteLocalId' :: Natural
pci = Natural
pPci_, $sel:earfcn:LteLocalId' :: Natural
earfcn = Natural
pEarfcn_}

-- | Physical cell ID.
lteLocalId_pci :: Lens.Lens' LteLocalId Prelude.Natural
lteLocalId_pci :: Lens' LteLocalId Natural
lteLocalId_pci = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LteLocalId' {Natural
pci :: Natural
$sel:pci:LteLocalId' :: LteLocalId -> Natural
pci} -> Natural
pci) (\s :: LteLocalId
s@LteLocalId' {} Natural
a -> LteLocalId
s {$sel:pci:LteLocalId' :: Natural
pci = Natural
a} :: LteLocalId)

-- | Evolved universal terrestrial radio access (E-UTRA) absolute radio
-- frequency channel number (FCN).
lteLocalId_earfcn :: Lens.Lens' LteLocalId Prelude.Natural
lteLocalId_earfcn :: Lens' LteLocalId Natural
lteLocalId_earfcn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LteLocalId' {Natural
earfcn :: Natural
$sel:earfcn:LteLocalId' :: LteLocalId -> Natural
earfcn} -> Natural
earfcn) (\s :: LteLocalId
s@LteLocalId' {} Natural
a -> LteLocalId
s {$sel:earfcn:LteLocalId' :: Natural
earfcn = Natural
a} :: LteLocalId)

instance Prelude.Hashable LteLocalId where
  hashWithSalt :: Int -> LteLocalId -> Int
hashWithSalt Int
_salt LteLocalId' {Natural
earfcn :: Natural
pci :: Natural
$sel:earfcn:LteLocalId' :: LteLocalId -> Natural
$sel:pci:LteLocalId' :: LteLocalId -> Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
pci
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
earfcn

instance Prelude.NFData LteLocalId where
  rnf :: LteLocalId -> ()
rnf LteLocalId' {Natural
earfcn :: Natural
pci :: Natural
$sel:earfcn:LteLocalId' :: LteLocalId -> Natural
$sel:pci:LteLocalId' :: LteLocalId -> Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Natural
pci seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
earfcn

instance Data.ToJSON LteLocalId where
  toJSON :: LteLocalId -> Value
toJSON LteLocalId' {Natural
earfcn :: Natural
pci :: Natural
$sel:earfcn:LteLocalId' :: LteLocalId -> Natural
$sel:pci:LteLocalId' :: LteLocalId -> Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Pci" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
pci),
            forall a. a -> Maybe a
Prelude.Just (Key
"Earfcn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
earfcn)
          ]
      )