{-# 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.EC2.Types.FpgaImageAttribute
-- 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.EC2.Types.FpgaImageAttribute where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.LoadPermission
import Amazonka.EC2.Types.ProductCode
import qualified Amazonka.Prelude as Prelude

-- | Describes an Amazon FPGA image (AFI) attribute.
--
-- /See:/ 'newFpgaImageAttribute' smart constructor.
data FpgaImageAttribute = FpgaImageAttribute'
  { -- | The description of the AFI.
    FpgaImageAttribute -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the AFI.
    FpgaImageAttribute -> Maybe Text
fpgaImageId :: Prelude.Maybe Prelude.Text,
    -- | The load permissions.
    FpgaImageAttribute -> Maybe [LoadPermission]
loadPermissions :: Prelude.Maybe [LoadPermission],
    -- | The name of the AFI.
    FpgaImageAttribute -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The product codes.
    FpgaImageAttribute -> Maybe [ProductCode]
productCodes :: Prelude.Maybe [ProductCode]
  }
  deriving (FpgaImageAttribute -> FpgaImageAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FpgaImageAttribute -> FpgaImageAttribute -> Bool
$c/= :: FpgaImageAttribute -> FpgaImageAttribute -> Bool
== :: FpgaImageAttribute -> FpgaImageAttribute -> Bool
$c== :: FpgaImageAttribute -> FpgaImageAttribute -> Bool
Prelude.Eq, ReadPrec [FpgaImageAttribute]
ReadPrec FpgaImageAttribute
Int -> ReadS FpgaImageAttribute
ReadS [FpgaImageAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FpgaImageAttribute]
$creadListPrec :: ReadPrec [FpgaImageAttribute]
readPrec :: ReadPrec FpgaImageAttribute
$creadPrec :: ReadPrec FpgaImageAttribute
readList :: ReadS [FpgaImageAttribute]
$creadList :: ReadS [FpgaImageAttribute]
readsPrec :: Int -> ReadS FpgaImageAttribute
$creadsPrec :: Int -> ReadS FpgaImageAttribute
Prelude.Read, Int -> FpgaImageAttribute -> ShowS
[FpgaImageAttribute] -> ShowS
FpgaImageAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FpgaImageAttribute] -> ShowS
$cshowList :: [FpgaImageAttribute] -> ShowS
show :: FpgaImageAttribute -> String
$cshow :: FpgaImageAttribute -> String
showsPrec :: Int -> FpgaImageAttribute -> ShowS
$cshowsPrec :: Int -> FpgaImageAttribute -> ShowS
Prelude.Show, forall x. Rep FpgaImageAttribute x -> FpgaImageAttribute
forall x. FpgaImageAttribute -> Rep FpgaImageAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FpgaImageAttribute x -> FpgaImageAttribute
$cfrom :: forall x. FpgaImageAttribute -> Rep FpgaImageAttribute x
Prelude.Generic)

-- |
-- Create a value of 'FpgaImageAttribute' 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:
--
-- 'description', 'fpgaImageAttribute_description' - The description of the AFI.
--
-- 'fpgaImageId', 'fpgaImageAttribute_fpgaImageId' - The ID of the AFI.
--
-- 'loadPermissions', 'fpgaImageAttribute_loadPermissions' - The load permissions.
--
-- 'name', 'fpgaImageAttribute_name' - The name of the AFI.
--
-- 'productCodes', 'fpgaImageAttribute_productCodes' - The product codes.
newFpgaImageAttribute ::
  FpgaImageAttribute
newFpgaImageAttribute :: FpgaImageAttribute
newFpgaImageAttribute =
  FpgaImageAttribute'
    { $sel:description:FpgaImageAttribute' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:fpgaImageId:FpgaImageAttribute' :: Maybe Text
fpgaImageId = forall a. Maybe a
Prelude.Nothing,
      $sel:loadPermissions:FpgaImageAttribute' :: Maybe [LoadPermission]
loadPermissions = forall a. Maybe a
Prelude.Nothing,
      $sel:name:FpgaImageAttribute' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:productCodes:FpgaImageAttribute' :: Maybe [ProductCode]
productCodes = forall a. Maybe a
Prelude.Nothing
    }

-- | The description of the AFI.
fpgaImageAttribute_description :: Lens.Lens' FpgaImageAttribute (Prelude.Maybe Prelude.Text)
fpgaImageAttribute_description :: Lens' FpgaImageAttribute (Maybe Text)
fpgaImageAttribute_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FpgaImageAttribute' {Maybe Text
description :: Maybe Text
$sel:description:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
description} -> Maybe Text
description) (\s :: FpgaImageAttribute
s@FpgaImageAttribute' {} Maybe Text
a -> FpgaImageAttribute
s {$sel:description:FpgaImageAttribute' :: Maybe Text
description = Maybe Text
a} :: FpgaImageAttribute)

-- | The ID of the AFI.
fpgaImageAttribute_fpgaImageId :: Lens.Lens' FpgaImageAttribute (Prelude.Maybe Prelude.Text)
fpgaImageAttribute_fpgaImageId :: Lens' FpgaImageAttribute (Maybe Text)
fpgaImageAttribute_fpgaImageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FpgaImageAttribute' {Maybe Text
fpgaImageId :: Maybe Text
$sel:fpgaImageId:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
fpgaImageId} -> Maybe Text
fpgaImageId) (\s :: FpgaImageAttribute
s@FpgaImageAttribute' {} Maybe Text
a -> FpgaImageAttribute
s {$sel:fpgaImageId:FpgaImageAttribute' :: Maybe Text
fpgaImageId = Maybe Text
a} :: FpgaImageAttribute)

-- | The load permissions.
fpgaImageAttribute_loadPermissions :: Lens.Lens' FpgaImageAttribute (Prelude.Maybe [LoadPermission])
fpgaImageAttribute_loadPermissions :: Lens' FpgaImageAttribute (Maybe [LoadPermission])
fpgaImageAttribute_loadPermissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FpgaImageAttribute' {Maybe [LoadPermission]
loadPermissions :: Maybe [LoadPermission]
$sel:loadPermissions:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [LoadPermission]
loadPermissions} -> Maybe [LoadPermission]
loadPermissions) (\s :: FpgaImageAttribute
s@FpgaImageAttribute' {} Maybe [LoadPermission]
a -> FpgaImageAttribute
s {$sel:loadPermissions:FpgaImageAttribute' :: Maybe [LoadPermission]
loadPermissions = Maybe [LoadPermission]
a} :: FpgaImageAttribute) 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

-- | The name of the AFI.
fpgaImageAttribute_name :: Lens.Lens' FpgaImageAttribute (Prelude.Maybe Prelude.Text)
fpgaImageAttribute_name :: Lens' FpgaImageAttribute (Maybe Text)
fpgaImageAttribute_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FpgaImageAttribute' {Maybe Text
name :: Maybe Text
$sel:name:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
name} -> Maybe Text
name) (\s :: FpgaImageAttribute
s@FpgaImageAttribute' {} Maybe Text
a -> FpgaImageAttribute
s {$sel:name:FpgaImageAttribute' :: Maybe Text
name = Maybe Text
a} :: FpgaImageAttribute)

-- | The product codes.
fpgaImageAttribute_productCodes :: Lens.Lens' FpgaImageAttribute (Prelude.Maybe [ProductCode])
fpgaImageAttribute_productCodes :: Lens' FpgaImageAttribute (Maybe [ProductCode])
fpgaImageAttribute_productCodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FpgaImageAttribute' {Maybe [ProductCode]
productCodes :: Maybe [ProductCode]
$sel:productCodes:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [ProductCode]
productCodes} -> Maybe [ProductCode]
productCodes) (\s :: FpgaImageAttribute
s@FpgaImageAttribute' {} Maybe [ProductCode]
a -> FpgaImageAttribute
s {$sel:productCodes:FpgaImageAttribute' :: Maybe [ProductCode]
productCodes = Maybe [ProductCode]
a} :: FpgaImageAttribute) 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

instance Data.FromXML FpgaImageAttribute where
  parseXML :: [Node] -> Either String FpgaImageAttribute
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe [LoadPermission]
-> Maybe Text
-> Maybe [ProductCode]
-> FpgaImageAttribute
FpgaImageAttribute'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"description")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"fpgaImageId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"loadPermissions"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"name")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"productCodes"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )

instance Prelude.Hashable FpgaImageAttribute where
  hashWithSalt :: Int -> FpgaImageAttribute -> Int
hashWithSalt Int
_salt FpgaImageAttribute' {Maybe [LoadPermission]
Maybe [ProductCode]
Maybe Text
productCodes :: Maybe [ProductCode]
name :: Maybe Text
loadPermissions :: Maybe [LoadPermission]
fpgaImageId :: Maybe Text
description :: Maybe Text
$sel:productCodes:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [ProductCode]
$sel:name:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
$sel:loadPermissions:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [LoadPermission]
$sel:fpgaImageId:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
$sel:description:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fpgaImageId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LoadPermission]
loadPermissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProductCode]
productCodes

instance Prelude.NFData FpgaImageAttribute where
  rnf :: FpgaImageAttribute -> ()
rnf FpgaImageAttribute' {Maybe [LoadPermission]
Maybe [ProductCode]
Maybe Text
productCodes :: Maybe [ProductCode]
name :: Maybe Text
loadPermissions :: Maybe [LoadPermission]
fpgaImageId :: Maybe Text
description :: Maybe Text
$sel:productCodes:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [ProductCode]
$sel:name:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
$sel:loadPermissions:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe [LoadPermission]
$sel:fpgaImageId:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
$sel:description:FpgaImageAttribute' :: FpgaImageAttribute -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fpgaImageId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LoadPermission]
loadPermissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProductCode]
productCodes