{-# 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.Transcribe.Types.InterruptionFilter
-- 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.Transcribe.Types.InterruptionFilter 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
import Amazonka.Transcribe.Types.AbsoluteTimeRange
import Amazonka.Transcribe.Types.ParticipantRole
import Amazonka.Transcribe.Types.RelativeTimeRange

-- | Flag the presence or absence of interruptions in your Call Analytics
-- transcription output.
--
-- Rules using @InterruptionFilter@ are designed to match:
--
-- -   Instances where an agent interrupts a customer
--
-- -   Instances where a customer interrupts an agent
--
-- -   Either participant interrupting the other
--
-- -   A lack of interruptions
--
-- See
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tca-categories-batch.html#tca-rules-batch Rule criteria for batch categories>
-- for usage examples.
--
-- /See:/ 'newInterruptionFilter' smart constructor.
data InterruptionFilter = InterruptionFilter'
  { -- | Makes it possible to specify a time range (in milliseconds) in your
    -- audio, during which you want to search for an interruption. See for more
    -- detail.
    InterruptionFilter -> Maybe AbsoluteTimeRange
absoluteTimeRange :: Prelude.Maybe AbsoluteTimeRange,
    -- | Set to @TRUE@ to flag speech that does not contain interruptions. Set to
    -- @FALSE@ to flag speech that contains interruptions.
    InterruptionFilter -> Maybe Bool
negate :: Prelude.Maybe Prelude.Bool,
    -- | Specify the interrupter that you want to flag. Omitting this parameter
    -- is equivalent to specifying both participants.
    InterruptionFilter -> Maybe ParticipantRole
participantRole :: Prelude.Maybe ParticipantRole,
    -- | Makes it possible to specify a time range (in percentage) in your media
    -- file, during which you want to search for an interruption. See for more
    -- detail.
    InterruptionFilter -> Maybe RelativeTimeRange
relativeTimeRange :: Prelude.Maybe RelativeTimeRange,
    -- | Specify the duration of the interruptions in milliseconds. For example,
    -- you can flag speech that contains more than 10,000 milliseconds of
    -- interruptions.
    InterruptionFilter -> Maybe Natural
threshold :: Prelude.Maybe Prelude.Natural
  }
  deriving (InterruptionFilter -> InterruptionFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterruptionFilter -> InterruptionFilter -> Bool
$c/= :: InterruptionFilter -> InterruptionFilter -> Bool
== :: InterruptionFilter -> InterruptionFilter -> Bool
$c== :: InterruptionFilter -> InterruptionFilter -> Bool
Prelude.Eq, ReadPrec [InterruptionFilter]
ReadPrec InterruptionFilter
Int -> ReadS InterruptionFilter
ReadS [InterruptionFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterruptionFilter]
$creadListPrec :: ReadPrec [InterruptionFilter]
readPrec :: ReadPrec InterruptionFilter
$creadPrec :: ReadPrec InterruptionFilter
readList :: ReadS [InterruptionFilter]
$creadList :: ReadS [InterruptionFilter]
readsPrec :: Int -> ReadS InterruptionFilter
$creadsPrec :: Int -> ReadS InterruptionFilter
Prelude.Read, Int -> InterruptionFilter -> ShowS
[InterruptionFilter] -> ShowS
InterruptionFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InterruptionFilter] -> ShowS
$cshowList :: [InterruptionFilter] -> ShowS
show :: InterruptionFilter -> String
$cshow :: InterruptionFilter -> String
showsPrec :: Int -> InterruptionFilter -> ShowS
$cshowsPrec :: Int -> InterruptionFilter -> ShowS
Prelude.Show, forall x. Rep InterruptionFilter x -> InterruptionFilter
forall x. InterruptionFilter -> Rep InterruptionFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InterruptionFilter x -> InterruptionFilter
$cfrom :: forall x. InterruptionFilter -> Rep InterruptionFilter x
Prelude.Generic)

-- |
-- Create a value of 'InterruptionFilter' 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:
--
-- 'absoluteTimeRange', 'interruptionFilter_absoluteTimeRange' - Makes it possible to specify a time range (in milliseconds) in your
-- audio, during which you want to search for an interruption. See for more
-- detail.
--
-- 'negate', 'interruptionFilter_negate' - Set to @TRUE@ to flag speech that does not contain interruptions. Set to
-- @FALSE@ to flag speech that contains interruptions.
--
-- 'participantRole', 'interruptionFilter_participantRole' - Specify the interrupter that you want to flag. Omitting this parameter
-- is equivalent to specifying both participants.
--
-- 'relativeTimeRange', 'interruptionFilter_relativeTimeRange' - Makes it possible to specify a time range (in percentage) in your media
-- file, during which you want to search for an interruption. See for more
-- detail.
--
-- 'threshold', 'interruptionFilter_threshold' - Specify the duration of the interruptions in milliseconds. For example,
-- you can flag speech that contains more than 10,000 milliseconds of
-- interruptions.
newInterruptionFilter ::
  InterruptionFilter
