{-# 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.Evidently.Types.Project
-- 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.Evidently.Types.Project where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Evidently.Types.ProjectAppConfigResource
import Amazonka.Evidently.Types.ProjectDataDelivery
import Amazonka.Evidently.Types.ProjectStatus
import qualified Amazonka.Prelude as Prelude

-- | This structure defines a project, which is the logical object in
-- Evidently that can contain features, launches, and experiments. Use
-- projects to group similar features together.
--
-- /See:/ 'newProject' smart constructor.
data Project = Project'
  { -- | The number of ongoing experiments currently in the project.
    Project -> Maybe Integer
activeExperimentCount :: Prelude.Maybe Prelude.Integer,
    -- | The number of ongoing launches currently in the project.
    Project -> Maybe Integer
activeLaunchCount :: Prelude.Maybe Prelude.Integer,
    -- | This structure defines the configuration of how your application
    -- integrates with AppConfig to run client-side evaluation.
    Project -> Maybe ProjectAppConfigResource
appConfigResource :: Prelude.Maybe ProjectAppConfigResource,
    -- | A structure that contains information about where Evidently is to store
    -- evaluation events for longer term storage.
    Project -> Maybe ProjectDataDelivery
dataDelivery :: Prelude.Maybe ProjectDataDelivery,
    -- | The user-entered description of the project.
    Project -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The number of experiments currently in the project. This includes all
    -- experiments that have been created and not deleted, whether they are
    -- ongoing or not.
    Project -> Maybe Integer
experimentCount :: Prelude.Maybe Prelude.Integer,
    -- | The number of features currently in the project.
    Project -> Maybe Integer
featureCount :: Prelude.Maybe Prelude.Integer,
    -- | The number of launches currently in the project. This includes all
    -- launches that have been created and not deleted, whether they are
    -- ongoing or not.
    Project -> Maybe Integer
launchCount :: Prelude.Maybe Prelude.Integer,
    -- | The list of tag keys and values associated with this project.
    Project -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name or ARN of the project.
    Project -> Text
arn :: Prelude.Text,
    -- | The date and time that the project is created.
    Project -> POSIX
createdTime :: Data.POSIX,
    -- | The date and time that the project was most recently updated.
    Project -> POSIX
lastUpdatedTime :: Data.POSIX,
    -- | The name of the project.
    Project -> Text
name :: Prelude.Text,
    -- | The current state of the project.
    Project -> ProjectStatus
status :: ProjectStatus
  }
  deriving (Project -> Project -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Project -> Project -> Bool
$c/= :: Project -> Project -> Bool
== :: Project -> Project -> Bool
$c== :: Project -> Project -> Bool
Prelude.Eq, ReadPrec [Project]
ReadPrec Project
Int -> ReadS Project
ReadS [Project]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Project]
$creadListPrec :: ReadPrec [Project]
readPrec :: ReadPrec Project
$creadPrec :: ReadPrec Project
readList :: ReadS [Project]
$creadList :: ReadS [Project]
readsPrec :: Int -> ReadS Project
$creadsPrec :: Int -> ReadS Project
Prelude.Read, Int -> Project -> ShowS
[Project] -> ShowS
Project -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Project] -> ShowS
$cshowList :: [Project] -> ShowS
show :: Project -> String
$cshow :: Project -> String
showsPrec :: Int -> Project -> ShowS
$cshowsPrec :: Int -> Project -> ShowS
Prelude.Show, forall x. Rep Project x -> Project
forall x. Project -> Rep Project x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Project x -> Project
$cfrom :: forall x. Project -> Rep Project x
Prelude.Generic)

-- |
-- Create a value of 'Project' 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:
--
-- 'activeExperimentCount', 'project_activeExperimentCount' - The number of ongoing experiments currently in the project.
--
-- 'activeLaunchCount', 'project_activeLaunchCount' - The number of ongoing launches currently in the project.
--
-- 'appConfigResource', 'project_appConfigResource' - This structure defines the configuration of how your application
-- integrates with AppConfig to run client-side evaluation.
--
-- 'dataDelivery', 'project_dataDelivery' - A structure that contains information about where Evidently is to store
-- evaluation events for longer term storage.
--
-- 'description', 'project_description' - The user-entered description of the project.
--
-- 'experimentCount', 'project_experimentCount' - The number of experiments currently in the project. This includes all
-- experiments that have been created and not deleted, whether they are
-- ongoing or not.
--
-- 'featureCount', 'project_featureCount' - The number of features currently in the project.
--
-- 'launchCount', 'project_launchCount' - The number of launches currently in the project. This includes all
-- launches that have been created and not deleted, whether they are
-- ongoing or not.
--
-- 'tags', 'project_tags' - The list of tag keys and values associated with this project.
--
-- 'arn', 'project_arn' - The name or ARN of the project.
--
-- 'createdTime', 'project_createdTime' - The date and time that the project is created.
--
-- 'lastUpdatedTime', 'project_lastUpdatedTime' - The date and time that the project was most recently updated.
--
-- 'name', 'project_name' - The name of the project.
--
-- 'status', 'project_status' - The current state of the project.
newProject ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'createdTime'
  Prelude.UTCTime ->
  -- | 'lastUpdatedTime'
  Prelude.UTCTime ->
  -- | 'name'
  Prelude.Text ->
  -- | 'status'
  ProjectStatus ->
  Project
