{-# 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.WorkMail.GetDefaultRetentionPolicy
  ( 
    GetDefaultRetentionPolicy (..),
    newGetDefaultRetentionPolicy,
    
    getDefaultRetentionPolicy_organizationId,
    
    GetDefaultRetentionPolicyResponse (..),
    newGetDefaultRetentionPolicyResponse,
    
    getDefaultRetentionPolicyResponse_description,
    getDefaultRetentionPolicyResponse_folderConfigurations,
    getDefaultRetentionPolicyResponse_id,
    getDefaultRetentionPolicyResponse_name,
    getDefaultRetentionPolicyResponse_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.WorkMail.Types
data GetDefaultRetentionPolicy = GetDefaultRetentionPolicy'
  { 
    GetDefaultRetentionPolicy -> Text
organizationId :: Prelude.Text
  }
  deriving (GetDefaultRetentionPolicy -> GetDefaultRetentionPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDefaultRetentionPolicy -> GetDefaultRetentionPolicy -> Bool
$c/= :: GetDefaultRetentionPolicy -> GetDefaultRetentionPolicy -> Bool
== :: GetDefaultRetentionPolicy -> GetDefaultRetentionPolicy -> Bool
$c== :: GetDefaultRetentionPolicy -> GetDefaultRetentionPolicy -> Bool
Prelude.Eq, ReadPrec [GetDefaultRetentionPolicy]
ReadPrec GetDefaultRetentionPolicy
Int -> ReadS GetDefaultRetentionPolicy
ReadS [GetDefaultRetentionPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDefaultRetentionPolicy]
$creadListPrec :: ReadPrec [GetDefaultRetentionPolicy]
readPrec :: ReadPrec GetDefaultRetentionPolicy
$creadPrec :: ReadPrec GetDefaultRetentionPolicy
readList :: ReadS [GetDefaultRetentionPolicy]
$creadList :: ReadS [GetDefaultRetentionPolicy]
readsPrec :: Int -> ReadS GetDefaultRetentionPolicy
$creadsPrec :: Int -> ReadS GetDefaultRetentionPolicy
Prelude.Read, Int -> GetDefaultRetentionPolicy -> ShowS
[GetDefaultRetentionPolicy] -> ShowS
GetDefaultRetentionPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDefaultRetentionPolicy] -> ShowS
$cshowList :: [GetDefaultRetentionPolicy] -> ShowS
show :: GetDefaultRetentionPolicy -> String
$cshow :: GetDefaultRetentionPolicy -> String
showsPrec :: Int -> GetDefaultRetentionPolicy -> ShowS
$cshowsPrec :: Int -> GetDefaultRetentionPolicy -> ShowS
Prelude.Show, forall x.
Rep GetDefaultRetentionPolicy x -> GetDefaultRetentionPolicy
forall x.
GetDefaultRetentionPolicy -> Rep GetDefaultRetentionPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDefaultRetentionPolicy x -> GetDefaultRetentionPolicy
$cfrom :: forall x.
GetDefaultRetentionPolicy -> Rep GetDefaultRetentionPolicy x
Prelude.Generic)
newGetDefaultRetentionPolicy ::
  
  Prelude.Text ->
  GetDefaultRetentionPolicy
newGetDefaultRetentionPolicy :: Text -> GetDefaultRetentionPolicy
newGetDefaultRetentionPolicy Text
pOrganizationId_ =
  GetDefaultRetentionPolicy'
    { $sel:organizationId:GetDefaultRetentionPolicy' :: Text
organizationId =
        Text
pOrganizationId_
    }
getDefaultRetentionPolicy_organizationId :: Lens.Lens' GetDefaultRetentionPolicy Prelude.Text
getDefaultRetentionPolicy_organizationId :: Lens' GetDefaultRetentionPolicy Text
getDefaultRetentionPolicy_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicy' {Text
organizationId :: Text
$sel:organizationId:GetDefaultRetentionPolicy' :: GetDefaultRetentionPolicy -> Text
organizationId} -> Text
organizationId) (\s :: GetDefaultRetentionPolicy
s@GetDefaultRetentionPolicy' {} Text
a -> GetDefaultRetentionPolicy
s {$sel:organizationId:GetDefaultRetentionPolicy' :: Text
organizationId = Text
a} :: GetDefaultRetentionPolicy)
instance Core.AWSRequest GetDefaultRetentionPolicy where
  type
    AWSResponse GetDefaultRetentionPolicy =
      GetDefaultRetentionPolicyResponse
  request :: (Service -> Service)
-> GetDefaultRetentionPolicy -> Request GetDefaultRetentionPolicy
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 GetDefaultRetentionPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDefaultRetentionPolicy)))
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 [FolderConfiguration]
-> Maybe Text
-> Maybe Text
-> Int
-> GetDefaultRetentionPolicyResponse
GetDefaultRetentionPolicyResponse'
            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
