module Network.AWS.SDB.Types.Product where
import           Network.AWS.Prelude
import           Network.AWS.SDB.Types.Sum
data Attribute = Attribute'
    { _aAlternateValueEncoding :: !(Maybe Text)
    , _aAlternateNameEncoding  :: !(Maybe Text)
    , _aName                   :: !Text
    , _aValue                  :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
attribute
    :: Text 
    -> Text 
    -> Attribute
attribute pName_ pValue_ =
    Attribute'
    { _aAlternateValueEncoding = Nothing
    , _aAlternateNameEncoding = Nothing
    , _aName = pName_
    , _aValue = pValue_
    }
aAlternateValueEncoding :: Lens' Attribute (Maybe Text)
aAlternateValueEncoding = lens _aAlternateValueEncoding (\ s a -> s{_aAlternateValueEncoding = a});
aAlternateNameEncoding :: Lens' Attribute (Maybe Text)
aAlternateNameEncoding = lens _aAlternateNameEncoding (\ s a -> s{_aAlternateNameEncoding = a});
aName :: Lens' Attribute Text
aName = lens _aName (\ s a -> s{_aName = a});
aValue :: Lens' Attribute Text
aValue = lens _aValue (\ s a -> s{_aValue = a});
instance FromXML Attribute where
        parseXML x
          = Attribute' <$>
              (x .@? "AlternateValueEncoding") <*>
                (x .@? "AlternateNameEncoding")
                <*> (x .@ "Name")
                <*> (x .@ "Value")
instance ToQuery Attribute where
        toQuery Attribute'{..}
          = mconcat
              ["AlternateValueEncoding" =:
                 _aAlternateValueEncoding,
               "AlternateNameEncoding" =: _aAlternateNameEncoding,
               "Name" =: _aName, "Value" =: _aValue]
data DeletableItem = DeletableItem'
    { _diAttributes :: !(Maybe [Attribute])
    , _diName       :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
deletableItem
    :: Text 
    -> DeletableItem
deletableItem pName_ =
    DeletableItem'
    { _diAttributes = Nothing
    , _diName = pName_
    }
diAttributes :: Lens' DeletableItem [Attribute]
diAttributes = lens _diAttributes (\ s a -> s{_diAttributes = a}) . _Default . _Coerce;
diName :: Lens' DeletableItem Text
diName = lens _diName (\ s a -> s{_diName = a});
instance ToQuery DeletableItem where
        toQuery DeletableItem'{..}
          = mconcat
              [toQuery (toQueryList "Attribute" <$> _diAttributes),
               "ItemName" =: _diName]
data Item = Item'
    { _iAlternateNameEncoding :: !(Maybe Text)
    , _iName                  :: !Text
    , _iAttributes            :: ![Attribute]
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
item
    :: Text 
    -> Item
item pName_ =
    Item'
    { _iAlternateNameEncoding = Nothing
    , _iName = pName_
    , _iAttributes = mempty
    }
iAlternateNameEncoding :: Lens' Item (Maybe Text)
iAlternateNameEncoding = lens _iAlternateNameEncoding (\ s a -> s{_iAlternateNameEncoding = a});
iName :: Lens' Item Text
iName = lens _iName (\ s a -> s{_iName = a});
iAttributes :: Lens' Item [Attribute]
iAttributes = lens _iAttributes (\ s a -> s{_iAttributes = a}) . _Coerce;
instance FromXML Item where
        parseXML x
          = Item' <$>
              (x .@? "AlternateNameEncoding") <*> (x .@ "Name") <*>
                (parseXMLList "Attribute" x)
data ReplaceableAttribute = ReplaceableAttribute'
    { _raReplace :: !(Maybe Bool)
    , _raName    :: !Text
    , _raValue   :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
replaceableAttribute
    :: Text 
    -> Text 
    -> ReplaceableAttribute
replaceableAttribute pName_ pValue_ =
    ReplaceableAttribute'
    { _raReplace = Nothing
    , _raName = pName_
    , _raValue = pValue_
    }
raReplace :: Lens' ReplaceableAttribute (Maybe Bool)
raReplace = lens _raReplace (\ s a -> s{_raReplace = a});
raName :: Lens' ReplaceableAttribute Text
raName = lens _raName (\ s a -> s{_raName = a});
raValue :: Lens' ReplaceableAttribute Text
raValue = lens _raValue (\ s a -> s{_raValue = a});
instance ToQuery ReplaceableAttribute where
        toQuery ReplaceableAttribute'{..}
          = mconcat
              ["Replace" =: _raReplace, "Name" =: _raName,
               "Value" =: _raValue]
data ReplaceableItem = ReplaceableItem'
    { _riName       :: !Text
    , _riAttributes :: ![ReplaceableAttribute]
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
replaceableItem
    :: Text 
    -> ReplaceableItem
replaceableItem pName_ =
    ReplaceableItem'
    { _riName = pName_
    , _riAttributes = mempty
    }
riName :: Lens' ReplaceableItem Text
riName = lens _riName (\ s a -> s{_riName = a});
riAttributes :: Lens' ReplaceableItem [ReplaceableAttribute]
riAttributes = lens _riAttributes (\ s a -> s{_riAttributes = a}) . _Coerce;
instance ToQuery ReplaceableItem where
        toQuery ReplaceableItem'{..}
          = mconcat
              ["ItemName" =: _riName,
               toQueryList "Attribute" _riAttributes]
data UpdateCondition = UpdateCondition'
    { _ucExists :: !(Maybe Bool)
    , _ucValue  :: !(Maybe Text)
    , _ucName   :: !(Maybe Text)
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
updateCondition
    :: UpdateCondition
updateCondition =
    UpdateCondition'
    { _ucExists = Nothing
    , _ucValue = Nothing
    , _ucName = Nothing
    }
ucExists :: Lens' UpdateCondition (Maybe Bool)
ucExists = lens _ucExists (\ s a -> s{_ucExists = a});
ucValue :: Lens' UpdateCondition (Maybe Text)
ucValue = lens _ucValue (\ s a -> s{_ucValue = a});
ucName :: Lens' UpdateCondition (Maybe Text)
ucName = lens _ucName (\ s a -> s{_ucName = a});
instance ToQuery UpdateCondition where
        toQuery UpdateCondition'{..}
          = mconcat
              ["Exists" =: _ucExists, "Value" =: _ucValue,
               "Name" =: _ucName]