{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

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

-- |
-- Module      : Amazonka.Lambda.Types.Cors
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Lambda.Types.Cors 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

-- | The
-- <https://developer.mozilla.org/en-US/docs/Web/HTTP/CORS cross-origin resource sharing (CORS)>
-- settings for your Lambda function URL. Use CORS to grant access to your
-- function URL from any origin. You can also use CORS to control access
-- for specific HTTP headers and methods in requests to your function URL.
--
-- /See:/ 'newCors' smart constructor.
data Cors = Cors'
  { -- | Whether to allow cookies or other credentials in requests to your
    -- function URL. The default is @false@.
    Cors -> Maybe Bool
allowCredentials :: Prelude.Maybe Prelude.Bool,
    -- | The HTTP headers that origins can include in requests to your function
    -- URL. For example: @Date@, @Keep-Alive@, @X-Custom-Header@.
    Cors -> Maybe [Text]
allowHeaders :: Prelude.Maybe [Prelude.Text],
    -- | The HTTP methods that are allowed when calling your function URL. For
    -- example: @GET@, @POST@, @DELETE@, or the wildcard character (@*@).
    Cors -> Maybe [Text]
allowMethods :: Prelude.Maybe [Prelude.Text],
    -- | The origins that can access your function URL. You can list any number
    -- of specific origins, separated by a comma. For example:
    -- @https:\/\/www.example.com@, @http:\/\/localhost:60905@.
    --
    -- Alternatively, you can grant access to all origins using the wildcard
    -- character (@*@).
    Cors -> Maybe [Text]
allowOrigins :: Prelude.Maybe [Prelude.Text],
    -- | The HTTP headers in your function response that you want to expose to
    -- origins that call your function URL. For example: @Date@, @Keep-Alive@,
    -- @X-Custom-Header@.
    Cors -> Maybe [Text]
exposeHeaders :: Prelude.Maybe [Prelude.Text],
    -- | The maximum amount of time, in seconds, that web browsers can cache
    -- results of a preflight request. By default, this is set to @0@, which
    -- means that the browser doesn\'t cache results.
    Cors -> Maybe Natural
maxAge :: Prelude.Maybe Prelude.Natural
  }
  deriving (Cors -> Cors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cors -> Cors -> Bool
$c/= :: Cors -> Cors -> Bool
== :: Cors -> Cors -> Bool
$c== :: Cors -> Cors -> Bool
Prelude.Eq, ReadPrec [Cors]
ReadPrec Cors
Int -> ReadS Cors
ReadS [Cors]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Cors]
$creadListPrec :: ReadPrec [Cors]
readPrec :: ReadPrec Cors
$creadPrec :: ReadPrec Cors
readList :: ReadS [Cors]
$creadList :: ReadS [Cors]
readsPrec :: Int -> ReadS Cors
$creadsPrec :: Int -> ReadS Cors
Prelude.Read, Int -> Cors -> ShowS
[Cors] -> ShowS
Cors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cors] -> ShowS
$cshowList :: [Cors] -> ShowS
show :: Cors -> String
$cshow :: Cors -> String
showsPrec :: Int -> Cors -> ShowS
$cshowsPrec :: Int -> Cors -> ShowS
Prelude.Show, forall x. Rep Cors x -> Cors
forall x. Cors -> Rep Cors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cors x -> Cors
$cfrom :: forall x. Cors -> Rep Cors x
Prelude.Generic)

-- |
-- Create a value of 'Cors' 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:
--
-- 'allowCredentials', 'cors_allowCredentials' - Whether to allow cookies or other credentials in requests to your
-- function URL. The default is @false@.
--
-- 'allowHeaders', 'cors_allowHeaders' - The HTTP headers that origins can include in requests to your function
-- URL. For example: @Date@, @Keep-Alive@, @X-Custom-Header@.
--
-- 'allowMethods', 'cors_allowMethods' - The HTTP methods that are allowed when calling your function URL. For
-- example: @GET@, @POST@, @DELETE@, or the wildcard character (@*@).
--
-- 'allowOrigins', 'cors_allowOrigins' - The origins that can access your function URL. You can list any number
-- of specific origins, separated by a comma. For example:
-- @https:\/\/www.example.com@, @http:\/\/localhost:60905@.
--
-- Alternatively, you can grant access to all origins using the wildcard
-- character (@*@).
--
-- 'exposeHeaders', 'cors_exposeHeaders' - The HTTP headers in your function response that you want to expose to
-- origins that call your function URL. For example: @Date@, @Keep-Alive@,
-- @X-Custom-Header@.
--
-- 'maxAge', 'cors_maxAge' - The maximum amount of time, in seconds, that web browsers can cache
-- results of a preflight request. By default, this is set to @0@, which
-- means that the browser doesn\'t cache results.
newCors ::
  Cors
newCors :: Cors
newCors =
  Cors'
    { $sel:allowCredentials:Cors' :: Maybe Bool
allowCredentials = forall a. Maybe a
Prelude.Nothing,
      $sel:allowHeaders:Cors' :: Maybe [Text]
allowHeaders = forall a. Maybe a
Prelude.Nothing,
      $sel:allowMethods:Cors' :: Maybe [Text]
allowMethods = forall a. Maybe a
Prelude.Nothing,
      $sel:allowOrigins:Cors' :: Maybe [Text]
allowOrigins = forall a. Maybe a
Prelude.Nothing,
      $sel:exposeHeaders:Cors' :: Maybe [Text]
exposeHeaders = forall a. Maybe a
Prelude.Nothing,
      $sel:maxAge:Cors' :: Maybe Natural
maxAge = forall a. Maybe a
Prelude.Nothing
    }

-- | Whether to allow cookies or other credentials in requests to your
-- function URL. The default is @false@.
cors_allowCredentials :: Lens.Lens' Cors (Prelude.Maybe Prelude.Bool)
cors_allowCredentials :: Lens' Cors (Maybe Bool)
cors_allowCredentials = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe Bool
allowCredentials :: Maybe Bool
$sel:allowCredentials:Cors' :: Cors -> Maybe Bool
allowCredentials} -> Maybe Bool
allowCredentials) (\s :: Cors
s@Cors' {} Maybe Bool
a -> Cors
s {$sel:allowCredentials:Cors' :: Maybe Bool
allowCredentials = Maybe Bool
a} :: Cors)

-- | The HTTP headers that origins can include in requests to your function
-- URL. For example: @Date@, @Keep-Alive@, @X-Custom-Header@.
cors_allowHeaders :: Lens.Lens' Cors (Prelude.Maybe [Prelude.Text])
cors_allowHeaders :: Lens' Cors (Maybe [Text])
cors_allowHeaders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe [Text]
allowHeaders :: Maybe [Text]
$sel:allowHeaders:Cors' :: Cors -> Maybe [Text]
allowHeaders} -> Maybe [Text]
allowHeaders) (\s :: Cors
s@Cors' {} Maybe [Text]
a -> Cors
s {$sel:allowHeaders:Cors' :: Maybe [Text]
allowHeaders = Maybe [Text]
a} :: Cors) 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 HTTP methods that are allowed when calling your function URL. For
-- example: @GET@, @POST@, @DELETE@, or the wildcard character (@*@).
cors_allowMethods :: Lens.Lens' Cors (Prelude.Maybe [Prelude.Text])
cors_allowMethods :: Lens' Cors (Maybe [Text])
cors_allowMethods = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe [Text]
allowMethods :: Maybe [Text]
$sel:allowMethods:Cors' :: Cors -> Maybe [Text]
allowMethods} -> Maybe [Text]
allowMethods) (\s :: Cors
s@Cors' {} Maybe [Text]
a -> Cors
s {$sel:allowMethods:Cors' :: Maybe [Text]
allowMethods = Maybe [Text]
a} :: Cors) 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 origins that can access your function URL. You can list any number
-- of specific origins, separated by a comma. For example:
-- @https:\/\/www.example.com@, @http:\/\/localhost:60905@.
--
-- Alternatively, you can grant access to all origins using the wildcard
-- character (@*@).
cors_allowOrigins :: Lens.Lens' Cors (Prelude.Maybe [Prelude.Text])
cors_allowOrigins :: Lens' Cors (Maybe [Text])
cors_allowOrigins = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe [Text]
allowOrigins :: Maybe [Text]
$sel:allowOrigins:Cors' :: Cors -> Maybe [Text]
allowOrigins} -> Maybe [Text]
allowOrigins) (\s :: Cors
s@Cors' {} Maybe [Text]
a -> Cors
s {$sel:allowOrigins:Cors' :: Maybe [Text]
allowOrigins = Maybe [Text]
a} :: Cors) 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 HTTP headers in your function response that you want to expose to
-- origins that call your function URL. For example: @Date@, @Keep-Alive@,
-- @X-Custom-Header@.
cors_exposeHeaders :: Lens.Lens' Cors (Prelude.Maybe [Prelude.Text])
cors_exposeHeaders :: Lens' Cors (Maybe [Text])
cors_exposeHeaders = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe [Text]
exposeHeaders :: Maybe [Text]
$sel:exposeHeaders:Cors' :: Cors -> Maybe [Text]
exposeHeaders} -> Maybe [Text]
exposeHeaders) (\s :: Cors
s@Cors' {} Maybe [Text]
a -> Cors
s {$sel:exposeHeaders:Cors' :: Maybe [Text]
exposeHeaders = Maybe [Text]
a} :: Cors) 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 maximum amount of time, in seconds, that web browsers can cache
-- results of a preflight request. By default, this is set to @0@, which
-- means that the browser doesn\'t cache results.
cors_maxAge :: Lens.Lens' Cors (Prelude.Maybe Prelude.Natural)
cors_maxAge :: Lens' Cors (Maybe Natural)
cors_maxAge = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Cors' {Maybe Natural
maxAge :: Maybe Natural
$sel:maxAge:Cors' :: Cors -> Maybe Natural
maxAge} -> Maybe Natural
maxAge) (\s :: Cors
s@Cors' {} Maybe Natural
a -> Cors
s {$sel:maxAge:Cors' :: Maybe Natural
maxAge = Maybe Natural
a} :: Cors)