"Description")
            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
"FolderConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"Id")
            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
"Name")
            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 GetDefaultRetentionPolicy where
  hashWithSalt :: Int -> GetDefaultRetentionPolicy -> Int
hashWithSalt Int
_salt GetDefaultRetentionPolicy' {Text
organizationId :: Text
$sel:organizationId:GetDefaultRetentionPolicy' :: GetDefaultRetentionPolicy -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
instance Prelude.NFData GetDefaultRetentionPolicy where
  rnf :: GetDefaultRetentionPolicy -> ()
rnf GetDefaultRetentionPolicy' {Text
organizationId :: Text
$sel:organizationId:GetDefaultRetentionPolicy' :: GetDefaultRetentionPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
instance Data.ToHeaders GetDefaultRetentionPolicy where
  toHeaders :: GetDefaultRetentionPolicy -> 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
"WorkMailService.GetDefaultRetentionPolicy" ::
                          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 GetDefaultRetentionPolicy where
  toJSON :: GetDefaultRetentionPolicy -> Value
toJSON GetDefaultRetentionPolicy' {Text
organizationId :: Text
$sel:organizationId:GetDefaultRetentionPolicy' :: GetDefaultRetentionPolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId)
          ]
      )
instance Data.ToPath GetDefaultRetentionPolicy where
  toPath :: GetDefaultRetentionPolicy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery GetDefaultRetentionPolicy where
  toQuery :: GetDefaultRetentionPolicy -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetDefaultRetentionPolicyResponse = GetDefaultRetentionPolicyResponse'
  { 
    GetDefaultRetentionPolicyResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    
    GetDefaultRetentionPolicyResponse -> Maybe [FolderConfiguration]
folderConfigurations :: Prelude.Maybe [FolderConfiguration],
    
    GetDefaultRetentionPolicyResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    
    GetDefaultRetentionPolicyResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    
    GetDefaultRetentionPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDefaultRetentionPolicyResponse
-> GetDefaultRetentionPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDefaultRetentionPolicyResponse
-> GetDefaultRetentionPolicyResponse -> Bool
$c/= :: GetDefaultRetentionPolicyResponse
-> GetDefaultRetentionPolicyResponse -> Bool
== :: GetDefaultRetentionPolicyResponse
-> GetDefaultRetentionPolicyResponse -> Bool
$c== :: GetDefaultRetentionPolicyResponse
-> GetDefaultRetentionPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetDefaultRetentionPolicyResponse]
ReadPrec GetDefaultRetentionPolicyResponse
Int -> ReadS GetDefaultRetentionPolicyResponse
ReadS [GetDefaultRetentionPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDefaultRetentionPolicyResponse]
$creadListPrec :: ReadPrec [GetDefaultRetentionPolicyResponse]
readPrec :: ReadPrec GetDefaultRetentionPolicyResponse
$creadPrec :: ReadPrec GetDefaultRetentionPolicyResponse
readList :: ReadS [GetDefaultRetentionPolicyResponse]
$creadList :: ReadS [GetDefaultRetentionPolicyResponse]
readsPrec :: Int -> ReadS GetDefaultRetentionPolicyResponse
$creadsPrec :: Int -> ReadS GetDefaultRetentionPolicyResponse
Prelude.Read, Int -> GetDefaultRetentionPolicyResponse -> ShowS
[GetDefaultRetentionPolicyResponse] -> ShowS
GetDefaultRetentionPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDefaultRetentionPolicyResponse] -> ShowS
$cshowList :: [GetDefaultRetentionPolicyResponse] -> ShowS
show :: GetDefaultRetentionPolicyResponse -> String
$cshow :: GetDefaultRetentionPolicyResponse -> String
showsPrec :: Int -> GetDefaultRetentionPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetDefaultRetentionPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep GetDefaultRetentionPolicyResponse x
-> GetDefaultRetentionPolicyResponse
forall x.
GetDefaultRetentionPolicyResponse
-> Rep GetDefaultRetentionPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDefaultRetentionPolicyResponse x
-> GetDefaultRetentionPolicyResponse
$cfrom :: forall x.
GetDefaultRetentionPolicyResponse
-> Rep GetDefaultRetentionPolicyResponse x
Prelude.Generic)
newGetDefaultRetentionPolicyResponse ::
  
  Prelude.Int ->
  GetDefaultRetentionPolicyResponse
newGetDefaultRetentionPolicyResponse :: Int -> GetDefaultRetentionPolicyResponse
newGetDefaultRetentionPolicyResponse Int
pHttpStatus_ =
  GetDefaultRetentionPolicyResponse'
    { $sel:description:GetDefaultRetentionPolicyResponse' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:folderConfigurations:GetDefaultRetentionPolicyResponse' :: Maybe [FolderConfiguration]
folderConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetDefaultRetentionPolicyResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetDefaultRetentionPolicyResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDefaultRetentionPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }
getDefaultRetentionPolicyResponse_description :: Lens.Lens' GetDefaultRetentionPolicyResponse (Prelude.Maybe Prelude.Text)
getDefaultRetentionPolicyResponse_description :: Lens' GetDefaultRetentionPolicyResponse (Maybe Text)
getDefaultRetentionPolicyResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicyResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetDefaultRetentionPolicyResponse
s@GetDefaultRetentionPolicyResponse' {} Maybe Text
a -> GetDefaultRetentionPolicyResponse
s {$sel:description:GetDefaultRetentionPolicyResponse' :: Maybe Text
description = Maybe Text
a} :: GetDefaultRetentionPolicyResponse)
getDefaultRetentionPolicyResponse_folderConfigurations :: Lens.Lens' GetDefaultRetentionPolicyResponse (Prelude.Maybe [FolderConfiguration])
getDefaultRetentionPolicyResponse_folderConfigurations :: Lens'
  GetDefaultRetentionPolicyResponse (Maybe [FolderConfiguration])
getDefaultRetentionPolicyResponse_folderConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicyResponse' {Maybe [FolderConfiguration]
folderConfigurations :: Maybe [FolderConfiguration]
$sel:folderConfigurations:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe [FolderConfiguration]
folderConfigurations} -> Maybe [FolderConfiguration]
folderConfigurations) (\s :: GetDefaultRetentionPolicyResponse
s@GetDefaultRetentionPolicyResponse' {} Maybe [FolderConfiguration]
a -> GetDefaultRetentionPolicyResponse
s {$sel:folderConfigurations:GetDefaultRetentionPolicyResponse' :: Maybe [FolderConfiguration]
folderConfigurations = Maybe [FolderConfiguration]
a} :: GetDefaultRetentionPolicyResponse) 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
getDefaultRetentionPolicyResponse_id :: Lens.Lens' GetDefaultRetentionPolicyResponse (Prelude.Maybe Prelude.Text)
getDefaultRetentionPolicyResponse_id :: Lens' GetDefaultRetentionPolicyResponse (Maybe Text)
getDefaultRetentionPolicyResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicyResponse' {Maybe Text
id :: Maybe Text
$sel:id:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: GetDefaultRetentionPolicyResponse
s@GetDefaultRetentionPolicyResponse' {} Maybe Text
a -> GetDefaultRetentionPolicyResponse
s {$sel:id:GetDefaultRetentionPolicyResponse' :: Maybe Text
id = Maybe Text
a} :: GetDefaultRetentionPolicyResponse)
getDefaultRetentionPolicyResponse_name :: Lens.Lens' GetDefaultRetentionPolicyResponse (Prelude.Maybe Prelude.Text)
getDefaultRetentionPolicyResponse_name :: Lens' GetDefaultRetentionPolicyResponse (Maybe Text)
getDefaultRetentionPolicyResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicyResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetDefaultRetentionPolicyResponse
s@GetDefaultRetentionPolicyResponse' {} Maybe Text
a -> GetDefaultRetentionPolicyResponse
s {$sel:name:GetDefaultRetentionPolicyResponse' :: Maybe Text
name = Maybe Text
a} :: GetDefaultRetentionPolicyResponse)
getDefaultRetentionPolicyResponse_httpStatus :: Lens.Lens' GetDefaultRetentionPolicyResponse Prelude.Int
getDefaultRetentionPolicyResponse_httpStatus :: Lens' GetDefaultRetentionPolicyResponse Int
getDefaultRetentionPolicyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDefaultRetentionPolicyResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetDefaultRetentionPolicyResponse
s@GetDefaultRetentionPolicyResponse' {} Int
a -> GetDefaultRetentionPolicyResponse
s {$sel:httpStatus:GetDefaultRetentionPolicyResponse' :: Int
httpStatus = Int
a} :: GetDefaultRetentionPolicyResponse)
instance
  Prelude.NFData
    GetDefaultRetentionPolicyResponse
  where
  rnf :: GetDefaultRetentionPolicyResponse -> ()
rnf GetDefaultRetentionPolicyResponse' {Int
Maybe [FolderConfiguration]
Maybe Text
httpStatus :: Int
name :: Maybe Text
id :: Maybe Text
folderConfigurations :: Maybe [FolderConfiguration]
description :: Maybe Text
$sel:httpStatus:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Int
$sel:name:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
$sel:id:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
$sel:folderConfigurations:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe [FolderConfiguration]
$sel:description:GetDefaultRetentionPolicyResponse' :: GetDefaultRetentionPolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [FolderConfiguration]
folderConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus