module Network.AWS.SDB.Types
    (
    
      SDB
    
    , RESTError
    
    , ns
    
    , Attribute
    , attribute
    , aAlternateNameEncoding
    , aAlternateValueEncoding
    , aName
    , aValue
    
    , DeletableItem
    , deletableItem
    , diAttributes
    , diName
    
    , ReplaceableItem
    , replaceableItem
    , riAttributes
    , riName
    
    , UpdateCondition
    , updateCondition
    , ucExists
    , ucName
    , ucValue
    
    , ReplaceableAttribute
    , replaceableAttribute
    , raName
    , raReplace
    , raValue
    
    , Item
    , item
    , iAlternateNameEncoding
    , iAttributes
    , iName
    ) where
import Network.AWS.Prelude
import Network.AWS.Signing
import qualified GHC.Exts
data SDB
instance AWSService SDB where
    type Sg SDB = V2
    type Er SDB = RESTError
    service = service'
      where
        service' :: Service SDB
        service' = Service
            { _svcAbbrev       = "SDB"
            , _svcPrefix       = "sdb"
            , _svcVersion      = "2009-04-15"
            , _svcTargetPrefix = Nothing
            , _svcJSONVersion  = Nothing
            , _svcHandle       = handle
            , _svcRetry        = retry
            }
        handle :: Status
               -> Maybe (LazyByteString -> ServiceError RESTError)
        handle = restError statusSuccess service'
        retry :: Retry SDB
        retry = Exponential
            { _retryBase     = 0.05
            , _retryGrowth   = 2
            , _retryAttempts = 5
            , _retryCheck    = check
            }
        check :: Status
              -> RESTError
              -> Bool
        check (statusCode -> s) (awsErrorCode -> e)
            | s == 500  = True 
            | s == 509  = True 
            | s == 503  = True 
            | otherwise = False
ns :: Text
ns = "http://sdb.amazonaws.com/doc/2009-04-15/"
data Attribute = Attribute
    { _aAlternateNameEncoding  :: Maybe Text
    , _aAlternateValueEncoding :: Maybe Text
    , _aName                   :: Text
    , _aValue                  :: Text
    } deriving (Eq, Ord, Read, Show)
attribute :: Text 
          -> Text 
          -> Attribute
attribute p1 p2 = Attribute
    { _aName                   = p1
    , _aValue                  = p2
    , _aAlternateNameEncoding  = Nothing
    , _aAlternateValueEncoding = Nothing
    }
aAlternateNameEncoding :: Lens' Attribute (Maybe Text)
aAlternateNameEncoding =
    lens _aAlternateNameEncoding (\s a -> s { _aAlternateNameEncoding = a })
aAlternateValueEncoding :: Lens' Attribute (Maybe Text)
aAlternateValueEncoding =
    lens _aAlternateValueEncoding (\s a -> s { _aAlternateValueEncoding = 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 .@? "AlternateNameEncoding"
        <*> x .@? "AlternateValueEncoding"
        <*> x .@  "Name"
        <*> x .@  "Value"
instance ToQuery Attribute where
    toQuery Attribute{..} = mconcat
        [ "AlternateNameEncoding"  =? _aAlternateNameEncoding
        , "AlternateValueEncoding" =? _aAlternateValueEncoding
        , "Name"                   =? _aName
        , "Value"                  =? _aValue
        ]
data DeletableItem = DeletableItem
    { _diAttributes :: List "member" Attribute
    , _diName       :: Text
    } deriving (Eq, Read, Show)
deletableItem :: Text 
              -> DeletableItem
deletableItem p1 = DeletableItem
    { _diName       = p1
    , _diAttributes = mempty
    }
diAttributes :: Lens' DeletableItem [Attribute]
diAttributes = lens _diAttributes (\s a -> s { _diAttributes = a }) . _List
diName :: Lens' DeletableItem Text
diName = lens _diName (\s a -> s { _diName = a })
instance FromXML DeletableItem where
    parseXML x = DeletableItem
        <$> parseXML x
        <*> x .@  "ItemName"
instance ToQuery DeletableItem where
    toQuery DeletableItem{..} = mconcat
        [ toQuery     _diAttributes
        , "ItemName"   =? _diName
        ]
data ReplaceableItem = ReplaceableItem
    { _riAttributes :: List "member" ReplaceableAttribute
    , _riName       :: Text
    } deriving (Eq, Read, Show)
replaceableItem :: Text 
                -> ReplaceableItem
replaceableItem p1 = ReplaceableItem
    { _riName       = p1
    , _riAttributes = mempty
    }
riAttributes :: Lens' ReplaceableItem [ReplaceableAttribute]
riAttributes = lens _riAttributes (\s a -> s { _riAttributes = a }) . _List
riName :: Lens' ReplaceableItem Text
riName = lens _riName (\s a -> s { _riName = a })
instance FromXML ReplaceableItem where
    parseXML x = ReplaceableItem
        <$> parseXML x
        <*> x .@  "ItemName"
instance ToQuery ReplaceableItem where
    toQuery ReplaceableItem{..} = mconcat
        [ toQuery     _riAttributes
        , "ItemName"   =? _riName
        ]
data UpdateCondition = UpdateCondition
    { _ucExists :: Maybe Bool
    , _ucName   :: Maybe Text
    , _ucValue  :: Maybe Text
    } deriving (Eq, Ord, Read, Show)
updateCondition :: UpdateCondition
updateCondition = UpdateCondition
    { _ucName   = Nothing
    , _ucValue  = Nothing
    , _ucExists = Nothing
    }
ucExists :: Lens' UpdateCondition (Maybe Bool)
ucExists = lens _ucExists (\s a -> s { _ucExists = a })
ucName :: Lens' UpdateCondition (Maybe Text)
ucName = lens _ucName (\s a -> s { _ucName = a })
ucValue :: Lens' UpdateCondition (Maybe Text)
ucValue = lens _ucValue (\s a -> s { _ucValue = a })
instance FromXML UpdateCondition where
    parseXML x = UpdateCondition
        <$> x .@? "Exists"
        <*> x .@? "Name"
        <*> x .@? "Value"
instance ToQuery UpdateCondition where
    toQuery UpdateCondition{..} = mconcat
        [ "Exists" =? _ucExists
        , "Name"   =? _ucName
        , "Value"  =? _ucValue
        ]
data ReplaceableAttribute = ReplaceableAttribute
    { _raName    :: Text
    , _raReplace :: Maybe Bool
    , _raValue   :: Text
    } deriving (Eq, Ord, Read, Show)
replaceableAttribute :: Text 
                     -> Text 
                     -> ReplaceableAttribute
replaceableAttribute p1 p2 = ReplaceableAttribute
    { _raName    = p1
    , _raValue   = p2
    , _raReplace = Nothing
    }
raName :: Lens' ReplaceableAttribute Text
raName = lens _raName (\s a -> s { _raName = a })
raReplace :: Lens' ReplaceableAttribute (Maybe Bool)
raReplace = lens _raReplace (\s a -> s { _raReplace = a })
raValue :: Lens' ReplaceableAttribute Text
raValue = lens _raValue (\s a -> s { _raValue = a })
instance FromXML ReplaceableAttribute where
    parseXML x = ReplaceableAttribute
        <$> x .@  "Name"
        <*> x .@? "Replace"
        <*> x .@  "Value"
instance ToQuery ReplaceableAttribute where
    toQuery ReplaceableAttribute{..} = mconcat
        [ "Name"    =? _raName
        , "Replace" =? _raReplace
        , "Value"   =? _raValue
        ]
data Item = Item
    { _iAlternateNameEncoding :: Maybe Text
    , _iAttributes            :: List "member" Attribute
    , _iName                  :: Text
    } deriving (Eq, Read, Show)
item :: Text 
     -> Item
item p1 = Item
    { _iName                  = p1
    , _iAlternateNameEncoding = Nothing
    , _iAttributes            = mempty
    }
iAlternateNameEncoding :: Lens' Item (Maybe Text)
iAlternateNameEncoding =
    lens _iAlternateNameEncoding (\s a -> s { _iAlternateNameEncoding = a })
iAttributes :: Lens' Item [Attribute]
iAttributes = lens _iAttributes (\s a -> s { _iAttributes = a }) . _List
iName :: Lens' Item Text
iName = lens _iName (\s a -> s { _iName = a })
instance FromXML Item where
    parseXML x = Item
        <$> x .@? "AlternateNameEncoding"
        <*> parseXML x
        <*> x .@  "Name"
instance ToQuery Item where
    toQuery Item{..} = mconcat
        [ "AlternateNameEncoding" =? _iAlternateNameEncoding
        , toQuery                _iAttributes
        , "Name"                  =? _iName
        ]