{-# 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.ChimeSdkVoice.CreateSipRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- -- | Undocumented operation.
module Amazonka.ChimeSdkVoice.CreateSipRule
  ( -- * Creating a Request
    CreateSipRule (..),
    newCreateSipRule,

    -- * Request Lenses
    createSipRule_disabled,
    createSipRule_targetApplications,
    createSipRule_name,
    createSipRule_triggerType,
    createSipRule_triggerValue,

    -- * Destructuring the Response
    CreateSipRuleResponse (..),
    newCreateSipRuleResponse,

    -- * Response Lenses
    createSipRuleResponse_sipRule,
    createSipRuleResponse_httpStatus,
  )
where

import Amazonka.ChimeSdkVoice.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateSipRule' smart constructor.
data CreateSipRule = CreateSipRule'
  { CreateSipRule -> Maybe Bool
disabled :: Prelude.Maybe Prelude.Bool,
    CreateSipRule -> Maybe (NonEmpty SipRuleTargetApplication)
targetApplications :: Prelude.Maybe (Prelude.NonEmpty SipRuleTargetApplication),
    CreateSipRule -> Text
name :: Prelude.Text,
    CreateSipRule -> SipRuleTriggerType
triggerType :: SipRuleTriggerType,
    CreateSipRule -> Text
triggerValue :: Prelude.Text
  }
  deriving (CreateSipRule -> CreateSipRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSipRule -> CreateSipRule -> Bool
$c/= :: CreateSipRule -> CreateSipRule -> Bool
== :: CreateSipRule -> CreateSipRule -> Bool
$c== :: CreateSipRule -> CreateSipRule -> Bool
Prelude.Eq, ReadPrec [CreateSipRule]
ReadPrec CreateSipRule
Int -> ReadS CreateSipRule
ReadS [CreateSipRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSipRule]
$creadListPrec :: ReadPrec [CreateSipRule]
readPrec :: ReadPrec CreateSipRule
$creadPrec :: ReadPrec CreateSipRule
readList :: ReadS [CreateSipRule]
$creadList :: ReadS [CreateSipRule]
readsPrec :: Int -> ReadS CreateSipRule
$creadsPrec :: Int -> ReadS CreateSipRule
Prelude.Read, Int -> CreateSipRule -> ShowS
[CreateSipRule] -> ShowS
CreateSipRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSipRule] -> ShowS
$cshowList :: [CreateSipRule] -> ShowS
show :: CreateSipRule -> String
$cshow :: CreateSipRule -> String
showsPrec :: Int -> CreateSipRule -> ShowS
$cshowsPrec :: Int -> CreateSipRule -> ShowS
Prelude.Show, forall x. Rep CreateSipRule x -> CreateSipRule
forall x. CreateSipRule -> Rep CreateSipRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSipRule x -> CreateSipRule
$cfrom :: forall x. CreateSipRule -> Rep CreateSipRule x
Prelude.Generic)

-- |
-- Create a value of 'CreateSipRule' 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:
--
-- 'disabled', 'createSipRule_disabled' - Undocumented member.
--
-- 'targetApplications', 'createSipRule_targetApplications' - Undocumented member.
--
-- 'name', 'createSipRule_name' - Undocumented member.
--
-- 'triggerType', 'createSipRule_triggerType' - Undocumented member.
--
-- 'triggerValue', 'createSipRule_triggerValue' - Undocumented member.
newCreateSipRule ::
  -- | 'name'
  Prelude.Text ->
  -- | 'triggerType'
  SipRuleTriggerType ->
  -- | 'triggerValue'
  Prelude.Text ->
  CreateSipRule
newCreateSipRule :: Text -> SipRuleTriggerType -> Text -> CreateSipRule
newCreateSipRule Text
pName_ SipRuleTriggerType
pTriggerType_ Text
pTriggerValue_ =
  CreateSipRule'
    { $sel:disabled:CreateSipRule' :: Maybe Bool
disabled = forall a. Maybe a
Prelude.Nothing,
      $sel:targetApplications:CreateSipRule' :: Maybe (NonEmpty SipRuleTargetApplication)
targetApplications = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateSipRule' :: Text
name = Text
pName_,
      $sel:triggerType:CreateSipRule' :: SipRuleTriggerType
triggerType = SipRuleTriggerType
pTriggerType_,
      $sel:triggerValue:CreateSipRule' :: Text
triggerValue = Text
pTriggerValue_
    }

-- | Undocumented member.
createSipRule_disabled :: Lens.Lens' CreateSipRule (Prelude.Maybe Prelude.Bool)
createSipRule_disabled :: Lens' CreateSipRule (Maybe Bool)
createSipRule_disabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRule' {Maybe Bool
disabled :: Maybe Bool
$sel:disabled:CreateSipRule' :: CreateSipRule -> Maybe Bool
disabled} -> Maybe Bool
disabled) (\s :: CreateSipRule
s@CreateSipRule' {} Maybe Bool
a -> CreateSipRule
s {$sel:disabled:CreateSipRule' :: Maybe Bool
disabled = Maybe Bool
a} :: CreateSipRule)

-- | Undocumented member.
createSipRule_targetApplications :: Lens.Lens' CreateSipRule (Prelude.Maybe (Prelude.NonEmpty SipRuleTargetApplication))
createSipRule_targetApplications :: Lens' CreateSipRule (Maybe (NonEmpty SipRuleTargetApplication))
createSipRule_targetApplications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRule' {Maybe (NonEmpty SipRuleTargetApplication)
targetApplications :: Maybe (NonEmpty SipRuleTargetApplication)
$sel:targetApplications:CreateSipRule' :: CreateSipRule -> Maybe (NonEmpty SipRuleTargetApplication)
targetApplications} -> Maybe (NonEmpty SipRuleTargetApplication)
targetApplications) (\s :: CreateSipRule
s@CreateSipRule' {} Maybe (NonEmpty SipRuleTargetApplication)
a -> CreateSipRule
s {$sel:targetApplications:CreateSipRule' :: Maybe (NonEmpty SipRuleTargetApplication)
targetApplications = Maybe (NonEmpty SipRuleTargetApplication)
a} :: CreateSipRule) 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

-- | Undocumented member.
createSipRule_name :: Lens.Lens' CreateSipRule Prelude.Text
createSipRule_name :: Lens' CreateSipRule Text
createSipRule_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRule' {Text
name :: Text
$sel:name:CreateSipRule' :: CreateSipRule -> Text
name} -> Text
name) (\s :: CreateSipRule
s@CreateSipRule' {} Text
a -> CreateSipRule
s {$sel:name:CreateSipRule' :: Text
name = Text
a} :: CreateSipRule)

-- | Undocumented member.
createSipRule_triggerType :: Lens.Lens' CreateSipRule SipRuleTriggerType
createSipRule_triggerType :: Lens' CreateSipRule SipRuleTriggerType
createSipRule_triggerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRule' {SipRuleTriggerType
triggerType :: SipRuleTriggerType
$sel:triggerType:CreateSipRule' :: CreateSipRule -> SipRuleTriggerType
triggerType} -> SipRuleTriggerType
triggerType) (\s :: CreateSipRule
s@CreateSipRule' {} SipRuleTriggerType
a -> CreateSipRule
s {$sel:triggerType:CreateSipRule' :: SipRuleTriggerType
triggerType = SipRuleTriggerType
a} :: CreateSipRule)

-- | Undocumented member.
createSipRule_triggerValue :: Lens.Lens' CreateSipRule Prelude.Text
createSipRule_triggerValue :: Lens' CreateSipRule Text
createSipRule_triggerValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRule' {Text
triggerValue :: Text
$sel:triggerValue:CreateSipRule' :: CreateSipRule -> Text
triggerValue} -> Text
triggerValue) (\s :: CreateSipRule
s@CreateSipRule' {} Text
a -> CreateSipRule
s {$sel:triggerValue:CreateSipRule' :: Text
triggerValue = Text
a} :: CreateSipRule)