newProject :: Text -> UTCTime -> UTCTime -> Text -> ProjectStatus -> Project
newProject
  Text
pArn_
  UTCTime
pCreatedTime_
  UTCTime
pLastUpdatedTime_
  Text
pName_
  ProjectStatus
pStatus_ =
    Project'
      { $sel:activeExperimentCount:Project' :: Maybe Integer
activeExperimentCount = forall a. Maybe a
Prelude.Nothing,
        $sel:activeLaunchCount:Project' :: Maybe Integer
activeLaunchCount = forall a. Maybe a
Prelude.Nothing,
        $sel:appConfigResource:Project' :: Maybe ProjectAppConfigResource
appConfigResource = forall a. Maybe a
Prelude.Nothing,
        $sel:dataDelivery:Project' :: Maybe ProjectDataDelivery
dataDelivery = forall a. Maybe a
Prelude.Nothing,
        $sel:description:Project' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:experimentCount:Project' :: Maybe Integer
experimentCount = forall a. Maybe a
Prelude.Nothing,
        $sel:featureCount:Project' :: Maybe Integer
featureCount = forall a. Maybe a
Prelude.Nothing,
        $sel:launchCount:Project' :: Maybe Integer
launchCount = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:Project' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:arn:Project' :: Text
arn = Text
pArn_,
        $sel:createdTime:Project' :: POSIX
createdTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedTime_,
        $sel:lastUpdatedTime:Project' :: POSIX
lastUpdatedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastUpdatedTime_,
        $sel:name:Project' :: Text
name = Text
pName_,
        $sel:status:Project' :: ProjectStatus
status = ProjectStatus
pStatus_
      }

-- | The number of ongoing experiments currently in the project.
project_activeExperimentCount :: Lens.Lens' Project (Prelude.Maybe Prelude.Integer)
project_activeExperimentCount :: Lens' Project (Maybe Integer)
project_activeExperimentCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Integer
activeExperimentCount :: Maybe Integer
$sel:activeExperimentCount:Project' :: Project -> Maybe Integer
activeExperimentCount} -> Maybe Integer
activeExperimentCount) (\s :: Project
s@Project' {} Maybe Integer
a -> Project
s {$sel:activeExperimentCount:Project' :: Maybe Integer
activeExperimentCount = Maybe Integer
a} :: Project)

-- | The number of ongoing launches currently in the project.
project_activeLaunchCount :: Lens.Lens' Project (Prelude.Maybe Prelude.Integer)
project_activeLaunchCount :: Lens' Project (Maybe Integer)
project_activeLaunchCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Integer
activeLaunchCount :: Maybe Integer
$sel:activeLaunchCount:Project' :: Project -> Maybe Integer
activeLaunchCount} -> Maybe Integer
activeLaunchCount) (\s :: Project
s@Project' {} Maybe Integer
a -> Project
s {$sel:activeLaunchCount:Project' :: Maybe Integer
activeLaunchCount = Maybe Integer
a} :: Project)

-- | This structure defines the configuration of how your application
-- integrates with AppConfig to run client-side evaluation.
project_appConfigResource :: Lens.Lens' Project (Prelude.Maybe ProjectAppConfigResource)
project_appConfigResource :: Lens' Project (Maybe ProjectAppConfigResource)
project_appConfigResource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe ProjectAppConfigResource
appConfigResource :: Maybe ProjectAppConfigResource
$sel:appConfigResource:Project' :: Project -> Maybe ProjectAppConfigResource
appConfigResource} -> Maybe ProjectAppConfigResource
appConfigResource) (\s :: Project
s@Project' {} Maybe ProjectAppConfigResource
a -> Project
s {$sel:appConfigResource:Project' :: Maybe ProjectAppConfigResource
appConfigResource = Maybe ProjectAppConfigResource
a} :: Project)

-- | A structure that contains information about where Evidently is to store
-- evaluation events for longer term storage.
project_dataDelivery :: Lens.Lens' Project (Prelude.Maybe ProjectDataDelivery)
project_dataDelivery :: Lens' Project (Maybe ProjectDataDelivery)
project_dataDelivery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe ProjectDataDelivery
dataDelivery :: Maybe ProjectDataDelivery
$sel:dataDelivery:Project' :: Project -> Maybe ProjectDataDelivery
dataDelivery} -> Maybe ProjectDataDelivery
dataDelivery) (\s :: Project
s@Project' {} Maybe ProjectDataDelivery
a -> Project
s {$sel:dataDelivery:Project' :: Maybe ProjectDataDelivery
dataDelivery = Maybe ProjectDataDelivery
a} :: Project)

