{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.WorkMail.ListMobileDeviceAccessRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the mobile device access rules for the specified WorkMail
-- organization.
module Amazonka.WorkMail.ListMobileDeviceAccessRules
  ( -- * Creating a Request
    ListMobileDeviceAccessRules (..),
    newListMobileDeviceAccessRules,

    -- * Request Lenses
    listMobileDeviceAccessRules_organizationId,

    -- * Destructuring the Response
    ListMobileDeviceAccessRulesResponse (..),
    newListMobileDeviceAccessRulesResponse,

    -- * Response Lenses
    listMobileDeviceAccessRulesResponse_rules,
    listMobileDeviceAccessRulesResponse_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

-- | /See:/ 'newListMobileDeviceAccessRules' smart constructor.
data ListMobileDeviceAccessRules = ListMobileDeviceAccessRules'
  { -- | The WorkMail organization for which to list the rules.
    ListMobileDeviceAccessRules -> Text
organizationId :: Prelude.Text
  }
  deriving (ListMobileDeviceAccessRules -> ListMobileDeviceAccessRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMobileDeviceAccessRules -> ListMobileDeviceAccessRules -> Bool
$c/= :: ListMobileDeviceAccessRules -> ListMobileDeviceAccessRules -> Bool
== :: ListMobileDeviceAccessRules -> ListMobileDeviceAccessRules -> Bool
$c== :: ListMobileDeviceAccessRules -> ListMobileDeviceAccessRules -> Bool
Prelude.Eq, ReadPrec [ListMobileDeviceAccessRules]
ReadPrec ListMobileDeviceAccessRules
Int -> ReadS ListMobileDeviceAccessRules
ReadS [ListMobileDeviceAccessRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListMobileDeviceAccessRules]
$creadListPrec :: ReadPrec [ListMobileDeviceAccessRules]
readPrec :: ReadPrec ListMobileDeviceAccessRules
$creadPrec :: ReadPrec ListMobileDeviceAccessRules
readList :: ReadS [ListMobileDeviceAccessRules]
$creadList :: ReadS [ListMobileDeviceAccessRules]
readsPrec :: Int -> ReadS ListMobileDeviceAccessRules
$creadsPrec :: Int -> ReadS ListMobileDeviceAccessRules
Prelude.Read, Int -> ListMobileDeviceAccessRules -> ShowS
[ListMobileDeviceAccessRules] -> ShowS
ListMobileDeviceAccessRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMobileDeviceAccessRules] -> ShowS
$cshowList :: [ListMobileDeviceAccessRules] -> ShowS
show :: ListMobileDeviceAccessRules -> String
$cshow :: ListMobileDeviceAccessRules -> String
showsPrec :: Int -> ListMobileDeviceAccessRules -> ShowS
$cshowsPrec :: Int -> ListMobileDeviceAccessRules -> ShowS
Prelude.Show, forall x.
Rep ListMobileDeviceAccessRules x -> ListMobileDeviceAccessRules
forall x.
ListMobileDeviceAccessRules -> Rep ListMobileDeviceAccessRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListMobileDeviceAccessRules x -> ListMobileDeviceAccessRules
$cfrom :: forall x.
ListMobileDeviceAccessRules -> Rep ListMobileDeviceAccessRules x
Prelude.Generic)

-- |
-- Create a value of 'ListMobileDeviceAccessRules' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'organizationId', 'listMobileDeviceAccessRules_organizationId' - The WorkMail organization for which to list the rules.
newListMobileDeviceAccessRules ::
  -- | 'organizationId'
  Prelude.Text ->
  ListMobileDeviceAccessRules
newListMobileDeviceAccessRules :: Text -> ListMobileDeviceAccessRules
newListMobileDeviceAccessRules Text
pOrganizationId_ =
  ListMobileDeviceAccessRules'
    { $sel:organizationId:ListMobileDeviceAccessRules' :: Text
organizationId =
        Text
pOrganizationId_
    }

-- | The WorkMail organization for which to list the rules.
listMobileDeviceAccessRules_organizationId :: Lens.Lens' ListMobileDeviceAccessRules Prelude.Text
listMobileDeviceAccessRules_organizationId :: Lens' ListMobileDeviceAccessRules Text
listMobileDeviceAccessRules_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMobileDeviceAccessRules' {Text
organizationId :: Text
$sel:organizationId:ListMobileDeviceAccessRules' :: ListMobileDeviceAccessRules -> Text
organizationId} -> Text
organizationId) (\s :: ListMobileDeviceAccessRules
s@ListMobileDeviceAccessRules' {} Text
a -> ListMobileDeviceAccessRules
s {$sel:organizationId:ListMobileDeviceAccessRules' :: Text
organizationId = Text
a} :: ListMobileDeviceAccessRules)