instance Core.AWSRequest CreateSipRule where
  type
    AWSResponse CreateSipRule =
      CreateSipRuleResponse
  request :: (Service -> Service) -> CreateSipRule -> Request CreateSipRule
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateSipRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateSipRule)))
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 ->
          Maybe SipRule -> Int -> CreateSipRuleResponse
CreateSipRuleResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SipRule")
            forall (f :: * -> *) a b. Applicative f => 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))
      )

instance Prelude.Hashable CreateSipRule where
  hashWithSalt :: Int -> CreateSipRule -> Int
hashWithSalt Int
_salt CreateSipRule' {Maybe Bool
Maybe (NonEmpty SipRuleTargetApplication)
Text
SipRuleTriggerType
triggerValue :: Text
triggerType :: SipRuleTriggerType
name :: Text
targetApplications :: Maybe (NonEmpty SipRuleTargetApplication)
disabled :: Maybe Bool
$sel:triggerValue:CreateSipRule' :: CreateSipRule -> Text
$sel:triggerType:CreateSipRule' :: CreateSipRule -> SipRuleTriggerType
$sel:name:CreateSipRule' :: CreateSipRule -> Text
$sel:targetApplications:CreateSipRule' :: CreateSipRule -> Maybe (NonEmpty SipRuleTargetApplication)
$sel:disabled:CreateSipRule' :: CreateSipRule -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
disabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty SipRuleTargetApplication)
targetApplications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SipRuleTriggerType
triggerType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
triggerValue

instance Prelude.NFData CreateSipRule where
  rnf :: CreateSipRule -> ()
rnf CreateSipRule' {Maybe Bool
Maybe (NonEmpty SipRuleTargetApplication)
Text
SipRuleTriggerType
triggerValue :: Text
triggerType :: SipRuleTriggerType
name :: Text
targetApplications :: Maybe (NonEmpty SipRuleTargetApplication)
disabled :: Maybe Bool
$sel:triggerValue:CreateSipRule' :: CreateSipRule -> Text
$sel:triggerType:CreateSipRule' :: CreateSipRule -> SipRuleTriggerType
$sel:name:CreateSipRule' :: CreateSipRule -> Text
$sel:targetApplications:CreateSipRule' :: CreateSipRule -> Maybe (NonEmpty SipRuleTargetApplication)
$sel:disabled:CreateSipRule' :: CreateSipRule -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
disabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty SipRuleTargetApplication)
targetApplications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SipRuleTriggerType
triggerType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
triggerValue

instance Data.ToHeaders CreateSipRule where
  toHeaders :: CreateSipRule -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateSipRule where
  toJSON :: CreateSipRule -> Value
toJSON CreateSipRule' {Maybe Bool
Maybe (NonEmpty SipRuleTargetApplication)
Text
SipRuleTriggerType
triggerValue :: Text
triggerType :: SipRuleTriggerType
name :: Text
targetApplications :: Maybe (NonEmpty SipRuleTargetApplication)
disabled :: Maybe Bool
$sel:triggerValue:CreateSipRule' :: CreateSipRule -> Text
$sel:triggerType:CreateSipRule' :: CreateSipRule -> SipRuleTriggerType
$sel:name:CreateSipRule' :: CreateSipRule -> Text
$sel:targetApplications:CreateSipRule' :: CreateSipRule -> Maybe (NonEmpty SipRuleTargetApplication)
$sel:disabled:CreateSipRule' :: CreateSipRule -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Disabled" 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 Bool
disabled,
            (Key
"TargetApplications" 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 (NonEmpty SipRuleTargetApplication)
targetApplications,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"TriggerType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SipRuleTriggerType
triggerType),
            forall a. a -> Maybe a
Prelude.Just (Key
"TriggerValue" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
triggerValue)
          ]
      )

instance Data.ToPath CreateSipRule where
  toPath :: CreateSipRule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/sip-rules"

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

-- | /See:/ 'newCreateSipRuleResponse' smart constructor.
data CreateSipRuleResponse = CreateSipRuleResponse'
  { CreateSipRuleResponse -> Maybe SipRule
sipRule :: Prelude.Maybe SipRule,
    -- | The response's http status code.
    CreateSipRuleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateSipRuleResponse -> CreateSipRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSipRuleResponse -> CreateSipRuleResponse -> Bool
$c/= :: CreateSipRuleResponse -> CreateSipRuleResponse -> Bool
== :: CreateSipRuleResponse -> CreateSipRuleResponse -> Bool
$c== :: CreateSipRuleResponse -> CreateSipRuleResponse -> Bool
Prelude.Eq, ReadPrec [CreateSipRuleResponse]
ReadPrec CreateSipRuleResponse
Int -> ReadS CreateSipRuleResponse
ReadS [CreateSipRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSipRuleResponse]
$creadListPrec :: ReadPrec [CreateSipRuleResponse]
readPrec :: ReadPrec CreateSipRuleResponse
$creadPrec :: ReadPrec CreateSipRuleResponse
readList :: ReadS [CreateSipRuleResponse]
$creadList :: ReadS [CreateSipRuleResponse]
readsPrec :: Int -> ReadS CreateSipRuleResponse
$creadsPrec :: Int -> ReadS CreateSipRuleResponse
Prelude.Read, Int -> CreateSipRuleResponse -> ShowS
[CreateSipRuleResponse] -> ShowS
CreateSipRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSipRuleResponse] -> ShowS
$cshowList :: [CreateSipRuleResponse] -> ShowS
show :: CreateSipRuleResponse -> String
$cshow :: CreateSipRuleResponse -> String
showsPrec :: Int -> CreateSipRuleResponse -> ShowS
$cshowsPrec :: Int -> CreateSipRuleResponse -> ShowS
Prelude.Show, forall x. Rep CreateSipRuleResponse x -> CreateSipRuleResponse
forall x. CreateSipRuleResponse -> Rep CreateSipRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSipRuleResponse x -> CreateSipRuleResponse
$cfrom :: forall x. CreateSipRuleResponse -> Rep CreateSipRuleResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSipRuleResponse' 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:
--
-- 'sipRule', 'createSipRuleResponse_sipRule' - Undocumented member.
--
-- 'httpStatus', 'createSipRuleResponse_httpStatus' - The response's http status code.
newCreateSipRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSipRuleResponse
newCreateSipRuleResponse :: Int -> CreateSipRuleResponse
newCreateSipRuleResponse Int
pHttpStatus_ =
  CreateSipRuleResponse'
    { $sel:sipRule:CreateSipRuleResponse' :: Maybe SipRule
sipRule = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSipRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createSipRuleResponse_sipRule :: Lens.Lens' CreateSipRuleResponse (Prelude.Maybe SipRule)
createSipRuleResponse_sipRule :: Lens' CreateSipRuleResponse (Maybe SipRule)
createSipRuleResponse_sipRule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSipRuleResponse' {Maybe SipRule
sipRule :: Maybe SipRule
$sel:sipRule:CreateSipRuleResponse' :: CreateSipRuleResponse -> Maybe SipRule
sipRule} -> Maybe SipRule
sipRule) (\s :: CreateSipRuleResponse
s@CreateSipRuleResponse' {} Maybe SipRule
a -> CreateSipRuleResponse
s {$sel:sipRule:CreateSipRuleResponse' :: Maybe SipRule
sipRule = Maybe SipRule
a} :: CreateSipRuleResponse)

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

instance Prelude.NFData CreateSipRuleResponse where
  rnf :: CreateSipRuleResponse -> ()
rnf CreateSipRuleResponse' {Int
Maybe SipRule
httpStatus :: Int
sipRule :: Maybe SipRule
$sel:httpStatus:CreateSipRuleResponse' :: CreateSipRuleResponse -> Int
$sel:sipRule:CreateSipRuleResponse' :: CreateSipRuleResponse -> Maybe SipRule
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SipRule
sipRule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus