module Network.AWS.KMS.Types.Product where
import           Network.AWS.KMS.Types.Sum
import           Network.AWS.Prelude
data AliasListEntry = AliasListEntry'
    { _aleTargetKeyId :: !(Maybe Text)
    , _aleAliasName   :: !(Maybe Text)
    , _aleAliasARN    :: !(Maybe Text)
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
aliasListEntry
    :: AliasListEntry
aliasListEntry =
    AliasListEntry'
    { _aleTargetKeyId = Nothing
    , _aleAliasName = Nothing
    , _aleAliasARN = Nothing
    }
aleTargetKeyId :: Lens' AliasListEntry (Maybe Text)
aleTargetKeyId = lens _aleTargetKeyId (\ s a -> s{_aleTargetKeyId = a});
aleAliasName :: Lens' AliasListEntry (Maybe Text)
aleAliasName = lens _aleAliasName (\ s a -> s{_aleAliasName = a});
aleAliasARN :: Lens' AliasListEntry (Maybe Text)
aleAliasARN = lens _aleAliasARN (\ s a -> s{_aleAliasARN = a});
instance FromJSON AliasListEntry where
        parseJSON
          = withObject "AliasListEntry"
              (\ x ->
                 AliasListEntry' <$>
                   (x .:? "TargetKeyId") <*> (x .:? "AliasName") <*>
                     (x .:? "AliasArn"))
data GrantConstraints = GrantConstraints'
    { _gcEncryptionContextEquals :: !(Maybe (Map Text Text))
    , _gcEncryptionContextSubset :: !(Maybe (Map Text Text))
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
grantConstraints
    :: GrantConstraints
grantConstraints =
    GrantConstraints'
    { _gcEncryptionContextEquals = Nothing
    , _gcEncryptionContextSubset = Nothing
    }
gcEncryptionContextEquals :: Lens' GrantConstraints (HashMap Text Text)
gcEncryptionContextEquals = lens _gcEncryptionContextEquals (\ s a -> s{_gcEncryptionContextEquals = a}) . _Default . _Map;
gcEncryptionContextSubset :: Lens' GrantConstraints (HashMap Text Text)
gcEncryptionContextSubset = lens _gcEncryptionContextSubset (\ s a -> s{_gcEncryptionContextSubset = a}) . _Default . _Map;
instance FromJSON GrantConstraints where
        parseJSON
          = withObject "GrantConstraints"
              (\ x ->
                 GrantConstraints' <$>
                   (x .:? "EncryptionContextEquals" .!= mempty) <*>
                     (x .:? "EncryptionContextSubset" .!= mempty))
instance ToJSON GrantConstraints where
        toJSON GrantConstraints'{..}
          = object
              ["EncryptionContextEquals" .=
                 _gcEncryptionContextEquals,
               "EncryptionContextSubset" .=
                 _gcEncryptionContextSubset]
data GrantListEntry = GrantListEntry'
    { _gleRetiringPrincipal :: !(Maybe Text)
    , _gleIssuingAccount    :: !(Maybe Text)
    , _gleGrantId           :: !(Maybe Text)
    , _gleConstraints       :: !(Maybe GrantConstraints)
    , _gleGranteePrincipal  :: !(Maybe Text)
    , _gleOperations        :: !(Maybe [GrantOperation])
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
grantListEntry
    :: GrantListEntry
grantListEntry =
    GrantListEntry'
    { _gleRetiringPrincipal = Nothing
    , _gleIssuingAccount = Nothing
    , _gleGrantId = Nothing
    , _gleConstraints = Nothing
    , _gleGranteePrincipal = Nothing
    , _gleOperations = Nothing
    }
gleRetiringPrincipal :: Lens' GrantListEntry (Maybe Text)
gleRetiringPrincipal = lens _gleRetiringPrincipal (\ s a -> s{_gleRetiringPrincipal = a});
gleIssuingAccount :: Lens' GrantListEntry (Maybe Text)
gleIssuingAccount = lens _gleIssuingAccount (\ s a -> s{_gleIssuingAccount = a});
gleGrantId :: Lens' GrantListEntry (Maybe Text)
gleGrantId = lens _gleGrantId (\ s a -> s{_gleGrantId = a});
gleConstraints :: Lens' GrantListEntry (Maybe GrantConstraints)
gleConstraints = lens _gleConstraints (\ s a -> s{_gleConstraints = a});
gleGranteePrincipal :: Lens' GrantListEntry (Maybe Text)
gleGranteePrincipal = lens _gleGranteePrincipal (\ s a -> s{_gleGranteePrincipal = a});
gleOperations :: Lens' GrantListEntry [GrantOperation]
gleOperations = lens _gleOperations (\ s a -> s{_gleOperations = a}) . _Default . _Coerce;
instance FromJSON GrantListEntry where
        parseJSON
          = withObject "GrantListEntry"
              (\ x ->
                 GrantListEntry' <$>
                   (x .:? "RetiringPrincipal") <*>
                     (x .:? "IssuingAccount")
                     <*> (x .:? "GrantId")
                     <*> (x .:? "Constraints")
                     <*> (x .:? "GranteePrincipal")
                     <*> (x .:? "Operations" .!= mempty))
data KeyListEntry = KeyListEntry'
    { _kleKeyARN :: !(Maybe Text)
    , _kleKeyId  :: !(Maybe Text)
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
keyListEntry
    :: KeyListEntry
keyListEntry =
    KeyListEntry'
    { _kleKeyARN = Nothing
    , _kleKeyId = Nothing
    }
kleKeyARN :: Lens' KeyListEntry (Maybe Text)
kleKeyARN = lens _kleKeyARN (\ s a -> s{_kleKeyARN = a});
kleKeyId :: Lens' KeyListEntry (Maybe Text)
kleKeyId = lens _kleKeyId (\ s a -> s{_kleKeyId = a});
instance FromJSON KeyListEntry where
        parseJSON
          = withObject "KeyListEntry"
              (\ x ->
                 KeyListEntry' <$>
                   (x .:? "KeyArn") <*> (x .:? "KeyId"))
data KeyMetadata = KeyMetadata'
    { _kmARN          :: !(Maybe Text)
    , _kmEnabled      :: !(Maybe Bool)
    , _kmAWSAccountId :: !(Maybe Text)
    , _kmKeyUsage     :: !(Maybe KeyUsageType)
    , _kmCreationDate :: !(Maybe POSIX)
    , _kmDescription  :: !(Maybe Text)
    , _kmKeyId        :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
keyMetadata
    :: Text 
    -> KeyMetadata
keyMetadata pKeyId_ =
    KeyMetadata'
    { _kmARN = Nothing
    , _kmEnabled = Nothing
    , _kmAWSAccountId = Nothing
    , _kmKeyUsage = Nothing
    , _kmCreationDate = Nothing
    , _kmDescription = Nothing
    , _kmKeyId = pKeyId_
    }
kmARN :: Lens' KeyMetadata (Maybe Text)
kmARN = lens _kmARN (\ s a -> s{_kmARN = a});
kmEnabled :: Lens' KeyMetadata (Maybe Bool)
kmEnabled = lens _kmEnabled (\ s a -> s{_kmEnabled = a});
kmAWSAccountId :: Lens' KeyMetadata (Maybe Text)
kmAWSAccountId = lens _kmAWSAccountId (\ s a -> s{_kmAWSAccountId = a});
kmKeyUsage :: Lens' KeyMetadata (Maybe KeyUsageType)
kmKeyUsage = lens _kmKeyUsage (\ s a -> s{_kmKeyUsage = a});
kmCreationDate :: Lens' KeyMetadata (Maybe UTCTime)
kmCreationDate = lens _kmCreationDate (\ s a -> s{_kmCreationDate = a}) . mapping _Time;
kmDescription :: Lens' KeyMetadata (Maybe Text)
kmDescription = lens _kmDescription (\ s a -> s{_kmDescription = a});
kmKeyId :: Lens' KeyMetadata Text
kmKeyId = lens _kmKeyId (\ s a -> s{_kmKeyId = a});
instance FromJSON KeyMetadata where
        parseJSON
          = withObject "KeyMetadata"
              (\ x ->
                 KeyMetadata' <$>
                   (x .:? "Arn") <*> (x .:? "Enabled") <*>
                     (x .:? "AWSAccountId")
                     <*> (x .:? "KeyUsage")
                     <*> (x .:? "CreationDate")
                     <*> (x .:? "Description")
                     <*> (x .: "KeyId"))