{-# 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.ElasticTranscoder.Types.AudioCodecOptions
-- 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.ElasticTranscoder.Types.AudioCodecOptions 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

-- | Options associated with your audio codec.
--
-- /See:/ 'newAudioCodecOptions' smart constructor.
data AudioCodecOptions = AudioCodecOptions'
  { -- | You can only choose an audio bit depth when you specify @flac@ or @pcm@
    -- for the value of Audio:Codec.
    --
    -- The bit depth of a sample is how many bits of information are included
    -- in the audio samples. The higher the bit depth, the better the audio,
    -- but the larger the file.
    --
    -- Valid values are @16@ and @24@.
    --
    -- The most common bit depth is @24@.
    AudioCodecOptions -> Maybe Text
bitDepth :: Prelude.Maybe Prelude.Text,
    -- | You can only choose an audio bit order when you specify @pcm@ for the
    -- value of Audio:Codec.
    --
    -- The order the bits of a PCM sample are stored in.
    --
    -- The supported value is @LittleEndian@.
    AudioCodecOptions -> Maybe Text
bitOrder :: Prelude.Maybe Prelude.Text,
    -- | You can only choose an audio profile when you specify AAC for the value
    -- of Audio:Codec.
    --
    -- Specify the AAC profile for the output file. Elastic Transcoder supports
    -- the following profiles:
    --
    -- -   @auto@: If you specify @auto@, Elastic Transcoder selects the
    --     profile based on the bit rate selected for the output file.
    --
    -- -   @AAC-LC@: The most common AAC profile. Use for bit rates larger than
    --     64 kbps.
    --
    -- -   @HE-AAC@: Not supported on some older players and devices. Use for
    --     bit rates between 40 and 80 kbps.
    --
    -- -   @HE-AACv2@: Not supported on some players and devices. Use for bit
    --     rates less than 48 kbps.
    --
    -- All outputs in a @Smooth@ playlist must have the same value for
    -- @Profile@.
    --
    -- If you created any presets before AAC profiles were added, Elastic
    -- Transcoder automatically updated your presets to use AAC-LC. You can
    -- change the value as required.
    AudioCodecOptions -> Maybe Text
profile :: Prelude.Maybe Prelude.Text,
    -- | You can only choose whether an audio sample is signed when you specify
    -- @pcm@ for the value of Audio:Codec.
    --
    -- Whether audio samples are represented with negative and positive numbers
    -- (signed) or only positive numbers (unsigned).
    --
    -- The supported value is @Signed@.
    AudioCodecOptions -> Maybe Text
signed :: Prelude.Maybe Prelude.Text
  }
  deriving (AudioCodecOptions -> AudioCodecOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioCodecOptions -> AudioCodecOptions -> Bool
$c/= :: AudioCodecOptions -> AudioCodecOptions -> Bool
== :: AudioCodecOptions -> AudioCodecOptions -> Bool
$c== :: AudioCodecOptions -> AudioCodecOptions -> Bool
Prelude.Eq, ReadPrec [AudioCodecOptions]
ReadPrec AudioCodecOptions
Int -> ReadS AudioCodecOptions
ReadS [AudioCodecOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AudioCodecOptions]
$creadListPrec :: ReadPrec [AudioCodecOptions]
readPrec :: ReadPrec AudioCodecOptions
$creadPrec :: ReadPrec AudioCodecOptions
readList :: ReadS [AudioCodecOptions]
$creadList :: ReadS [AudioCodecOptions]
readsPrec :: Int -> ReadS AudioCodecOptions
$creadsPrec :: Int -> ReadS AudioCodecOptions
Prelude.Read, Int -> AudioCodecOptions -> ShowS
[AudioCodecOptions] -> ShowS
AudioCodecOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AudioCodecOptions] -> ShowS
$cshowList :: [AudioCodecOptions] -> ShowS
show :: AudioCodecOptions -> String
$cshow :: AudioCodecOptions -> String
showsPrec :: Int -> AudioCodecOptions -> ShowS
$cshowsPrec :: Int -> AudioCodecOptions -> ShowS
Prelude.Show, forall x. Rep AudioCodecOptions x -> AudioCodecOptions
forall x. AudioCodecOptions -> Rep AudioCodecOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AudioCodecOptions x -> AudioCodecOptions
$cfrom :: forall x. AudioCodecOptions -> Rep AudioCodecOptions x
Prelude.Generic)