-- | The user-entered description of the project.
project_description :: Lens.Lens' Project (Prelude.Maybe Prelude.Text)
project_description :: Lens' Project (Maybe Text)
project_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Text
description :: Maybe Text
$sel:description:Project' :: Project -> Maybe Text
description} -> Maybe Text
description) (\s :: Project
s@Project' {} Maybe Text
a -> Project
s {$sel:description:Project' :: Maybe Text
description = Maybe Text
a} :: Project)

-- | The number of experiments currently in the project. This includes all
-- experiments that have been created and not deleted, whether they are
-- ongoing or not.
project_experimentCount :: Lens.Lens' Project (Prelude.Maybe Prelude.Integer)
project_experimentCount :: Lens' Project (Maybe Integer)
project_experimentCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Integer
experimentCount :: Maybe Integer
$sel:experimentCount:Project' :: Project -> Maybe Integer
experimentCount} -> Maybe Integer
experimentCount) (\s :: Project
s@Project' {} Maybe Integer
a -> Project
s {$sel:experimentCount:Project' :: Maybe Integer
experimentCount = Maybe Integer
a} :: Project)

-- | The number of features currently in the project.
project_featureCount :: Lens.Lens' Project (Prelude.Maybe Prelude.Integer)
project_featureCount :: Lens' Project (Maybe Integer)
project_featureCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Integer
featureCount :: Maybe Integer
$sel:featureCount:Project' :: Project -> Maybe Integer
featureCount} -> Maybe Integer
featureCount) (\s :: Project
s@Project' {} Maybe Integer
a -> Project
s {$sel:featureCount:Project' :: Maybe Integer
featureCount = Maybe Integer
a} :: Project)

-- | The number of launches currently in the project. This includes all
-- launches that have been created and not deleted, whether they are
-- ongoing or not.
project_launchCount :: Lens.Lens' Project (Prelude.Maybe Prelude.Integer)
project_launchCount :: Lens' Project (Maybe Integer)
project_launchCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe Integer
launchCount :: Maybe Integer
$sel:launchCount:Project' :: Project -> Maybe Integer
launchCount} -> Maybe Integer
launchCount) (\s :: Project
s@Project' {} Maybe Integer
a -> Project
s {$sel:launchCount:Project' :: Maybe Integer
launchCount = Maybe Integer
a} :: Project)

-- | The list of tag keys and values associated with this project.
project_tags :: Lens.Lens' Project (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
project_tags :: Lens' Project (Maybe (HashMap Text Text))
project_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Project' :: Project -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Project
s@Project' {} Maybe (HashMap Text Text)
a -> Project
s {$sel:tags:Project' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Project) 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 or ARN of the project.
project_arn :: Lens.Lens' Project Prelude.Text
project_arn :: Lens' Project Text
project_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {Text
arn :: Text
$sel:arn:Project' :: Project -> Text
arn} -> Text
arn) (\s :: Project
s@Project' {} Text
a -> Project
s {$sel:arn:Project' :: Text
arn = Text
a} :: Project)

-- | The date and time that the project is created.
project_createdTime :: Lens.Lens' Project Prelude.UTCTime
project_createdTime :: Lens' Project UTCTime
project_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {POSIX
createdTime :: POSIX
$sel:createdTime:Project' :: Project -> POSIX
createdTime} -> POSIX
createdTime) (\s :: Project
s@Project' {} POSIX
a -> Project
s {$sel:createdTime:Project' :: POSIX
createdTime = POSIX
a} :: Project) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date and time that the project was most recently updated.
project_lastUpdatedTime :: Lens.Lens' Project Prelude.UTCTime
project_lastUpdatedTime :: Lens' Project UTCTime
project_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {POSIX
lastUpdatedTime :: POSIX
$sel:lastUpdatedTime:Project' :: Project -> POSIX
lastUpdatedTime} -> POSIX
lastUpdatedTime) (\s :: Project
s@Project' {} POSIX
a -> Project
s {$sel:lastUpdatedTime:Project' :: POSIX
lastUpdatedTime = POSIX
a} :: Project) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The current state of the project.
project_status :: Lens.Lens' Project ProjectStatus
project_status :: Lens' Project ProjectStatus
project_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Project' {ProjectStatus
status :: ProjectStatus
$sel:status:Project' :: Project -> ProjectStatus
status} -> ProjectStatus
status) (\s :: Project
s@Project' {} ProjectStatus
a -> Project
s {$sel:status:Project' :: ProjectStatus
status = ProjectStatus
a} :: Project)