instance Data.FromJSON Cors where
  parseJSON :: Value -> Parser Cors
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Cors"
      ( \Object
x ->
          Maybe Bool
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Natural
-> Cors
Cors'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AllowCredentials")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AllowHeaders" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"AllowMethods" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"AllowOrigins" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"ExposeHeaders" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"MaxAge")
      )

instance Prelude.Hashable Cors where
  hashWithSalt :: Int -> Cors -> Int
hashWithSalt Int
_salt Cors' {Maybe Bool
Maybe Natural
Maybe [Text]
maxAge :: Maybe Natural
exposeHeaders :: Maybe [Text]
allowOrigins :: Maybe [Text]
allowMethods :: Maybe [Text]
allowHeaders :: Maybe [Text]
allowCredentials :: Maybe Bool
$sel:maxAge:Cors' :: Cors -> Maybe Natural
$sel:exposeHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowOrigins:Cors' :: Cors -> Maybe [Text]
$sel:allowMethods:Cors' :: Cors -> Maybe [Text]
$sel:allowHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowCredentials:Cors' :: Cors -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowCredentials
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
allowHeaders
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
allowMethods
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
allowOrigins
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
exposeHeaders
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxAge

instance Prelude.NFData Cors where
  rnf :: Cors -> ()
rnf Cors' {Maybe Bool
Maybe Natural
Maybe [Text]
maxAge :: Maybe Natural
exposeHeaders :: Maybe [Text]
allowOrigins :: Maybe [Text]
allowMethods :: Maybe [Text]
allowHeaders :: Maybe [Text]
allowCredentials :: Maybe Bool
$sel:maxAge:Cors' :: Cors -> Maybe Natural
$sel:exposeHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowOrigins:Cors' :: Cors -> Maybe [Text]
$sel:allowMethods:Cors' :: Cors -> Maybe [Text]
$sel:allowHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowCredentials:Cors' :: Cors -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowCredentials
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
allowHeaders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
allowMethods
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
allowOrigins
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
exposeHeaders
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxAge

instance Data.ToJSON Cors where
  toJSON :: Cors -> Value
toJSON Cors' {Maybe Bool
Maybe Natural
Maybe [Text]
maxAge :: Maybe Natural
exposeHeaders :: Maybe [Text]
allowOrigins :: Maybe [Text]
allowMethods :: Maybe [Text]
allowHeaders :: Maybe [Text]
allowCredentials :: Maybe Bool
$sel:maxAge:Cors' :: Cors -> Maybe Natural
$sel:exposeHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowOrigins:Cors' :: Cors -> Maybe [Text]
$sel:allowMethods:Cors' :: Cors -> Maybe [Text]
$sel:allowHeaders:Cors' :: Cors -> Maybe [Text]
$sel:allowCredentials:Cors' :: Cors -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AllowCredentials" 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
allowCredentials,
            (Key
"AllowHeaders" 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 [Text]
allowHeaders,
            (Key
"AllowMethods" 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 [Text]
allowMethods,
            (Key
"AllowOrigins" 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 [Text]
allowOrigins,
            (Key
"ExposeHeaders" 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 [Text]
exposeHeaders,
            (Key
"MaxAge" 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 Natural
maxAge
          ]
      )