-- |
-- Create a value of 'AudioCodecOptions' 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:
--
-- 'bitDepth', 'audioCodecOptions_bitDepth' - You can only choose an audio bit depth when you specify @flac@ or @pcm@
-- for the value of Audio:Codec.
--
-- The bit depth of a sample is how many bits of information are included
-- in the audio samples. The higher the bit depth, the better the audio,
-- but the larger the file.
--
-- Valid values are @16@ and @24@.
--
-- The most common bit depth is @24@.
--
-- 'bitOrder', 'audioCodecOptions_bitOrder' - You can only choose an audio bit order when you specify @pcm@ for the
-- value of Audio:Codec.
--
-- The order the bits of a PCM sample are stored in.
--
-- The supported value is @LittleEndian@.
--
-- 'profile', 'audioCodecOptions_profile' - You can only choose an audio profile when you specify AAC for the value
-- of Audio:Codec.
--
-- Specify the AAC profile for the output file. Elastic Transcoder supports
-- the following profiles:
--
-- -   @auto@: If you specify @auto@, Elastic Transcoder selects the
--     profile based on the bit rate selected for the output file.
--
-- -   @AAC-LC@: The most common AAC profile. Use for bit rates larger than
--     64 kbps.
--
-- -   @HE-AAC@: Not supported on some older players and devices. Use for
--     bit rates between 40 and 80 kbps.
--
-- -   @HE-AACv2@: Not supported on some players and devices. Use for bit
--     rates less than 48 kbps.
--
-- All outputs in a @Smooth@ playlist must have the same value for
-- @Profile@.
--
-- If you created any presets before AAC profiles were added, Elastic
-- Transcoder automatically updated your presets to use AAC-LC. You can
-- change the value as required.
--
-- 'signed', 'audioCodecOptions_signed' - You can only choose whether an audio sample is signed when you specify
-- @pcm@ for the value of Audio:Codec.
--
-- Whether audio samples are represented with negative and positive numbers
-- (signed) or only positive numbers (unsigned).
--
-- The supported value is @Signed@.
newAudioCodecOptions ::
  AudioCodecOptions
newAudioCodecOptions :: AudioCodecOptions
newAudioCodecOptions =
  AudioCodecOptions'
    { $sel:bitDepth:AudioCodecOptions' :: Maybe Text
bitDepth = forall a. Maybe a
Prelude.Nothing,
      $sel:bitOrder:AudioCodecOptions' :: Maybe Text
bitOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:profile:AudioCodecOptions' :: Maybe Text
profile = forall a. Maybe a
Prelude.Nothing,
      $sel:signed:AudioCodecOptions' :: Maybe Text
signed = forall a. Maybe a
Prelude.Nothing
    }

-- | You can only choose an audio bit depth when you specify @flac@ or @pcm@
-- for the value of Audio:Codec.
--
-- The bit depth of a sample is how many bits of information are included
-- in the audio samples. The higher the bit depth, the better the audio,
-- but the larger the file.
--
-- Valid values are @16@ and @24@.
--
-- The most common bit depth is @24@.
audioCodecOptions_bitDepth :: Lens.Lens' AudioCodecOptions (Prelude.Maybe Prelude.Text)
audioCodecOptions_bitDepth :: Lens' AudioCodecOptions (Maybe Text)
audioCodecOptions_bitDepth = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AudioCodecOptions' {Maybe Text
bitDepth :: Maybe Text
$sel:bitDepth:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
bitDepth} -> Maybe Text
bitDepth) (\s :: AudioCodecOptions
s@AudioCodecOptions' {} Maybe Text
a -> AudioCodecOptions
s {$sel:bitDepth:AudioCodecOptions' :: Maybe Text
bitDepth = Maybe Text
a} :: AudioCodecOptions)

-- | You can only choose an audio bit order when you specify @pcm@ for the
-- value of Audio:Codec.
--
-- The order the bits of a PCM sample are stored in.
--
-- The supported value is @LittleEndian@.
audioCodecOptions_bitOrder :: Lens.Lens' AudioCodecOptions (Prelude.Maybe Prelude.Text)
audioCodecOptions_bitOrder :: Lens' AudioCodecOptions (Maybe Text)
audioCodecOptions_bitOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AudioCodecOptions' {Maybe Text
bitOrder :: Maybe Text
$sel:bitOrder:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
bitOrder} -> Maybe Text
bitOrder) (\s :: AudioCodecOptions
s@AudioCodecOptions' {} Maybe Text
a -> AudioCodecOptions
s {$sel:bitOrder:AudioCodecOptions' :: Maybe Text
bitOrder = Maybe Text
a} :: AudioCodecOptions)