newInterruptionFilter :: InterruptionFilter
newInterruptionFilter =
  InterruptionFilter'
    { $sel:absoluteTimeRange:InterruptionFilter' :: Maybe AbsoluteTimeRange
absoluteTimeRange =
        forall a. Maybe a
Prelude.Nothing,
      $sel:negate:InterruptionFilter' :: Maybe Bool
negate = forall a. Maybe a
Prelude.Nothing,
      $sel:participantRole:InterruptionFilter' :: Maybe ParticipantRole
participantRole = forall a. Maybe a
Prelude.Nothing,
      $sel:relativeTimeRange:InterruptionFilter' :: Maybe RelativeTimeRange
relativeTimeRange = forall a. Maybe a
Prelude.Nothing,
      $sel:threshold:InterruptionFilter' :: Maybe Natural
threshold = forall a. Maybe a
Prelude.Nothing
    }

-- | Makes it possible to specify a time range (in milliseconds) in your
-- audio, during which you want to search for an interruption. See for more
-- detail.
interruptionFilter_absoluteTimeRange :: Lens.Lens' InterruptionFilter (Prelude.Maybe AbsoluteTimeRange)
interruptionFilter_absoluteTimeRange :: Lens' InterruptionFilter (Maybe AbsoluteTimeRange)
interruptionFilter_absoluteTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InterruptionFilter' {Maybe AbsoluteTimeRange
absoluteTimeRange :: Maybe AbsoluteTimeRange
$sel:absoluteTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe AbsoluteTimeRange
absoluteTimeRange} -> Maybe AbsoluteTimeRange
absoluteTimeRange) (\s :: InterruptionFilter
s@InterruptionFilter' {} Maybe AbsoluteTimeRange
a -> InterruptionFilter
s {$sel:absoluteTimeRange:InterruptionFilter' :: Maybe AbsoluteTimeRange
absoluteTimeRange = Maybe AbsoluteTimeRange
a} :: InterruptionFilter)

-- | Set to @TRUE@ to flag speech that does not contain interruptions. Set to
-- @FALSE@ to flag speech that contains interruptions.
interruptionFilter_negate :: Lens.Lens' InterruptionFilter (Prelude.Maybe Prelude.Bool)
interruptionFilter_negate :: Lens' InterruptionFilter (Maybe Bool)
interruptionFilter_negate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InterruptionFilter' {Maybe Bool
negate :: Maybe Bool
$sel:negate:InterruptionFilter' :: InterruptionFilter -> Maybe Bool
negate} -> Maybe Bool
negate) (\s :: InterruptionFilter
s@InterruptionFilter' {} Maybe Bool
a -> InterruptionFilter
s {$sel:negate:InterruptionFilter' :: Maybe Bool
negate = Maybe Bool
a} :: InterruptionFilter)

-- | Specify the interrupter that you want to flag. Omitting this parameter
-- is equivalent to specifying both participants.
interruptionFilter_participantRole :: Lens.Lens' InterruptionFilter (Prelude.Maybe ParticipantRole)
interruptionFilter_participantRole :: Lens' InterruptionFilter (Maybe ParticipantRole)
interruptionFilter_participantRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InterruptionFilter' {Maybe ParticipantRole
participantRole :: Maybe ParticipantRole
$sel:participantRole:InterruptionFilter' :: InterruptionFilter -> Maybe ParticipantRole
participantRole} -> Maybe ParticipantRole
participantRole) (\s :: InterruptionFilter
s@InterruptionFilter' {} Maybe ParticipantRole
a -> InterruptionFilter
s {$sel:participantRole:InterruptionFilter' :: Maybe ParticipantRole
participantRole = Maybe ParticipantRole
a} :: InterruptionFilter)

-- | Makes it possible to specify a time range (in percentage) in your media
-- file, during which you want to search for an interruption. See for more
-- detail.
interruptionFilter_relativeTimeRange :: Lens.Lens' InterruptionFilter (Prelude.Maybe RelativeTimeRange)
interruptionFilter_relativeTimeRange :: Lens' InterruptionFilter (Maybe RelativeTimeRange)
interruptionFilter_relativeTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InterruptionFilter' {Maybe RelativeTimeRange
relativeTimeRange :: Maybe RelativeTimeRange
$sel:relativeTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe RelativeTimeRange
relativeTimeRange} -> Maybe RelativeTimeRange
relativeTimeRange) (\s :: InterruptionFilter
s@InterruptionFilter' {} Maybe RelativeTimeRange
a -> InterruptionFilter
s {$sel:relativeTimeRange:InterruptionFilter' :: Maybe RelativeTimeRange
relativeTimeRange = Maybe RelativeTimeRange
a} :: InterruptionFilter)

-- | Specify the duration of the interruptions in milliseconds. For example,
-- you can flag speech that contains more than 10,000 milliseconds of
-- interruptions.
interruptionFilter_threshold :: Lens.Lens' InterruptionFilter (Prelude.Maybe Prelude.Natural)
interruptionFilter_threshold :: Lens' InterruptionFilter (Maybe Natural)
interruptionFilter_threshold = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InterruptionFilter' {Maybe Natural
threshold :: Maybe Natural
$sel:threshold:InterruptionFilter' :: InterruptionFilter -> Maybe Natural
threshold} -> Maybe Natural
threshold) (\s :: InterruptionFilter
s@InterruptionFilter' {} Maybe Natural
a -> InterruptionFilter
s {$sel:threshold:InterruptionFilter' :: Maybe Natural
threshold = Maybe Natural
a} :: InterruptionFilter)

instance Data.FromJSON InterruptionFilter where
  parseJSON :: Value -> Parser InterruptionFilter
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"InterruptionFilter"
      ( \Object
x ->
          Maybe AbsoluteTimeRange
-> Maybe Bool
-> Maybe ParticipantRole
-> Maybe RelativeTimeRange
-> Maybe Natural
-> InterruptionFilter
InterruptionFilter'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AbsoluteTimeRange")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Negate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ParticipantRole")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RelativeTimeRange")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Threshold")
      )

instance Prelude.Hashable InterruptionFilter where
  hashWithSalt :: Int -> InterruptionFilter -> Int
hashWithSalt Int
_salt InterruptionFilter' {Maybe Bool
Maybe Natural
Maybe AbsoluteTimeRange
Maybe ParticipantRole
Maybe RelativeTimeRange
threshold :: Maybe Natural
relativeTimeRange :: Maybe RelativeTimeRange
participantRole :: Maybe ParticipantRole
negate :: Maybe Bool
absoluteTimeRange :: Maybe AbsoluteTimeRange
$sel:threshold:InterruptionFilter' :: InterruptionFilter -> Maybe Natural
$sel:relativeTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe RelativeTimeRange
$sel:participantRole:InterruptionFilter' :: InterruptionFilter -> Maybe ParticipantRole
$sel:negate:InterruptionFilter' :: InterruptionFilter -> Maybe Bool
$sel:absoluteTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe AbsoluteTimeRange
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AbsoluteTimeRange
absoluteTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
negate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ParticipantRole
participantRole
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RelativeTimeRange
relativeTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
threshold

instance Prelude.NFData InterruptionFilter where
  rnf :: InterruptionFilter -> ()
rnf InterruptionFilter' {Maybe Bool
Maybe Natural
Maybe AbsoluteTimeRange
Maybe ParticipantRole
Maybe RelativeTimeRange
threshold :: Maybe Natural
relativeTimeRange :: Maybe RelativeTimeRange
participantRole :: Maybe ParticipantRole
negate :: Maybe Bool
absoluteTimeRange :: Maybe AbsoluteTimeRange
$sel:threshold:InterruptionFilter' :: InterruptionFilter -> Maybe Natural
$sel:relativeTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe RelativeTimeRange
$sel:participantRole:InterruptionFilter' :: InterruptionFilter -> Maybe ParticipantRole
$sel:negate:InterruptionFilter' :: InterruptionFilter -> Maybe Bool
$sel:absoluteTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe AbsoluteTimeRange
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AbsoluteTimeRange
absoluteTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
negate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ParticipantRole
participantRole
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RelativeTimeRange
relativeTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
threshold

instance Data.ToJSON InterruptionFilter where
  toJSON :: InterruptionFilter -> Value
toJSON InterruptionFilter' {Maybe Bool
Maybe Natural
Maybe AbsoluteTimeRange
Maybe ParticipantRole
Maybe RelativeTimeRange
threshold :: Maybe Natural
relativeTimeRange :: Maybe RelativeTimeRange
participantRole :: Maybe ParticipantRole
negate :: Maybe Bool
absoluteTimeRange :: Maybe AbsoluteTimeRange
$sel:threshold:InterruptionFilter' :: InterruptionFilter -> Maybe Natural
$sel:relativeTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe RelativeTimeRange
$sel:participantRole:InterruptionFilter' :: InterruptionFilter -> Maybe ParticipantRole
$sel:negate:InterruptionFilter' :: InterruptionFilter -> Maybe Bool
$sel:absoluteTimeRange:InterruptionFilter' :: InterruptionFilter -> Maybe AbsoluteTimeRange
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AbsoluteTimeRange" 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 AbsoluteTimeRange
absoluteTimeRange,
            (Key
"Negate" 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
negate,
            (Key
"ParticipantRole" 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 ParticipantRole
participantRole,
            (Key
"RelativeTimeRange" 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 RelativeTimeRange
relativeTimeRange,
            (Key
"Threshold" 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 Natural
threshold
          ]
      )