instance Core.AWSRequest ListMobileDeviceAccessRules where
  type
    AWSResponse ListMobileDeviceAccessRules =
      ListMobileDeviceAccessRulesResponse
  request :: (Service -> Service)
-> ListMobileDeviceAccessRules
-> Request ListMobileDeviceAccessRules
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 ListMobileDeviceAccessRules
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListMobileDeviceAccessRules)))
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 [MobileDeviceAccessRule]
-> Int -> ListMobileDeviceAccessRulesResponse
ListMobileDeviceAccessRulesResponse'
            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
"Rules" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListMobileDeviceAccessRules where
  hashWithSalt :: Int -> ListMobileDeviceAccessRules -> Int
hashWithSalt Int
_salt ListMobileDeviceAccessRules' {Text
organizationId :: Text
$sel:organizationId:ListMobileDeviceAccessRules' :: ListMobileDeviceAccessRules -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId

instance Prelude.NFData ListMobileDeviceAccessRules where
  rnf :: ListMobileDeviceAccessRules -> ()
rnf ListMobileDeviceAccessRules' {Text
organizationId :: Text
$sel:organizationId:ListMobileDeviceAccessRules' :: ListMobileDeviceAccessRules -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId

instance Data.ToHeaders ListMobileDeviceAccessRules where
  toHeaders :: ListMobileDeviceAccessRules -> 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.ListMobileDeviceAccessRules" ::
                          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 ListMobileDeviceAccessRules where
  toJSON :: ListMobileDeviceAccessRules -> Value
toJSON ListMobileDeviceAccessRules' {Text
organizationId :: Text
$sel:organizationId:ListMobileDeviceAccessRules' :: ListMobileDeviceAccessRules -> 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 ListMobileDeviceAccessRules where
  toPath :: ListMobileDeviceAccessRules -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery ListMobileDeviceAccessRules where
  toQuery :: ListMobileDeviceAccessRules -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListMobileDeviceAccessRulesResponse' smart constructor.
data ListMobileDeviceAccessRulesResponse = ListMobileDeviceAccessRulesResponse'
  { -- | The list of mobile device access rules that exist under the specified
    -- WorkMail organization.
    ListMobileDeviceAccessRulesResponse
-> Maybe [MobileDeviceAccessRule]
rules :: Prelude.Maybe [MobileDeviceAccessRule],
    -- | The response's http status code.
    ListMobileDeviceAccessRulesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListMobileDeviceAccessRulesResponse
-> ListMobileDeviceAccessRulesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMobileDeviceAccessRulesResponse
-> ListMobileDeviceAccessRulesResponse -> Bool
$c/= :: ListMobileDeviceAccessRulesResponse
-> ListMobileDeviceAccessRulesResponse -> Bool
== :: ListMobileDeviceAccessRulesResponse
-> ListMobileDeviceAccessRulesResponse -> Bool
$c== :: ListMobileDeviceAccessRulesResponse
-> ListMobileDeviceAccessRulesResponse -> Bool
Prelude.Eq, ReadPrec [ListMobileDeviceAccessRulesResponse]
ReadPrec ListMobileDeviceAccessRulesResponse
Int -> ReadS ListMobileDeviceAccessRulesResponse
ReadS [ListMobileDeviceAccessRulesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListMobileDeviceAccessRulesResponse]
$creadListPrec :: ReadPrec [ListMobileDeviceAccessRulesResponse]
readPrec :: ReadPrec ListMobileDeviceAccessRulesResponse
$creadPrec :: ReadPrec ListMobileDeviceAccessRulesResponse
readList :: ReadS [ListMobileDeviceAccessRulesResponse]
$creadList :: ReadS [ListMobileDeviceAccessRulesResponse]
readsPrec :: Int -> ReadS ListMobileDeviceAccessRulesResponse
$creadsPrec :: Int -> ReadS ListMobileDeviceAccessRulesResponse
Prelude.Read, Int -> ListMobileDeviceAccessRulesResponse -> ShowS
[ListMobileDeviceAccessRulesResponse] -> ShowS
ListMobileDeviceAccessRulesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMobileDeviceAccessRulesResponse] -> ShowS
$cshowList :: [ListMobileDeviceAccessRulesResponse] -> ShowS
show :: ListMobileDeviceAccessRulesResponse -> String
$cshow :: ListMobileDeviceAccessRulesResponse -> String
showsPrec :: Int -> ListMobileDeviceAccessRulesResponse -> ShowS
$cshowsPrec :: Int -> ListMobileDeviceAccessRulesResponse -> ShowS
Prelude.Show, forall x.
Rep ListMobileDeviceAccessRulesResponse x
-> ListMobileDeviceAccessRulesResponse
forall x.
ListMobileDeviceAccessRulesResponse
-> Rep ListMobileDeviceAccessRulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListMobileDeviceAccessRulesResponse x
-> ListMobileDeviceAccessRulesResponse
$cfrom :: forall x.
ListMobileDeviceAccessRulesResponse
-> Rep ListMobileDeviceAccessRulesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListMobileDeviceAccessRulesResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'rules', 'listMobileDeviceAccessRulesResponse_rules' - The list of mobile device access rules that exist under the specified
-- WorkMail organization.
--
-- 'httpStatus', 'listMobileDeviceAccessRulesResponse_httpStatus' - The response's http status code.
newListMobileDeviceAccessRulesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListMobileDeviceAccessRulesResponse
newListMobileDeviceAccessRulesResponse :: Int -> ListMobileDeviceAccessRulesResponse
newListMobileDeviceAccessRulesResponse Int
pHttpStatus_ =
  ListMobileDeviceAccessRulesResponse'
    { $sel:rules:ListMobileDeviceAccessRulesResponse' :: Maybe [MobileDeviceAccessRule]
rules =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListMobileDeviceAccessRulesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of mobile device access rules that exist under the specified
-- WorkMail organization.
listMobileDeviceAccessRulesResponse_rules :: Lens.Lens' ListMobileDeviceAccessRulesResponse (Prelude.Maybe [MobileDeviceAccessRule])
listMobileDeviceAccessRulesResponse_rules :: Lens'
  ListMobileDeviceAccessRulesResponse
  (Maybe [MobileDeviceAccessRule])
listMobileDeviceAccessRulesResponse_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMobileDeviceAccessRulesResponse' {Maybe [MobileDeviceAccessRule]
rules :: Maybe [MobileDeviceAccessRule]
$sel:rules:ListMobileDeviceAccessRulesResponse' :: ListMobileDeviceAccessRulesResponse
-> Maybe [MobileDeviceAccessRule]
rules} -> Maybe [MobileDeviceAccessRule]
rules) (\s :: ListMobileDeviceAccessRulesResponse
s@ListMobileDeviceAccessRulesResponse' {} Maybe [MobileDeviceAccessRule]
a -> ListMobileDeviceAccessRulesResponse
s {$sel:rules:ListMobileDeviceAccessRulesResponse' :: Maybe [MobileDeviceAccessRule]
rules = Maybe [MobileDeviceAccessRule]
a} :: ListMobileDeviceAccessRulesResponse) 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

-- | The response's http status code.
listMobileDeviceAccessRulesResponse_httpStatus :: Lens.Lens' ListMobileDeviceAccessRulesResponse Prelude.Int
listMobileDeviceAccessRulesResponse_httpStatus :: Lens' ListMobileDeviceAccessRulesResponse Int
listMobileDeviceAccessRulesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMobileDeviceAccessRulesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListMobileDeviceAccessRulesResponse' :: ListMobileDeviceAccessRulesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListMobileDeviceAccessRulesResponse
s@ListMobileDeviceAccessRulesResponse' {} Int
a -> ListMobileDeviceAccessRulesResponse
s {$sel:httpStatus:ListMobileDeviceAccessRulesResponse' :: Int
httpStatus = Int
a} :: ListMobileDeviceAccessRulesResponse)

instance
  Prelude.NFData
    ListMobileDeviceAccessRulesResponse
  where
  rnf :: ListMobileDeviceAccessRulesResponse -> ()
rnf ListMobileDeviceAccessRulesResponse' {Int
Maybe [MobileDeviceAccessRule]
httpStatus :: Int
rules :: Maybe [MobileDeviceAccessRule]
$sel:httpStatus:ListMobileDeviceAccessRulesResponse' :: ListMobileDeviceAccessRulesResponse -> Int
$sel:rules:ListMobileDeviceAccessRulesResponse' :: ListMobileDeviceAccessRulesResponse
-> Maybe [MobileDeviceAccessRule]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [MobileDeviceAccessRule]
rules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus