{-# 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.GroundStation.Types.TLEData
-- 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.GroundStation.Types.TLEData where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GroundStation.Types.TimeRange
import qualified Amazonka.Prelude as Prelude

-- | Two-line element set (TLE) data.
--
-- /See:/ 'newTLEData' smart constructor.
data TLEData = TLEData'
  { -- | First line of two-line element set (TLE) data.
    TLEData -> Text
tleLine1 :: Prelude.Text,
    -- | Second line of two-line element set (TLE) data.
    TLEData -> Text
tleLine2 :: Prelude.Text,
    -- | The valid time range for the TLE. Gaps or overlap are not permitted.
    TLEData -> TimeRange
validTimeRange :: TimeRange
  }
  deriving (TLEData -> TLEData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TLEData -> TLEData -> Bool
$c/= :: TLEData -> TLEData -> Bool
== :: TLEData -> TLEData -> Bool
$c== :: TLEData -> TLEData -> Bool
Prelude.Eq, ReadPrec [TLEData]
ReadPrec TLEData
Int -> ReadS TLEData
ReadS [TLEData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TLEData]
$creadListPrec :: ReadPrec [TLEData]
readPrec :: ReadPrec TLEData
$creadPrec :: ReadPrec TLEData
readList :: ReadS [TLEData]
$creadList :: ReadS [TLEData]
readsPrec :: Int -> ReadS TLEData
$creadsPrec :: Int -> ReadS TLEData
Prelude.Read, Int -> TLEData -> ShowS
[TLEData] -> ShowS
TLEData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TLEData] -> ShowS
$cshowList :: [TLEData] -> ShowS
show :: TLEData -> String
$cshow :: TLEData -> String
showsPrec :: Int -> TLEData -> ShowS
$cshowsPrec :: Int -> TLEData -> ShowS
Prelude.Show, forall x. Rep TLEData x -> TLEData
forall x. TLEData -> Rep TLEData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TLEData x -> TLEData
$cfrom :: forall x. TLEData -> Rep TLEData x
Prelude.Generic)

-- |
-- Create a value of 'TLEData' 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:
--
-- 'tleLine1', 'tLEData_tleLine1' - First line of two-line element set (TLE) data.
--
-- 'tleLine2', 'tLEData_tleLine2' - Second line of two-line element set (TLE) data.
--
-- 'validTimeRange', 'tLEData_validTimeRange' - The valid time range for the TLE. Gaps or overlap are not permitted.
newTLEData ::
  -- | 'tleLine1'
  Prelude.Text ->
  -- | 'tleLine2'
  Prelude.Text ->
  -- | 'validTimeRange'
  TimeRange ->
  TLEData
newTLEData :: Text -> Text -> TimeRange -> TLEData
newTLEData Text
pTleLine1_ Text
pTleLine2_ TimeRange
pValidTimeRange_ =
  TLEData'
    { $sel:tleLine1:TLEData' :: Text
tleLine1 = Text
pTleLine1_,
      $sel:tleLine2:TLEData' :: Text
tleLine2 = Text
pTleLine2_,
      $sel:validTimeRange:TLEData' :: TimeRange
validTimeRange = TimeRange
pValidTimeRange_
    }

-- | First line of two-line element set (TLE) data.
tLEData_tleLine1 :: Lens.Lens' TLEData Prelude.Text
tLEData_tleLine1 :: Lens' TLEData Text
tLEData_tleLine1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TLEData' {Text
tleLine1 :: Text
$sel:tleLine1:TLEData' :: TLEData -> Text
tleLine1} -> Text
tleLine1) (\s :: TLEData
s@TLEData' {} Text
a -> TLEData
s {$sel:tleLine1:TLEData' :: Text
tleLine1 = Text
a} :: TLEData)

-- | Second line of two-line element set (TLE) data.
tLEData_tleLine2 :: Lens.Lens' TLEData Prelude.Text
tLEData_tleLine2 :: Lens' TLEData Text
tLEData_tleLine2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TLEData' {Text
tleLine2 :: Text
$sel:tleLine2:TLEData' :: TLEData -> Text
tleLine2} -> Text
tleLine2) (\s :: TLEData
s@TLEData' {} Text
a -> TLEData
s {$sel:tleLine2:TLEData' :: Text
tleLine2 = Text
a} :: TLEData)

-- | The valid time range for the TLE. Gaps or overlap are not permitted.
tLEData_validTimeRange :: Lens.Lens' TLEData TimeRange
tLEData_validTimeRange :: Lens' TLEData TimeRange
tLEData_validTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TLEData' {TimeRange
validTimeRange :: TimeRange
$sel:validTimeRange:TLEData' :: TLEData -> TimeRange
validTimeRange} -> TimeRange
validTimeRange) (\s :: TLEData
s@TLEData' {} TimeRange
a -> TLEData
s {$sel:validTimeRange:TLEData' :: TimeRange
validTimeRange = TimeRange
a} :: TLEData)

instance Prelude.Hashable TLEData where
  hashWithSalt :: Int -> TLEData -> Int
hashWithSalt Int
_salt TLEData' {Text
TimeRange
validTimeRange :: TimeRange
tleLine2 :: Text
tleLine1 :: Text
$sel:validTimeRange:TLEData' :: TLEData -> TimeRange
$sel:tleLine2:TLEData' :: TLEData -> Text
$sel:tleLine1:TLEData' :: TLEData -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tleLine1
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tleLine2
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TimeRange
validTimeRange

instance Prelude.NFData TLEData where
  rnf :: TLEData -> ()
rnf TLEData' {Text
TimeRange
validTimeRange :: TimeRange
tleLine2 :: Text
tleLine1 :: Text
$sel:validTimeRange:TLEData' :: TLEData -> TimeRange
$sel:tleLine2:TLEData' :: TLEData -> Text
$sel:tleLine1:TLEData' :: TLEData -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
tleLine1
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tleLine2
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimeRange
validTimeRange

instance Data.ToJSON TLEData where
  toJSON :: TLEData -> Value
toJSON TLEData' {Text
TimeRange
validTimeRange :: TimeRange
tleLine2 :: Text
tleLine1 :: Text
$sel:validTimeRange:TLEData' :: TLEData -> TimeRange
$sel:tleLine2:TLEData' :: TLEData -> Text
$sel:tleLine1:TLEData' :: TLEData -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"tleLine1" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tleLine1),
            forall a. a -> Maybe a
Prelude.Just (Key
"tleLine2" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tleLine2),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"validTimeRange" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TimeRange
validTimeRange)
          ]
      )