-- | You can only choose an audio profile when you specify AAC for the value
-- of Audio:Codec.
--
-- Specify the AAC profile for the output file. Elastic Transcoder supports
-- the following profiles:
--
-- -   @auto@: If you specify @auto@, Elastic Transcoder selects the
--     profile based on the bit rate selected for the output file.
--
-- -   @AAC-LC@: The most common AAC profile. Use for bit rates larger than
--     64 kbps.
--
-- -   @HE-AAC@: Not supported on some older players and devices. Use for
--     bit rates between 40 and 80 kbps.
--
-- -   @HE-AACv2@: Not supported on some players and devices. Use for bit
--     rates less than 48 kbps.
--
-- All outputs in a @Smooth@ playlist must have the same value for
-- @Profile@.
--
-- If you created any presets before AAC profiles were added, Elastic
-- Transcoder automatically updated your presets to use AAC-LC. You can
-- change the value as required.
audioCodecOptions_profile :: Lens.Lens' AudioCodecOptions (Prelude.Maybe Prelude.Text)
audioCodecOptions_profile :: Lens' AudioCodecOptions (Maybe Text)
audioCodecOptions_profile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AudioCodecOptions' {Maybe Text
profile :: Maybe Text
$sel:profile:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
profile} -> Maybe Text
profile) (\s :: AudioCodecOptions
s@AudioCodecOptions' {} Maybe Text
a -> AudioCodecOptions
s {$sel:profile:AudioCodecOptions' :: Maybe Text
profile = Maybe Text
a} :: AudioCodecOptions)

-- | You can only choose whether an audio sample is signed when you specify
-- @pcm@ for the value of Audio:Codec.
--
-- Whether audio samples are represented with negative and positive numbers
-- (signed) or only positive numbers (unsigned).
--
-- The supported value is @Signed@.
audioCodecOptions_signed :: Lens.Lens' AudioCodecOptions (Prelude.Maybe Prelude.Text)
audioCodecOptions_signed :: Lens' AudioCodecOptions (Maybe Text)
audioCodecOptions_signed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AudioCodecOptions' {Maybe Text
signed :: Maybe Text
$sel:signed:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
signed} -> Maybe Text
signed) (\s :: AudioCodecOptions
s@AudioCodecOptions' {} Maybe Text
a -> AudioCodecOptions
s {$sel:signed:AudioCodecOptions' :: Maybe Text
signed = Maybe Text
a} :: AudioCodecOptions)

instance Data.FromJSON AudioCodecOptions where
  parseJSON :: Value -> Parser AudioCodecOptions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AudioCodecOptions"
      ( \Object
x ->
          Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> AudioCodecOptions
AudioCodecOptions'
            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
"BitDepth")
            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
"BitOrder")
            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
"Profile")
            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
"Signed")
      )

instance Prelude.Hashable AudioCodecOptions where
  hashWithSalt :: Int -> AudioCodecOptions -> Int
hashWithSalt Int
_salt AudioCodecOptions' {Maybe Text
signed :: Maybe Text
profile :: Maybe Text
bitOrder :: Maybe Text
bitDepth :: Maybe Text
$sel:signed:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:profile:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitOrder:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitDepth:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
bitDepth
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
bitOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
profile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
signed

instance Prelude.NFData AudioCodecOptions where
  rnf :: AudioCodecOptions -> ()
rnf AudioCodecOptions' {Maybe Text
signed :: Maybe Text
profile :: Maybe Text
bitOrder :: Maybe Text
bitDepth :: Maybe Text
$sel:signed:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:profile:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitOrder:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitDepth:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
bitDepth
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
bitOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
profile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
signed

instance Data.ToJSON AudioCodecOptions where
  toJSON :: AudioCodecOptions -> Value
toJSON AudioCodecOptions' {Maybe Text
signed :: Maybe Text
profile :: Maybe Text
bitOrder :: Maybe Text
bitDepth :: Maybe Text
$sel:signed:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:profile:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitOrder:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
$sel:bitDepth:AudioCodecOptions' :: AudioCodecOptions -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BitDepth" 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 Text
bitDepth,
            (Key
"BitOrder" 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 Text
bitOrder,
            (Key
"Profile" 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 Text
profile,
            (Key
"Signed" 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 Text
signed
          ]
      )