{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.StorageGateway.RefreshCache
(
RefreshCache (..),
newRefreshCache,
refreshCache_folderList,
refreshCache_recursive,
refreshCache_fileShareARN,
RefreshCacheResponse (..),
newRefreshCacheResponse,
refreshCacheResponse_fileShareARN,
refreshCacheResponse_notificationId,
refreshCacheResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.StorageGateway.Types
data RefreshCache = RefreshCache'
{
RefreshCache -> Maybe (NonEmpty Text)
folderList :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
RefreshCache -> Maybe Bool
recursive :: Prelude.Maybe Prelude.Bool,
RefreshCache -> Text
fileShareARN :: Prelude.Text
}
deriving (RefreshCache -> RefreshCache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefreshCache -> RefreshCache -> Bool
$c/= :: RefreshCache -> RefreshCache -> Bool
== :: RefreshCache -> RefreshCache -> Bool
$c== :: RefreshCache -> RefreshCache -> Bool
Prelude.Eq, ReadPrec [RefreshCache]
ReadPrec RefreshCache
Int -> ReadS RefreshCache
ReadS [RefreshCache]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RefreshCache]
$creadListPrec :: ReadPrec [RefreshCache]
readPrec :: ReadPrec RefreshCache
$creadPrec :: ReadPrec RefreshCache
readList :: ReadS [RefreshCache]
$creadList :: ReadS [RefreshCache]
readsPrec :: Int -> ReadS RefreshCache
$creadsPrec :: Int -> ReadS RefreshCache
Prelude.Read, Int -> RefreshCache -> ShowS
[RefreshCache] -> ShowS
RefreshCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefreshCache] -> ShowS
$cshowList :: [RefreshCache] -> ShowS
show :: RefreshCache -> String
$cshow :: RefreshCache -> String
showsPrec :: Int -> RefreshCache -> ShowS
$cshowsPrec :: Int -> RefreshCache -> ShowS
Prelude.Show, forall x. Rep RefreshCache x -> RefreshCache
forall x. RefreshCache -> Rep RefreshCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RefreshCache x -> RefreshCache
$cfrom :: forall x. RefreshCache -> Rep RefreshCache x
Prelude.Generic)
newRefreshCache ::
Prelude.Text ->
RefreshCache
newRefreshCache :: Text -> RefreshCache
newRefreshCache Text
pFileShareARN_ =
RefreshCache'
{ $sel:folderList:RefreshCache' :: Maybe (NonEmpty Text)
folderList = forall a. Maybe a
Prelude.Nothing,
$sel:recursive:RefreshCache' :: Maybe Bool
recursive = forall a. Maybe a
Prelude.Nothing,
$sel:fileShareARN:RefreshCache' :: Text
fileShareARN = Text
pFileShareARN_
}
refreshCache_folderList :: Lens.Lens' RefreshCache (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
refreshCache_folderList :: Lens' RefreshCache (Maybe (NonEmpty Text))
refreshCache_folderList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCache' {Maybe (NonEmpty Text)
folderList :: Maybe (NonEmpty Text)
$sel:folderList:RefreshCache' :: RefreshCache -> Maybe (NonEmpty Text)
folderList} -> Maybe (NonEmpty Text)
folderList) (\s :: RefreshCache
s@RefreshCache' {} Maybe (NonEmpty Text)
a -> RefreshCache
s {$sel:folderList:RefreshCache' :: Maybe (NonEmpty Text)
folderList = Maybe (NonEmpty Text)
a} :: RefreshCache) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
refreshCache_recursive :: Lens.Lens' RefreshCache (Prelude.Maybe Prelude.Bool)
refreshCache_recursive :: Lens' RefreshCache (Maybe Bool)
refreshCache_recursive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCache' {Maybe Bool
recursive :: Maybe Bool
$sel:recursive:RefreshCache' :: RefreshCache -> Maybe Bool
recursive} -> Maybe Bool
recursive) (\s :: RefreshCache
s@RefreshCache' {} Maybe Bool
a -> RefreshCache
s {$sel:recursive:RefreshCache' :: Maybe Bool
recursive = Maybe Bool
a} :: RefreshCache)
refreshCache_fileShareARN :: Lens.Lens' RefreshCache Prelude.Text
refreshCache_fileShareARN :: Lens' RefreshCache Text
refreshCache_fileShareARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCache' {Text
fileShareARN :: Text
$sel:fileShareARN:RefreshCache' :: RefreshCache -> Text
fileShareARN} -> Text
fileShareARN) (\s :: RefreshCache
s@RefreshCache' {} Text
a -> RefreshCache
s {$sel:fileShareARN:RefreshCache' :: Text
fileShareARN = Text
a} :: RefreshCache)
instance Core.AWSRequest RefreshCache where
type AWSResponse RefreshCache = RefreshCacheResponse
request :: (Service -> Service) -> RefreshCache -> Request RefreshCache
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RefreshCache
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RefreshCache)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe Text -> Maybe Text -> Int -> RefreshCacheResponse
RefreshCacheResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FileShareARN")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NotificationId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable RefreshCache where
hashWithSalt :: Int -> RefreshCache -> Int
hashWithSalt Int
_salt RefreshCache' {Maybe Bool
Maybe (NonEmpty Text)
Text
fileShareARN :: Text
recursive :: Maybe Bool
folderList :: Maybe (NonEmpty Text)
$sel:fileShareARN:RefreshCache' :: RefreshCache -> Text
$sel:recursive:RefreshCache' :: RefreshCache -> Maybe Bool
$sel:folderList:RefreshCache' :: RefreshCache -> Maybe (NonEmpty Text)
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
folderList
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
recursive
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fileShareARN
instance Prelude.NFData RefreshCache where
rnf :: RefreshCache -> ()
rnf RefreshCache' {Maybe Bool
Maybe (NonEmpty Text)
Text
fileShareARN :: Text
recursive :: Maybe Bool
folderList :: Maybe (NonEmpty Text)
$sel:fileShareARN:RefreshCache' :: RefreshCache -> Text
$sel:recursive:RefreshCache' :: RefreshCache -> Maybe Bool
$sel:folderList:RefreshCache' :: RefreshCache -> Maybe (NonEmpty Text)
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
folderList
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
recursive
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fileShareARN
instance Data.ToHeaders RefreshCache where
toHeaders :: RefreshCache -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"StorageGateway_20130630.RefreshCache" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON RefreshCache where
toJSON :: RefreshCache -> Value
toJSON RefreshCache' {Maybe Bool
Maybe (NonEmpty Text)
Text
fileShareARN :: Text
recursive :: Maybe Bool
folderList :: Maybe (NonEmpty Text)
$sel:fileShareARN:RefreshCache' :: RefreshCache -> Text
$sel:recursive:RefreshCache' :: RefreshCache -> Maybe Bool
$sel:folderList:RefreshCache' :: RefreshCache -> Maybe (NonEmpty Text)
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"FolderList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty Text)
folderList,
(Key
"Recursive" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
recursive,
forall a. a -> Maybe a
Prelude.Just (Key
"FileShareARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fileShareARN)
]
)
instance Data.ToPath RefreshCache where
toPath :: RefreshCache -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery RefreshCache where
toQuery :: RefreshCache -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data RefreshCacheResponse = RefreshCacheResponse'
{ RefreshCacheResponse -> Maybe Text
fileShareARN :: Prelude.Maybe Prelude.Text,
RefreshCacheResponse -> Maybe Text
notificationId :: Prelude.Maybe Prelude.Text,
RefreshCacheResponse -> Int
httpStatus :: Prelude.Int
}
deriving (RefreshCacheResponse -> RefreshCacheResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefreshCacheResponse -> RefreshCacheResponse -> Bool
$c/= :: RefreshCacheResponse -> RefreshCacheResponse -> Bool
== :: RefreshCacheResponse -> RefreshCacheResponse -> Bool
$c== :: RefreshCacheResponse -> RefreshCacheResponse -> Bool
Prelude.Eq, ReadPrec [RefreshCacheResponse]
ReadPrec RefreshCacheResponse
Int -> ReadS RefreshCacheResponse
ReadS [RefreshCacheResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RefreshCacheResponse]
$creadListPrec :: ReadPrec [RefreshCacheResponse]
readPrec :: ReadPrec RefreshCacheResponse
$creadPrec :: ReadPrec RefreshCacheResponse
readList :: ReadS [RefreshCacheResponse]
$creadList :: ReadS [RefreshCacheResponse]
readsPrec :: Int -> ReadS RefreshCacheResponse
$creadsPrec :: Int -> ReadS RefreshCacheResponse
Prelude.Read, Int -> RefreshCacheResponse -> ShowS
[RefreshCacheResponse] -> ShowS
RefreshCacheResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefreshCacheResponse] -> ShowS
$cshowList :: [RefreshCacheResponse] -> ShowS
show :: RefreshCacheResponse -> String
$cshow :: RefreshCacheResponse -> String
showsPrec :: Int -> RefreshCacheResponse -> ShowS
$cshowsPrec :: Int -> RefreshCacheResponse -> ShowS
Prelude.Show, forall x. Rep RefreshCacheResponse x -> RefreshCacheResponse
forall x. RefreshCacheResponse -> Rep RefreshCacheResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RefreshCacheResponse x -> RefreshCacheResponse
$cfrom :: forall x. RefreshCacheResponse -> Rep RefreshCacheResponse x
Prelude.Generic)
newRefreshCacheResponse ::
Prelude.Int ->
RefreshCacheResponse
newRefreshCacheResponse :: Int -> RefreshCacheResponse
newRefreshCacheResponse Int
pHttpStatus_ =
RefreshCacheResponse'
{ $sel:fileShareARN:RefreshCacheResponse' :: Maybe Text
fileShareARN =
forall a. Maybe a
Prelude.Nothing,
$sel:notificationId:RefreshCacheResponse' :: Maybe Text
notificationId = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:RefreshCacheResponse' :: Int
httpStatus = Int
pHttpStatus_
}
refreshCacheResponse_fileShareARN :: Lens.Lens' RefreshCacheResponse (Prelude.Maybe Prelude.Text)
refreshCacheResponse_fileShareARN :: Lens' RefreshCacheResponse (Maybe Text)
refreshCacheResponse_fileShareARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCacheResponse' {Maybe Text
fileShareARN :: Maybe Text
$sel:fileShareARN:RefreshCacheResponse' :: RefreshCacheResponse -> Maybe Text
fileShareARN} -> Maybe Text
fileShareARN) (\s :: RefreshCacheResponse
s@RefreshCacheResponse' {} Maybe Text
a -> RefreshCacheResponse
s {$sel:fileShareARN:RefreshCacheResponse' :: Maybe Text
fileShareARN = Maybe Text
a} :: RefreshCacheResponse)
refreshCacheResponse_notificationId :: Lens.Lens' RefreshCacheResponse (Prelude.Maybe Prelude.Text)
refreshCacheResponse_notificationId :: Lens' RefreshCacheResponse (Maybe Text)
refreshCacheResponse_notificationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCacheResponse' {Maybe Text
notificationId :: Maybe Text
$sel:notificationId:RefreshCacheResponse' :: RefreshCacheResponse -> Maybe Text
notificationId} -> Maybe Text
notificationId) (\s :: RefreshCacheResponse
s@RefreshCacheResponse' {} Maybe Text
a -> RefreshCacheResponse
s {$sel:notificationId:RefreshCacheResponse' :: Maybe Text
notificationId = Maybe Text
a} :: RefreshCacheResponse)
refreshCacheResponse_httpStatus :: Lens.Lens' RefreshCacheResponse Prelude.Int
refreshCacheResponse_httpStatus :: Lens' RefreshCacheResponse Int
refreshCacheResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshCacheResponse' {Int
httpStatus :: Int
$sel:httpStatus:RefreshCacheResponse' :: RefreshCacheResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: RefreshCacheResponse
s@RefreshCacheResponse' {} Int
a -> RefreshCacheResponse
s {$sel:httpStatus:RefreshCacheResponse' :: Int
httpStatus = Int
a} :: RefreshCacheResponse)
instance Prelude.NFData RefreshCacheResponse where
rnf :: RefreshCacheResponse -> ()
rnf RefreshCacheResponse' {Int
Maybe Text
httpStatus :: Int
notificationId :: Maybe Text
fileShareARN :: Maybe Text
$sel:httpStatus:RefreshCacheResponse' :: RefreshCacheResponse -> Int
$sel:notificationId:RefreshCacheResponse' :: RefreshCacheResponse -> Maybe Text
$sel:fileShareARN:RefreshCacheResponse' :: RefreshCacheResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileShareARN
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
notificationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus