{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE RecordWildCards    #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.AWS.DAX.Types.Product where
import Network.AWS.DAX.Types.Sum
import Network.AWS.Lens
import Network.AWS.Prelude
data Cluster = Cluster'
  { _cStatus                     :: !(Maybe Text)
  , _cIAMRoleARN                 :: !(Maybe Text)
  , _cClusterARN                 :: !(Maybe Text)
  , _cActiveNodes                :: !(Maybe Int)
  , _cSecurityGroups             :: !(Maybe [SecurityGroupMembership])
  , _cNotificationConfiguration  :: !(Maybe NotificationConfiguration)
  , _cNodeIdsToRemove            :: !(Maybe [Text])
  , _cTotalNodes                 :: !(Maybe Int)
  , _cPreferredMaintenanceWindow :: !(Maybe Text)
  , _cSubnetGroup                :: !(Maybe Text)
  , _cClusterName                :: !(Maybe Text)
  , _cNodeType                   :: !(Maybe Text)
  , _cNodes                      :: !(Maybe [Node])
  , _cClusterDiscoveryEndpoint   :: !(Maybe Endpoint)
  , _cDescription                :: !(Maybe Text)
  , _cParameterGroup             :: !(Maybe ParameterGroupStatus)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
cluster
    :: Cluster
cluster =
  Cluster'
    { _cStatus = Nothing
    , _cIAMRoleARN = Nothing
    , _cClusterARN = Nothing
    , _cActiveNodes = Nothing
    , _cSecurityGroups = Nothing
    , _cNotificationConfiguration = Nothing
    , _cNodeIdsToRemove = Nothing
    , _cTotalNodes = Nothing
    , _cPreferredMaintenanceWindow = Nothing
    , _cSubnetGroup = Nothing
    , _cClusterName = Nothing
    , _cNodeType = Nothing
    , _cNodes = Nothing
    , _cClusterDiscoveryEndpoint = Nothing
    , _cDescription = Nothing
    , _cParameterGroup = Nothing
    }
cStatus :: Lens' Cluster (Maybe Text)
cStatus = lens _cStatus (\ s a -> s{_cStatus = a})
cIAMRoleARN :: Lens' Cluster (Maybe Text)
cIAMRoleARN = lens _cIAMRoleARN (\ s a -> s{_cIAMRoleARN = a})
cClusterARN :: Lens' Cluster (Maybe Text)
cClusterARN = lens _cClusterARN (\ s a -> s{_cClusterARN = a})
cActiveNodes :: Lens' Cluster (Maybe Int)
cActiveNodes = lens _cActiveNodes (\ s a -> s{_cActiveNodes = a})
cSecurityGroups :: Lens' Cluster [SecurityGroupMembership]
cSecurityGroups = lens _cSecurityGroups (\ s a -> s{_cSecurityGroups = a}) . _Default . _Coerce
cNotificationConfiguration :: Lens' Cluster (Maybe NotificationConfiguration)
cNotificationConfiguration = lens _cNotificationConfiguration (\ s a -> s{_cNotificationConfiguration = a})
cNodeIdsToRemove :: Lens' Cluster [Text]
cNodeIdsToRemove = lens _cNodeIdsToRemove (\ s a -> s{_cNodeIdsToRemove = a}) . _Default . _Coerce
cTotalNodes :: Lens' Cluster (Maybe Int)
cTotalNodes = lens _cTotalNodes (\ s a -> s{_cTotalNodes = a})
cPreferredMaintenanceWindow :: Lens' Cluster (Maybe Text)
cPreferredMaintenanceWindow = lens _cPreferredMaintenanceWindow (\ s a -> s{_cPreferredMaintenanceWindow = a})
cSubnetGroup :: Lens' Cluster (Maybe Text)
cSubnetGroup = lens _cSubnetGroup (\ s a -> s{_cSubnetGroup = a})
cClusterName :: Lens' Cluster (Maybe Text)
cClusterName = lens _cClusterName (\ s a -> s{_cClusterName = a})
cNodeType :: Lens' Cluster (Maybe Text)
cNodeType = lens _cNodeType (\ s a -> s{_cNodeType = a})
cNodes :: Lens' Cluster [Node]
cNodes = lens _cNodes (\ s a -> s{_cNodes = a}) . _Default . _Coerce
cClusterDiscoveryEndpoint :: Lens' Cluster (Maybe Endpoint)
cClusterDiscoveryEndpoint = lens _cClusterDiscoveryEndpoint (\ s a -> s{_cClusterDiscoveryEndpoint = a})
cDescription :: Lens' Cluster (Maybe Text)
cDescription = lens _cDescription (\ s a -> s{_cDescription = a})
cParameterGroup :: Lens' Cluster (Maybe ParameterGroupStatus)
cParameterGroup = lens _cParameterGroup (\ s a -> s{_cParameterGroup = a})
instance FromJSON Cluster where
        parseJSON
          = withObject "Cluster"
              (\ x ->
                 Cluster' <$>
                   (x .:? "Status") <*> (x .:? "IamRoleArn") <*>
                     (x .:? "ClusterArn")
                     <*> (x .:? "ActiveNodes")
                     <*> (x .:? "SecurityGroups" .!= mempty)
                     <*> (x .:? "NotificationConfiguration")
                     <*> (x .:? "NodeIdsToRemove" .!= mempty)
                     <*> (x .:? "TotalNodes")
                     <*> (x .:? "PreferredMaintenanceWindow")
                     <*> (x .:? "SubnetGroup")
                     <*> (x .:? "ClusterName")
                     <*> (x .:? "NodeType")
                     <*> (x .:? "Nodes" .!= mempty)
                     <*> (x .:? "ClusterDiscoveryEndpoint")
                     <*> (x .:? "Description")
                     <*> (x .:? "ParameterGroup"))
instance Hashable Cluster where
instance NFData Cluster where
data Endpoint = Endpoint'
  { _eAddress :: !(Maybe Text)
  , _ePort    :: !(Maybe Int)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
endpoint
    :: Endpoint
endpoint = Endpoint' {_eAddress = Nothing, _ePort = Nothing}
eAddress :: Lens' Endpoint (Maybe Text)
eAddress = lens _eAddress (\ s a -> s{_eAddress = a})
ePort :: Lens' Endpoint (Maybe Int)
ePort = lens _ePort (\ s a -> s{_ePort = a})
instance FromJSON Endpoint where
        parseJSON
          = withObject "Endpoint"
              (\ x ->
                 Endpoint' <$> (x .:? "Address") <*> (x .:? "Port"))
instance Hashable Endpoint where
instance NFData Endpoint where
data Event = Event'
  { _eSourceName :: !(Maybe Text)
  , _eSourceType :: !(Maybe SourceType)
  , _eDate       :: !(Maybe POSIX)
  , _eMessage    :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
event
    :: Event
event =
  Event'
    { _eSourceName = Nothing
    , _eSourceType = Nothing
    , _eDate = Nothing
    , _eMessage = Nothing
    }
eSourceName :: Lens' Event (Maybe Text)
eSourceName = lens _eSourceName (\ s a -> s{_eSourceName = a})
eSourceType :: Lens' Event (Maybe SourceType)
eSourceType = lens _eSourceType (\ s a -> s{_eSourceType = a})
eDate :: Lens' Event (Maybe UTCTime)
eDate = lens _eDate (\ s a -> s{_eDate = a}) . mapping _Time
eMessage :: Lens' Event (Maybe Text)
eMessage = lens _eMessage (\ s a -> s{_eMessage = a})
instance FromJSON Event where
        parseJSON
          = withObject "Event"
              (\ x ->
                 Event' <$>
                   (x .:? "SourceName") <*> (x .:? "SourceType") <*>
                     (x .:? "Date")
                     <*> (x .:? "Message"))
instance Hashable Event where
instance NFData Event where
data Node = Node'
  { _nNodeStatus           :: !(Maybe Text)
  , _nParameterGroupStatus :: !(Maybe Text)
  , _nAvailabilityZone     :: !(Maybe Text)
  , _nNodeId               :: !(Maybe Text)
  , _nEndpoint             :: !(Maybe Endpoint)
  , _nNodeCreateTime       :: !(Maybe POSIX)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
node
    :: Node
node =
  Node'
    { _nNodeStatus = Nothing
    , _nParameterGroupStatus = Nothing
    , _nAvailabilityZone = Nothing
    , _nNodeId = Nothing
    , _nEndpoint = Nothing
    , _nNodeCreateTime = Nothing
    }
nNodeStatus :: Lens' Node (Maybe Text)
nNodeStatus = lens _nNodeStatus (\ s a -> s{_nNodeStatus = a})
nParameterGroupStatus :: Lens' Node (Maybe Text)
nParameterGroupStatus = lens _nParameterGroupStatus (\ s a -> s{_nParameterGroupStatus = a})
nAvailabilityZone :: Lens' Node (Maybe Text)
nAvailabilityZone = lens _nAvailabilityZone (\ s a -> s{_nAvailabilityZone = a})
nNodeId :: Lens' Node (Maybe Text)
nNodeId = lens _nNodeId (\ s a -> s{_nNodeId = a})
nEndpoint :: Lens' Node (Maybe Endpoint)
nEndpoint = lens _nEndpoint (\ s a -> s{_nEndpoint = a})
nNodeCreateTime :: Lens' Node (Maybe UTCTime)
nNodeCreateTime = lens _nNodeCreateTime (\ s a -> s{_nNodeCreateTime = a}) . mapping _Time
instance FromJSON Node where
        parseJSON
          = withObject "Node"
              (\ x ->
                 Node' <$>
                   (x .:? "NodeStatus") <*>
                     (x .:? "ParameterGroupStatus")
                     <*> (x .:? "AvailabilityZone")
                     <*> (x .:? "NodeId")
                     <*> (x .:? "Endpoint")
                     <*> (x .:? "NodeCreateTime"))
instance Hashable Node where
instance NFData Node where
data NodeTypeSpecificValue = NodeTypeSpecificValue'
  { _ntsvValue    :: !(Maybe Text)
  , _ntsvNodeType :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
nodeTypeSpecificValue
    :: NodeTypeSpecificValue
nodeTypeSpecificValue =
  NodeTypeSpecificValue' {_ntsvValue = Nothing, _ntsvNodeType = Nothing}
ntsvValue :: Lens' NodeTypeSpecificValue (Maybe Text)
ntsvValue = lens _ntsvValue (\ s a -> s{_ntsvValue = a})
ntsvNodeType :: Lens' NodeTypeSpecificValue (Maybe Text)
ntsvNodeType = lens _ntsvNodeType (\ s a -> s{_ntsvNodeType = a})
instance FromJSON NodeTypeSpecificValue where
        parseJSON
          = withObject "NodeTypeSpecificValue"
              (\ x ->
                 NodeTypeSpecificValue' <$>
                   (x .:? "Value") <*> (x .:? "NodeType"))
instance Hashable NodeTypeSpecificValue where
instance NFData NodeTypeSpecificValue where
data NotificationConfiguration = NotificationConfiguration'
  { _ncTopicStatus :: !(Maybe Text)
  , _ncTopicARN    :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
notificationConfiguration
    :: NotificationConfiguration
notificationConfiguration =
  NotificationConfiguration' {_ncTopicStatus = Nothing, _ncTopicARN = Nothing}
ncTopicStatus :: Lens' NotificationConfiguration (Maybe Text)
ncTopicStatus = lens _ncTopicStatus (\ s a -> s{_ncTopicStatus = a})
ncTopicARN :: Lens' NotificationConfiguration (Maybe Text)
ncTopicARN = lens _ncTopicARN (\ s a -> s{_ncTopicARN = a})
instance FromJSON NotificationConfiguration where
        parseJSON
          = withObject "NotificationConfiguration"
              (\ x ->
                 NotificationConfiguration' <$>
                   (x .:? "TopicStatus") <*> (x .:? "TopicArn"))
instance Hashable NotificationConfiguration where
instance NFData NotificationConfiguration where
data Parameter = Parameter'
  { _pParameterValue         :: !(Maybe Text)
  , _pParameterType          :: !(Maybe ParameterType)
  , _pSource                 :: !(Maybe Text)
  , _pIsModifiable           :: !(Maybe IsModifiable)
  , _pDataType               :: !(Maybe Text)
  , _pNodeTypeSpecificValues :: !(Maybe [NodeTypeSpecificValue])
  , _pAllowedValues          :: !(Maybe Text)
  , _pParameterName          :: !(Maybe Text)
  , _pDescription            :: !(Maybe Text)
  , _pChangeType             :: !(Maybe ChangeType)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
parameter
    :: Parameter
parameter =
  Parameter'
    { _pParameterValue = Nothing
    , _pParameterType = Nothing
    , _pSource = Nothing
    , _pIsModifiable = Nothing
    , _pDataType = Nothing
    , _pNodeTypeSpecificValues = Nothing
    , _pAllowedValues = Nothing
    , _pParameterName = Nothing
    , _pDescription = Nothing
    , _pChangeType = Nothing
    }
pParameterValue :: Lens' Parameter (Maybe Text)
pParameterValue = lens _pParameterValue (\ s a -> s{_pParameterValue = a})
pParameterType :: Lens' Parameter (Maybe ParameterType)
pParameterType = lens _pParameterType (\ s a -> s{_pParameterType = a})
pSource :: Lens' Parameter (Maybe Text)
pSource = lens _pSource (\ s a -> s{_pSource = a})
pIsModifiable :: Lens' Parameter (Maybe IsModifiable)
pIsModifiable = lens _pIsModifiable (\ s a -> s{_pIsModifiable = a})
pDataType :: Lens' Parameter (Maybe Text)
pDataType = lens _pDataType (\ s a -> s{_pDataType = a})
pNodeTypeSpecificValues :: Lens' Parameter [NodeTypeSpecificValue]
pNodeTypeSpecificValues = lens _pNodeTypeSpecificValues (\ s a -> s{_pNodeTypeSpecificValues = a}) . _Default . _Coerce
pAllowedValues :: Lens' Parameter (Maybe Text)
pAllowedValues = lens _pAllowedValues (\ s a -> s{_pAllowedValues = a})
pParameterName :: Lens' Parameter (Maybe Text)
pParameterName = lens _pParameterName (\ s a -> s{_pParameterName = a})
pDescription :: Lens' Parameter (Maybe Text)
pDescription = lens _pDescription (\ s a -> s{_pDescription = a})
pChangeType :: Lens' Parameter (Maybe ChangeType)
pChangeType = lens _pChangeType (\ s a -> s{_pChangeType = a})
instance FromJSON Parameter where
        parseJSON
          = withObject "Parameter"
              (\ x ->
                 Parameter' <$>
                   (x .:? "ParameterValue") <*> (x .:? "ParameterType")
                     <*> (x .:? "Source")
                     <*> (x .:? "IsModifiable")
                     <*> (x .:? "DataType")
                     <*> (x .:? "NodeTypeSpecificValues" .!= mempty)
                     <*> (x .:? "AllowedValues")
                     <*> (x .:? "ParameterName")
                     <*> (x .:? "Description")
                     <*> (x .:? "ChangeType"))
instance Hashable Parameter where
instance NFData Parameter where
data ParameterGroup = ParameterGroup'
  { _pgDescription        :: !(Maybe Text)
  , _pgParameterGroupName :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
parameterGroup
    :: ParameterGroup
parameterGroup =
  ParameterGroup' {_pgDescription = Nothing, _pgParameterGroupName = Nothing}
pgDescription :: Lens' ParameterGroup (Maybe Text)
pgDescription = lens _pgDescription (\ s a -> s{_pgDescription = a})
pgParameterGroupName :: Lens' ParameterGroup (Maybe Text)
pgParameterGroupName = lens _pgParameterGroupName (\ s a -> s{_pgParameterGroupName = a})
instance FromJSON ParameterGroup where
        parseJSON
          = withObject "ParameterGroup"
              (\ x ->
                 ParameterGroup' <$>
                   (x .:? "Description") <*>
                     (x .:? "ParameterGroupName"))
instance Hashable ParameterGroup where
instance NFData ParameterGroup where
data ParameterGroupStatus = ParameterGroupStatus'
  { _pgsNodeIdsToReboot      :: !(Maybe [Text])
  , _pgsParameterApplyStatus :: !(Maybe Text)
  , _pgsParameterGroupName   :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
parameterGroupStatus
    :: ParameterGroupStatus
parameterGroupStatus =
  ParameterGroupStatus'
    { _pgsNodeIdsToReboot = Nothing
    , _pgsParameterApplyStatus = Nothing
    , _pgsParameterGroupName = Nothing
    }
pgsNodeIdsToReboot :: Lens' ParameterGroupStatus [Text]
pgsNodeIdsToReboot = lens _pgsNodeIdsToReboot (\ s a -> s{_pgsNodeIdsToReboot = a}) . _Default . _Coerce
pgsParameterApplyStatus :: Lens' ParameterGroupStatus (Maybe Text)
pgsParameterApplyStatus = lens _pgsParameterApplyStatus (\ s a -> s{_pgsParameterApplyStatus = a})
pgsParameterGroupName :: Lens' ParameterGroupStatus (Maybe Text)
pgsParameterGroupName = lens _pgsParameterGroupName (\ s a -> s{_pgsParameterGroupName = a})
instance FromJSON ParameterGroupStatus where
        parseJSON
          = withObject "ParameterGroupStatus"
              (\ x ->
                 ParameterGroupStatus' <$>
                   (x .:? "NodeIdsToReboot" .!= mempty) <*>
                     (x .:? "ParameterApplyStatus")
                     <*> (x .:? "ParameterGroupName"))
instance Hashable ParameterGroupStatus where
instance NFData ParameterGroupStatus where
data ParameterNameValue = ParameterNameValue'
  { _pnvParameterValue :: !(Maybe Text)
  , _pnvParameterName  :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
parameterNameValue
    :: ParameterNameValue
parameterNameValue =
  ParameterNameValue'
    {_pnvParameterValue = Nothing, _pnvParameterName = Nothing}
pnvParameterValue :: Lens' ParameterNameValue (Maybe Text)
pnvParameterValue = lens _pnvParameterValue (\ s a -> s{_pnvParameterValue = a})
pnvParameterName :: Lens' ParameterNameValue (Maybe Text)
pnvParameterName = lens _pnvParameterName (\ s a -> s{_pnvParameterName = a})
instance Hashable ParameterNameValue where
instance NFData ParameterNameValue where
instance ToJSON ParameterNameValue where
        toJSON ParameterNameValue'{..}
          = object
              (catMaybes
                 [("ParameterValue" .=) <$> _pnvParameterValue,
                  ("ParameterName" .=) <$> _pnvParameterName])
data SecurityGroupMembership = SecurityGroupMembership'
  { _sgmStatus                  :: !(Maybe Text)
  , _sgmSecurityGroupIdentifier :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
securityGroupMembership
    :: SecurityGroupMembership
securityGroupMembership =
  SecurityGroupMembership'
    {_sgmStatus = Nothing, _sgmSecurityGroupIdentifier = Nothing}
sgmStatus :: Lens' SecurityGroupMembership (Maybe Text)
sgmStatus = lens _sgmStatus (\ s a -> s{_sgmStatus = a})
sgmSecurityGroupIdentifier :: Lens' SecurityGroupMembership (Maybe Text)
sgmSecurityGroupIdentifier = lens _sgmSecurityGroupIdentifier (\ s a -> s{_sgmSecurityGroupIdentifier = a})
instance FromJSON SecurityGroupMembership where
        parseJSON
          = withObject "SecurityGroupMembership"
              (\ x ->
                 SecurityGroupMembership' <$>
                   (x .:? "Status") <*>
                     (x .:? "SecurityGroupIdentifier"))
instance Hashable SecurityGroupMembership where
instance NFData SecurityGroupMembership where
data Subnet = Subnet'
  { _sSubnetIdentifier       :: !(Maybe Text)
  , _sSubnetAvailabilityZone :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
subnet
    :: Subnet
subnet =
  Subnet' {_sSubnetIdentifier = Nothing, _sSubnetAvailabilityZone = Nothing}
sSubnetIdentifier :: Lens' Subnet (Maybe Text)
sSubnetIdentifier = lens _sSubnetIdentifier (\ s a -> s{_sSubnetIdentifier = a})
sSubnetAvailabilityZone :: Lens' Subnet (Maybe Text)
sSubnetAvailabilityZone = lens _sSubnetAvailabilityZone (\ s a -> s{_sSubnetAvailabilityZone = a})
instance FromJSON Subnet where
        parseJSON
          = withObject "Subnet"
              (\ x ->
                 Subnet' <$>
                   (x .:? "SubnetIdentifier") <*>
                     (x .:? "SubnetAvailabilityZone"))
instance Hashable Subnet where
instance NFData Subnet where
data SubnetGroup = SubnetGroup'
  { _sgVPCId           :: !(Maybe Text)
  , _sgSubnets         :: !(Maybe [Subnet])
  , _sgSubnetGroupName :: !(Maybe Text)
  , _sgDescription     :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
subnetGroup
    :: SubnetGroup
subnetGroup =
  SubnetGroup'
    { _sgVPCId = Nothing
    , _sgSubnets = Nothing
    , _sgSubnetGroupName = Nothing
    , _sgDescription = Nothing
    }
sgVPCId :: Lens' SubnetGroup (Maybe Text)
sgVPCId = lens _sgVPCId (\ s a -> s{_sgVPCId = a})
sgSubnets :: Lens' SubnetGroup [Subnet]
sgSubnets = lens _sgSubnets (\ s a -> s{_sgSubnets = a}) . _Default . _Coerce
sgSubnetGroupName :: Lens' SubnetGroup (Maybe Text)
sgSubnetGroupName = lens _sgSubnetGroupName (\ s a -> s{_sgSubnetGroupName = a})
sgDescription :: Lens' SubnetGroup (Maybe Text)
sgDescription = lens _sgDescription (\ s a -> s{_sgDescription = a})
instance FromJSON SubnetGroup where
        parseJSON
          = withObject "SubnetGroup"
              (\ x ->
                 SubnetGroup' <$>
                   (x .:? "VpcId") <*> (x .:? "Subnets" .!= mempty) <*>
                     (x .:? "SubnetGroupName")
                     <*> (x .:? "Description"))
instance Hashable SubnetGroup where
instance NFData SubnetGroup where
data Tag = Tag'
  { _tagValue :: !(Maybe Text)
  , _tagKey   :: !(Maybe Text)
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
tag
    :: Tag
tag = Tag' {_tagValue = Nothing, _tagKey = Nothing}
tagValue :: Lens' Tag (Maybe Text)
tagValue = lens _tagValue (\ s a -> s{_tagValue = a})
tagKey :: Lens' Tag (Maybe Text)
tagKey = lens _tagKey (\ s a -> s{_tagKey = a})
instance FromJSON Tag where
        parseJSON
          = withObject "Tag"
              (\ x -> Tag' <$> (x .:? "Value") <*> (x .:? "Key"))
instance Hashable Tag where
instance NFData Tag where
instance ToJSON Tag where
        toJSON Tag'{..}
          = object
              (catMaybes
                 [("Value" .=) <$> _tagValue, ("Key" .=) <$> _tagKey])