module Network.AWS.Redshift.AuthorizeSnapshotAccess
    (
    
      AuthorizeSnapshotAccess
    
    , authorizeSnapshotAccess
    
    , asaAccountWithRestoreAccess
    , asaSnapshotClusterIdentifier
    , asaSnapshotIdentifier
    
    , AuthorizeSnapshotAccessResponse
    
    , authorizeSnapshotAccessResponse
    
    , asarSnapshot
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.Query
import Network.AWS.Redshift.Types
import qualified GHC.Exts
data AuthorizeSnapshotAccess = AuthorizeSnapshotAccess
    { _asaAccountWithRestoreAccess  :: Text
    , _asaSnapshotClusterIdentifier :: Maybe Text
    , _asaSnapshotIdentifier        :: Text
    } deriving (Eq, Ord, Show)
authorizeSnapshotAccess :: Text 
                        -> Text 
                        -> AuthorizeSnapshotAccess
authorizeSnapshotAccess p1 p2 = AuthorizeSnapshotAccess
    { _asaSnapshotIdentifier        = p1
    , _asaAccountWithRestoreAccess  = p2
    , _asaSnapshotClusterIdentifier = Nothing
    }
asaAccountWithRestoreAccess :: Lens' AuthorizeSnapshotAccess Text
asaAccountWithRestoreAccess =
    lens _asaAccountWithRestoreAccess
        (\s a -> s { _asaAccountWithRestoreAccess = a })
asaSnapshotClusterIdentifier :: Lens' AuthorizeSnapshotAccess (Maybe Text)
asaSnapshotClusterIdentifier =
    lens _asaSnapshotClusterIdentifier
        (\s a -> s { _asaSnapshotClusterIdentifier = a })
asaSnapshotIdentifier :: Lens' AuthorizeSnapshotAccess Text
asaSnapshotIdentifier =
    lens _asaSnapshotIdentifier (\s a -> s { _asaSnapshotIdentifier = a })
newtype AuthorizeSnapshotAccessResponse = AuthorizeSnapshotAccessResponse
    { _asarSnapshot :: Maybe Snapshot
    } deriving (Eq, Show)
authorizeSnapshotAccessResponse :: AuthorizeSnapshotAccessResponse
authorizeSnapshotAccessResponse = AuthorizeSnapshotAccessResponse
    { _asarSnapshot = Nothing
    }
asarSnapshot :: Lens' AuthorizeSnapshotAccessResponse (Maybe Snapshot)
asarSnapshot = lens _asarSnapshot (\s a -> s { _asarSnapshot = a })
instance ToPath AuthorizeSnapshotAccess where
    toPath = const "/"
instance ToQuery AuthorizeSnapshotAccess where
    toQuery AuthorizeSnapshotAccess{..} = mconcat
        [ "AccountWithRestoreAccess"  =? _asaAccountWithRestoreAccess
        , "SnapshotClusterIdentifier" =? _asaSnapshotClusterIdentifier
        , "SnapshotIdentifier"        =? _asaSnapshotIdentifier
        ]
instance ToHeaders AuthorizeSnapshotAccess
instance AWSRequest AuthorizeSnapshotAccess where
    type Sv AuthorizeSnapshotAccess = Redshift
    type Rs AuthorizeSnapshotAccess = AuthorizeSnapshotAccessResponse
    request  = post "AuthorizeSnapshotAccess"
    response = xmlResponse
instance FromXML AuthorizeSnapshotAccessResponse where
    parseXML = withElement "AuthorizeSnapshotAccessResult" $ \x -> AuthorizeSnapshotAccessResponse
        <$> x .@? "Snapshot"