{-# 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.GameLift.Types.IpPermission
-- 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.GameLift.Types.IpPermission where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GameLift.Types.IpProtocol
import qualified Amazonka.Prelude as Prelude

-- | A range of IP addresses and port settings that allow inbound traffic to
-- connect to server processes on an instance in a fleet. New game sessions
-- are assigned an IP address\/port number combination, which must fall
-- into the fleet\'s allowed ranges. Fleets with custom game builds must
-- have permissions explicitly set. For Realtime Servers fleets, GameLift
-- automatically opens two port ranges, one for TCP messaging and one for
-- UDP.
--
-- /See:/ 'newIpPermission' smart constructor.
data IpPermission = IpPermission'
  { -- | A starting value for a range of allowed port numbers.
    --
    -- For fleets using Windows and Linux builds, only ports 1026-60000 are
    -- valid.
    IpPermission -> Natural
fromPort :: Prelude.Natural,
    -- | An ending value for a range of allowed port numbers. Port numbers are
    -- end-inclusive. This value must be higher than @FromPort@.
    --
    -- For fleets using Windows and Linux builds, only ports 1026-60000 are
    -- valid.
    IpPermission -> Natural
toPort :: Prelude.Natural,
    -- | A range of allowed IP addresses. This value must be expressed in CIDR
    -- notation. Example: \"@000.000.000.000\/[subnet mask]@\" or optionally
    -- the shortened version \"@0.0.0.0\/[subnet mask]@\".
    IpPermission -> Text
ipRange :: Prelude.Text,
    -- | The network communication protocol used by the fleet.
    IpPermission -> IpProtocol
protocol :: IpProtocol
  }
  deriving (IpPermission -> IpPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IpPermission -> IpPermission -> Bool
$c/= :: IpPermission -> IpPermission -> Bool
== :: IpPermission -> IpPermission -> Bool
$c== :: IpPermission -> IpPermission -> Bool
Prelude.Eq, ReadPrec [IpPermission]
ReadPrec IpPermission
Int -> ReadS IpPermission
ReadS [IpPermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IpPermission]
$creadListPrec :: ReadPrec [IpPermission]
readPrec :: ReadPrec IpPermission
$creadPrec :: ReadPrec IpPermission
readList :: ReadS [IpPermission]
$creadList :: ReadS [IpPermission]
readsPrec :: Int -> ReadS IpPermission
$creadsPrec :: Int -> ReadS IpPermission
Prelude.Read, Int -> IpPermission -> ShowS
[IpPermission] -> ShowS
IpPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IpPermission] -> ShowS
$cshowList :: [IpPermission] -> ShowS
show :: IpPermission -> String
$cshow :: IpPermission -> String
showsPrec :: Int -> IpPermission -> ShowS
$cshowsPrec :: Int -> IpPermission -> ShowS
Prelude.Show, forall x. Rep IpPermission x -> IpPermission
forall x. IpPermission -> Rep IpPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IpPermission x -> IpPermission
$cfrom :: forall x. IpPermission -> Rep IpPermission x
Prelude.Generic)

-- |
-- Create a value of 'IpPermission' 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:
--
-- 'fromPort', 'ipPermission_fromPort' - A starting value for a range of allowed port numbers.
--
-- For fleets using Windows and Linux builds, only ports 1026-60000 are
-- valid.
--
-- 'toPort', 'ipPermission_toPort' - An ending value for a range of allowed port numbers. Port numbers are
-- end-inclusive. This value must be higher than @FromPort@.
--
-- For fleets using Windows and Linux builds, only ports 1026-60000 are
-- valid.
--
-- 'ipRange', 'ipPermission_ipRange' - A range of allowed IP addresses. This value must be expressed in CIDR
-- notation. Example: \"@000.000.000.000\/[subnet mask]@\" or optionally
-- the shortened version \"@0.0.0.0\/[subnet mask]@\".
--
-- 'protocol', 'ipPermission_protocol' - The network communication protocol used by the fleet.
newIpPermission ::
  -- | 'fromPort'
  Prelude.Natural ->
  -- | 'toPort'
  Prelude.Natural ->
  -- | 'ipRange'
  Prelude.Text ->
  -- | 'protocol'
  IpProtocol ->
  IpPermission
newIpPermission :: Natural -> Natural -> Text -> IpProtocol -> IpPermission
newIpPermission
  Natural
pFromPort_
  Natural
pToPort_
  Text
pIpRange_
  IpProtocol
pProtocol_ =
    IpPermission'
      { $sel:fromPort:IpPermission' :: Natural
fromPort = Natural
pFromPort_,
        $sel:toPort:IpPermission' :: Natural
toPort = Natural
pToPort_,
        $sel:ipRange:IpPermission' :: Text
ipRange = Text
pIpRange_,
        $sel:protocol:IpPermission' :: IpProtocol
protocol = IpProtocol
pProtocol_
      }

-- | A starting value for a range of allowed port numbers.
--
-- For fleets using Windows and Linux builds, only ports 1026-60000 are
-- valid.
ipPermission_fromPort :: Lens.Lens' IpPermission Prelude.Natural
ipPermission_fromPort :: Lens' IpPermission Natural
ipPermission_fromPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpPermission' {Natural
fromPort :: Natural
$sel:fromPort:IpPermission' :: IpPermission -> Natural
fromPort} -> Natural
fromPort) (\s :: IpPermission
s@IpPermission' {} Natural
a -> IpPermission
s {$sel:fromPort:IpPermission' :: Natural
fromPort = Natural
a} :: IpPermission)

-- | An ending value for a range of allowed port numbers. Port numbers are
-- end-inclusive. This value must be higher than @FromPort@.
--
-- For fleets using Windows and Linux builds, only ports 1026-60000 are
-- valid.
ipPermission_toPort :: Lens.Lens' IpPermission Prelude.Natural
ipPermission_toPort :: Lens' IpPermission Natural
ipPermission_toPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpPermission' {Natural
toPort :: Natural
$sel:toPort:IpPermission' :: IpPermission -> Natural
toPort} -> Natural
toPort) (\s :: IpPermission
s@IpPermission' {} Natural
a -> IpPermission
s {$sel:toPort:IpPermission' :: Natural
toPort = Natural
a} :: IpPermission)

-- | A range of allowed IP addresses. This value must be expressed in CIDR
-- notation. Example: \"@000.000.000.000\/[subnet mask]@\" or optionally
-- the shortened version \"@0.0.0.0\/[subnet mask]@\".
ipPermission_ipRange :: Lens.Lens' IpPermission Prelude.Text
ipPermission_ipRange :: Lens' IpPermission Text
ipPermission_ipRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpPermission' {Text
ipRange :: Text
$sel:ipRange:IpPermission' :: IpPermission -> Text
ipRange} -> Text
ipRange) (\s :: IpPermission
s@IpPermission' {} Text
a -> IpPermission
s {$sel:ipRange:IpPermission' :: Text
ipRange = Text
a} :: IpPermission)

-- | The network communication protocol used by the fleet.
ipPermission_protocol :: Lens.Lens' IpPermission IpProtocol
ipPermission_protocol :: Lens' IpPermission IpProtocol
ipPermission_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\IpPermission' {IpProtocol
protocol :: IpProtocol
$sel:protocol:IpPermission' :: IpPermission -> IpProtocol
protocol} -> IpProtocol
protocol) (\s :: IpPermission
s@IpPermission' {} IpProtocol
a -> IpPermission
s {$sel:protocol:IpPermission' :: IpProtocol
protocol = IpProtocol
a} :: IpPermission)

instance Data.FromJSON IpPermission where
  parseJSON :: Value -> Parser IpPermission
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"IpPermission"
      ( \Object
x ->
          Natural -> Natural -> Text -> IpProtocol -> IpPermission
IpPermission'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"FromPort")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"ToPort")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"IpRange")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Protocol")
      )

instance Prelude.Hashable IpPermission where
  hashWithSalt :: Int -> IpPermission -> Int
hashWithSalt Int
_salt IpPermission' {Natural
Text
IpProtocol
protocol :: IpProtocol
ipRange :: Text
toPort :: Natural
fromPort :: Natural
$sel:protocol:IpPermission' :: IpPermission -> IpProtocol
$sel:ipRange:IpPermission' :: IpPermission -> Text
$sel:toPort:IpPermission' :: IpPermission -> Natural
$sel:fromPort:IpPermission' :: IpPermission -> Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
fromPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
toPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ipRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IpProtocol
protocol

instance Prelude.NFData IpPermission where
  rnf :: IpPermission -> ()
rnf IpPermission' {Natural
Text
IpProtocol
protocol :: IpProtocol
ipRange :: Text
toPort :: Natural
fromPort :: Natural
$sel:protocol:IpPermission' :: IpPermission -> IpProtocol
$sel:ipRange:IpPermission' :: IpPermission -> Text
$sel:toPort:IpPermission' :: IpPermission -> Natural
$sel:fromPort:IpPermission' :: IpPermission -> Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Natural
fromPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
toPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ipRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IpProtocol
protocol

instance Data.ToJSON IpPermission where
  toJSON :: IpPermission -> Value
toJSON IpPermission' {Natural
Text
IpProtocol
protocol :: IpProtocol
ipRange :: Text
toPort :: Natural
fromPort :: Natural
$sel:protocol:IpPermission' :: IpPermission -> IpProtocol
$sel:ipRange:IpPermission' :: IpPermission -> Text
$sel:toPort:IpPermission' :: IpPermission -> Natural
$sel:fromPort:IpPermission' :: IpPermission -> Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"FromPort" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
fromPort),
            forall a. a -> Maybe a
Prelude.Just (Key
"ToPort" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
toPort),
            forall a. a -> Maybe a
Prelude.Just (Key
"IpRange" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ipRange),
            forall a. a -> Maybe a
Prelude.Just (Key
"Protocol" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IpProtocol
protocol)
          ]
      )