instance Data.FromJSON Project where
  parseJSON :: Value -> Parser Project
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Project"
      ( \Object
x ->
          Maybe Integer
-> Maybe Integer
-> Maybe ProjectAppConfigResource
-> Maybe ProjectDataDelivery
-> Maybe Text
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> Maybe (HashMap Text Text)
-> Text
-> POSIX
-> POSIX
-> Text
-> ProjectStatus
-> Project
Project'
            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
"activeExperimentCount")
            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
"activeLaunchCount")
            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
"appConfigResource")
            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
"dataDelivery")
            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
"description")
            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
"experimentCount")
            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
"featureCount")
            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
"launchCount")
            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
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"arn")
            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
"createdTime")
            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
"lastUpdatedTime")
            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
"name")
            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
"status")
      )

instance Prelude.Hashable Project where
  hashWithSalt :: Int -> Project -> Int
hashWithSalt Int
_salt Project' {Maybe Integer
Maybe Text
Maybe (HashMap Text Text)
Maybe ProjectAppConfigResource
Maybe ProjectDataDelivery
Text
POSIX
ProjectStatus
status :: ProjectStatus
name :: Text
lastUpdatedTime :: POSIX
createdTime :: POSIX
arn :: Text
tags :: Maybe (HashMap Text Text)
launchCount :: Maybe Integer
featureCount :: Maybe Integer
experimentCount :: Maybe Integer
description :: Maybe Text
dataDelivery :: Maybe ProjectDataDelivery
appConfigResource :: Maybe ProjectAppConfigResource
activeLaunchCount :: Maybe Integer
activeExperimentCount :: Maybe Integer
$sel:status:Project' :: Project -> ProjectStatus
$sel:name:Project' :: Project -> Text
$sel:lastUpdatedTime:Project' :: Project -> POSIX
$sel:createdTime:Project' :: Project -> POSIX
$sel:arn:Project' :: Project -> Text
$sel:tags:Project' :: Project -> Maybe (HashMap Text Text)
$sel:launchCount:Project' :: Project -> Maybe Integer
$sel:featureCount:Project' :: Project -> Maybe Integer
$sel:experimentCount:Project' :: Project -> Maybe Integer
$sel:description:Project' :: Project -> Maybe Text
$sel:dataDelivery:Project' :: Project -> Maybe ProjectDataDelivery
$sel:appConfigResource:Project' :: Project -> Maybe ProjectAppConfigResource
$sel:activeLaunchCount:Project' :: Project -> Maybe Integer
$sel:activeExperimentCount:Project' :: Project -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
activeExperimentCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
activeLaunchCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectAppConfigResource
appConfigResource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectDataDelivery
dataDelivery
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
experimentCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
featureCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
launchCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastUpdatedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProjectStatus
status

instance Prelude.NFData Project where
  rnf :: Project -> ()
rnf Project' {Maybe Integer
Maybe Text
Maybe (HashMap Text Text)
Maybe ProjectAppConfigResource
Maybe ProjectDataDelivery
Text
POSIX
ProjectStatus
status :: ProjectStatus
name :: Text
lastUpdatedTime :: POSIX
createdTime :: POSIX
arn :: Text
tags :: Maybe (HashMap Text Text)
launchCount :: Maybe Integer
featureCount :: Maybe Integer
experimentCount :: Maybe Integer
description :: Maybe Text
dataDelivery :: Maybe ProjectDataDelivery
appConfigResource :: Maybe ProjectAppConfigResource
activeLaunchCount :: Maybe Integer
activeExperimentCount :: Maybe Integer
$sel:status:Project' :: Project -> ProjectStatus
$sel:name:Project' :: Project -> Text
$sel:lastUpdatedTime:Project' :: Project -> POSIX
$sel:createdTime:Project' :: Project -> POSIX
$sel:arn:Project' :: Project -> Text
$sel:tags:Project' :: Project -> Maybe (HashMap Text Text)
$sel:launchCount:Project' :: Project -> Maybe Integer
$sel:featureCount:Project' :: Project -> Maybe Integer
$sel:experimentCount:Project' :: Project -> Maybe Integer
$sel:description:Project' :: Project -> Maybe Text
$sel:dataDelivery:Project' :: Project -> Maybe ProjectDataDelivery
$sel:appConfigResource:Project' :: Project -> Maybe ProjectAppConfigResource
$sel:activeLaunchCount:Project' :: Project -> Maybe Integer
$sel:activeExperimentCount:Project' :: Project -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
activeExperimentCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
activeLaunchCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectAppConfigResource
appConfigResource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectDataDelivery
dataDelivery
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Integer
experimentCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
featureCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
launchCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastUpdatedTime
      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 ProjectStatus
status