{-# 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.ECR.CreatePullThroughCacheRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a pull through cache rule. A pull through cache rule provides a
-- way to cache images from an external public registry in your Amazon ECR
-- private registry.
module Amazonka.ECR.CreatePullThroughCacheRule
  ( -- * Creating a Request
    CreatePullThroughCacheRule (..),
    newCreatePullThroughCacheRule,

    -- * Request Lenses
    createPullThroughCacheRule_registryId,
    createPullThroughCacheRule_ecrRepositoryPrefix,
    createPullThroughCacheRule_upstreamRegistryUrl,

    -- * Destructuring the Response
    CreatePullThroughCacheRuleResponse (..),
    newCreatePullThroughCacheRuleResponse,

    -- * Response Lenses
    createPullThroughCacheRuleResponse_createdAt,
    createPullThroughCacheRuleResponse_ecrRepositoryPrefix,
    createPullThroughCacheRuleResponse_registryId,
    createPullThroughCacheRuleResponse_upstreamRegistryUrl,
    createPullThroughCacheRuleResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ECR.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreatePullThroughCacheRule' smart constructor.
data CreatePullThroughCacheRule = CreatePullThroughCacheRule'
  { -- | The Amazon Web Services account ID associated with the registry to
    -- create the pull through cache rule for. If you do not specify a
    -- registry, the default registry is assumed.
    CreatePullThroughCacheRule -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The repository name prefix to use when caching images from the source
    -- registry.
    CreatePullThroughCacheRule -> Text
ecrRepositoryPrefix :: Prelude.Text,
    -- | The registry URL of the upstream public registry to use as the source
    -- for the pull through cache rule.
    CreatePullThroughCacheRule -> Text
upstreamRegistryUrl :: Prelude.Text
  }
  deriving (CreatePullThroughCacheRule -> CreatePullThroughCacheRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePullThroughCacheRule -> CreatePullThroughCacheRule -> Bool
$c/= :: CreatePullThroughCacheRule -> CreatePullThroughCacheRule -> Bool
== :: CreatePullThroughCacheRule -> CreatePullThroughCacheRule -> Bool
$c== :: CreatePullThroughCacheRule -> CreatePullThroughCacheRule -> Bool
Prelude.Eq, ReadPrec [CreatePullThroughCacheRule]
ReadPrec CreatePullThroughCacheRule
Int -> ReadS CreatePullThroughCacheRule
ReadS [CreatePullThroughCacheRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePullThroughCacheRule]
$creadListPrec :: ReadPrec [CreatePullThroughCacheRule]
readPrec :: ReadPrec CreatePullThroughCacheRule
$creadPrec :: ReadPrec CreatePullThroughCacheRule
readList :: ReadS [CreatePullThroughCacheRule]
$creadList :: ReadS [CreatePullThroughCacheRule]
readsPrec :: Int -> ReadS CreatePullThroughCacheRule
$creadsPrec :: Int -> ReadS CreatePullThroughCacheRule
Prelude.Read, Int -> CreatePullThroughCacheRule -> ShowS
[CreatePullThroughCacheRule] -> ShowS
CreatePullThroughCacheRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePullThroughCacheRule] -> ShowS
$cshowList :: [CreatePullThroughCacheRule] -> ShowS
show :: CreatePullThroughCacheRule -> String
$cshow :: CreatePullThroughCacheRule -> String
showsPrec :: Int -> CreatePullThroughCacheRule -> ShowS
$cshowsPrec :: Int -> CreatePullThroughCacheRule -> ShowS
Prelude.Show, forall x.
Rep CreatePullThroughCacheRule x -> CreatePullThroughCacheRule
forall x.
CreatePullThroughCacheRule -> Rep CreatePullThroughCacheRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreatePullThroughCacheRule x -> CreatePullThroughCacheRule
$cfrom :: forall x.
CreatePullThroughCacheRule -> Rep CreatePullThroughCacheRule x
Prelude.Generic)

-- |
-- Create a value of 'CreatePullThroughCacheRule' 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:
--
-- 'registryId', 'createPullThroughCacheRule_registryId' - The Amazon Web Services account ID associated with the registry to
-- create the pull through cache rule for. If you do not specify a
-- registry, the default registry is assumed.
--
-- 'ecrRepositoryPrefix', 'createPullThroughCacheRule_ecrRepositoryPrefix' - The repository name prefix to use when caching images from the source
-- registry.
--
-- 'upstreamRegistryUrl', 'createPullThroughCacheRule_upstreamRegistryUrl' - The registry URL of the upstream public registry to use as the source
-- for the pull through cache rule.
newCreatePullThroughCacheRule ::
  -- | 'ecrRepositoryPrefix'
  Prelude.Text ->
  -- | 'upstreamRegistryUrl'
  Prelude.Text ->
  CreatePullThroughCacheRule
newCreatePullThroughCacheRule :: Text -> Text -> CreatePullThroughCacheRule
newCreatePullThroughCacheRule
  Text
pEcrRepositoryPrefix_
  Text
pUpstreamRegistryUrl_ =
    CreatePullThroughCacheRule'
      { $sel:registryId:CreatePullThroughCacheRule' :: Maybe Text
registryId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: Text
ecrRepositoryPrefix = Text
pEcrRepositoryPrefix_,
        $sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: Text
upstreamRegistryUrl = Text
pUpstreamRegistryUrl_
      }

-- | The Amazon Web Services account ID associated with the registry to
-- create the pull through cache rule for. If you do not specify a
-- registry, the default registry is assumed.
createPullThroughCacheRule_registryId :: Lens.Lens' CreatePullThroughCacheRule (Prelude.Maybe Prelude.Text)
createPullThroughCacheRule_registryId :: Lens' CreatePullThroughCacheRule (Maybe Text)
createPullThroughCacheRule_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRule' {Maybe Text
registryId :: Maybe Text
$sel:registryId:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: CreatePullThroughCacheRule
s@CreatePullThroughCacheRule' {} Maybe Text
a -> CreatePullThroughCacheRule
s {$sel:registryId:CreatePullThroughCacheRule' :: Maybe Text
registryId = Maybe Text
a} :: CreatePullThroughCacheRule)

-- | The repository name prefix to use when caching images from the source
-- registry.
createPullThroughCacheRule_ecrRepositoryPrefix :: Lens.Lens' CreatePullThroughCacheRule Prelude.Text
createPullThroughCacheRule_ecrRepositoryPrefix :: Lens' CreatePullThroughCacheRule Text
createPullThroughCacheRule_ecrRepositoryPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRule' {Text
ecrRepositoryPrefix :: Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
ecrRepositoryPrefix} -> Text
ecrRepositoryPrefix) (\s :: CreatePullThroughCacheRule
s@CreatePullThroughCacheRule' {} Text
a -> CreatePullThroughCacheRule
s {$sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: Text
ecrRepositoryPrefix = Text
a} :: CreatePullThroughCacheRule)

-- | The registry URL of the upstream public registry to use as the source
-- for the pull through cache rule.
createPullThroughCacheRule_upstreamRegistryUrl :: Lens.Lens' CreatePullThroughCacheRule Prelude.Text
createPullThroughCacheRule_upstreamRegistryUrl :: Lens' CreatePullThroughCacheRule Text
createPullThroughCacheRule_upstreamRegistryUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRule' {Text
upstreamRegistryUrl :: Text
$sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
upstreamRegistryUrl} -> Text
upstreamRegistryUrl) (\s :: CreatePullThroughCacheRule
s@CreatePullThroughCacheRule' {} Text
a -> CreatePullThroughCacheRule
s {$sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: Text
upstreamRegistryUrl = Text
a} :: CreatePullThroughCacheRule)

instance Core.AWSRequest CreatePullThroughCacheRule where
  type
    AWSResponse CreatePullThroughCacheRule =
      CreatePullThroughCacheRuleResponse
  request :: (Service -> Service)
-> CreatePullThroughCacheRule -> Request CreatePullThroughCacheRule
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 CreatePullThroughCacheRule
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreatePullThroughCacheRule)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> CreatePullThroughCacheRuleResponse
CreatePullThroughCacheRuleResponse'
            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
"createdAt")
            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
"ecrRepositoryPrefix")
            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
"registryId")
            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
"upstreamRegistryUrl")
            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 CreatePullThroughCacheRule where
  hashWithSalt :: Int -> CreatePullThroughCacheRule -> Int
hashWithSalt Int
_salt CreatePullThroughCacheRule' {Maybe Text
Text
upstreamRegistryUrl :: Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:registryId:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
registryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ecrRepositoryPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
upstreamRegistryUrl

instance Prelude.NFData CreatePullThroughCacheRule where
  rnf :: CreatePullThroughCacheRule -> ()
rnf CreatePullThroughCacheRule' {Maybe Text
Text
upstreamRegistryUrl :: Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:registryId:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
registryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ecrRepositoryPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
upstreamRegistryUrl

instance Data.ToHeaders CreatePullThroughCacheRule where
  toHeaders :: CreatePullThroughCacheRule -> 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
"AmazonEC2ContainerRegistry_V20150921.CreatePullThroughCacheRule" ::
                          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 CreatePullThroughCacheRule where
  toJSON :: CreatePullThroughCacheRule -> Value
toJSON CreatePullThroughCacheRule' {Maybe Text
Text
upstreamRegistryUrl :: Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:upstreamRegistryUrl:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Text
$sel:registryId:CreatePullThroughCacheRule' :: CreatePullThroughCacheRule -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"registryId" 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
registryId,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ecrRepositoryPrefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ecrRepositoryPrefix),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"upstreamRegistryUrl" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
upstreamRegistryUrl)
          ]
      )

instance Data.ToPath CreatePullThroughCacheRule where
  toPath :: CreatePullThroughCacheRule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreatePullThroughCacheRuleResponse' smart constructor.
data CreatePullThroughCacheRuleResponse = CreatePullThroughCacheRuleResponse'
  { -- | The date and time, in JavaScript date format, when the pull through
    -- cache rule was created.
    CreatePullThroughCacheRuleResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The Amazon ECR repository prefix associated with the pull through cache
    -- rule.
    CreatePullThroughCacheRuleResponse -> Maybe Text
ecrRepositoryPrefix :: Prelude.Maybe Prelude.Text,
    -- | The registry ID associated with the request.
    CreatePullThroughCacheRuleResponse -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The upstream registry URL associated with the pull through cache rule.
    CreatePullThroughCacheRuleResponse -> Maybe Text
upstreamRegistryUrl :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreatePullThroughCacheRuleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreatePullThroughCacheRuleResponse
-> CreatePullThroughCacheRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePullThroughCacheRuleResponse
-> CreatePullThroughCacheRuleResponse -> Bool
$c/= :: CreatePullThroughCacheRuleResponse
-> CreatePullThroughCacheRuleResponse -> Bool
== :: CreatePullThroughCacheRuleResponse
-> CreatePullThroughCacheRuleResponse -> Bool
$c== :: CreatePullThroughCacheRuleResponse
-> CreatePullThroughCacheRuleResponse -> Bool
Prelude.Eq, ReadPrec [CreatePullThroughCacheRuleResponse]
ReadPrec CreatePullThroughCacheRuleResponse
Int -> ReadS CreatePullThroughCacheRuleResponse
ReadS [CreatePullThroughCacheRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePullThroughCacheRuleResponse]
$creadListPrec :: ReadPrec [CreatePullThroughCacheRuleResponse]
readPrec :: ReadPrec CreatePullThroughCacheRuleResponse
$creadPrec :: ReadPrec CreatePullThroughCacheRuleResponse
readList :: ReadS [CreatePullThroughCacheRuleResponse]
$creadList :: ReadS [CreatePullThroughCacheRuleResponse]
readsPrec :: Int -> ReadS CreatePullThroughCacheRuleResponse
$creadsPrec :: Int -> ReadS CreatePullThroughCacheRuleResponse
Prelude.Read, Int -> CreatePullThroughCacheRuleResponse -> ShowS
[CreatePullThroughCacheRuleResponse] -> ShowS
CreatePullThroughCacheRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePullThroughCacheRuleResponse] -> ShowS
$cshowList :: [CreatePullThroughCacheRuleResponse] -> ShowS
show :: CreatePullThroughCacheRuleResponse -> String
$cshow :: CreatePullThroughCacheRuleResponse -> String
showsPrec :: Int -> CreatePullThroughCacheRuleResponse -> ShowS
$cshowsPrec :: Int -> CreatePullThroughCacheRuleResponse -> ShowS
Prelude.Show, forall x.
Rep CreatePullThroughCacheRuleResponse x
-> CreatePullThroughCacheRuleResponse
forall x.
CreatePullThroughCacheRuleResponse
-> Rep CreatePullThroughCacheRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreatePullThroughCacheRuleResponse x
-> CreatePullThroughCacheRuleResponse
$cfrom :: forall x.
CreatePullThroughCacheRuleResponse
-> Rep CreatePullThroughCacheRuleResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreatePullThroughCacheRuleResponse' 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:
--
-- 'createdAt', 'createPullThroughCacheRuleResponse_createdAt' - The date and time, in JavaScript date format, when the pull through
-- cache rule was created.
--
-- 'ecrRepositoryPrefix', 'createPullThroughCacheRuleResponse_ecrRepositoryPrefix' - The Amazon ECR repository prefix associated with the pull through cache
-- rule.
--
-- 'registryId', 'createPullThroughCacheRuleResponse_registryId' - The registry ID associated with the request.
--
-- 'upstreamRegistryUrl', 'createPullThroughCacheRuleResponse_upstreamRegistryUrl' - The upstream registry URL associated with the pull through cache rule.
--
-- 'httpStatus', 'createPullThroughCacheRuleResponse_httpStatus' - The response's http status code.
newCreatePullThroughCacheRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreatePullThroughCacheRuleResponse
newCreatePullThroughCacheRuleResponse :: Int -> CreatePullThroughCacheRuleResponse
newCreatePullThroughCacheRuleResponse Int
pHttpStatus_ =
  CreatePullThroughCacheRuleResponse'
    { $sel:createdAt:CreatePullThroughCacheRuleResponse' :: Maybe POSIX
createdAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ecrRepositoryPrefix:CreatePullThroughCacheRuleResponse' :: Maybe Text
ecrRepositoryPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:CreatePullThroughCacheRuleResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:upstreamRegistryUrl:CreatePullThroughCacheRuleResponse' :: Maybe Text
upstreamRegistryUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreatePullThroughCacheRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The date and time, in JavaScript date format, when the pull through
-- cache rule was created.
createPullThroughCacheRuleResponse_createdAt :: Lens.Lens' CreatePullThroughCacheRuleResponse (Prelude.Maybe Prelude.UTCTime)
createPullThroughCacheRuleResponse_createdAt :: Lens' CreatePullThroughCacheRuleResponse (Maybe UTCTime)
createPullThroughCacheRuleResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRuleResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: CreatePullThroughCacheRuleResponse
s@CreatePullThroughCacheRuleResponse' {} Maybe POSIX
a -> CreatePullThroughCacheRuleResponse
s {$sel:createdAt:CreatePullThroughCacheRuleResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: CreatePullThroughCacheRuleResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Amazon ECR repository prefix associated with the pull through cache
-- rule.
createPullThroughCacheRuleResponse_ecrRepositoryPrefix :: Lens.Lens' CreatePullThroughCacheRuleResponse (Prelude.Maybe Prelude.Text)
createPullThroughCacheRuleResponse_ecrRepositoryPrefix :: Lens' CreatePullThroughCacheRuleResponse (Maybe Text)
createPullThroughCacheRuleResponse_ecrRepositoryPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRuleResponse' {Maybe Text
ecrRepositoryPrefix :: Maybe Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
ecrRepositoryPrefix} -> Maybe Text
ecrRepositoryPrefix) (\s :: CreatePullThroughCacheRuleResponse
s@CreatePullThroughCacheRuleResponse' {} Maybe Text
a -> CreatePullThroughCacheRuleResponse
s {$sel:ecrRepositoryPrefix:CreatePullThroughCacheRuleResponse' :: Maybe Text
ecrRepositoryPrefix = Maybe Text
a} :: CreatePullThroughCacheRuleResponse)

-- | The registry ID associated with the request.
createPullThroughCacheRuleResponse_registryId :: Lens.Lens' CreatePullThroughCacheRuleResponse (Prelude.Maybe Prelude.Text)
createPullThroughCacheRuleResponse_registryId :: Lens' CreatePullThroughCacheRuleResponse (Maybe Text)
createPullThroughCacheRuleResponse_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRuleResponse' {Maybe Text
registryId :: Maybe Text
$sel:registryId:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: CreatePullThroughCacheRuleResponse
s@CreatePullThroughCacheRuleResponse' {} Maybe Text
a -> CreatePullThroughCacheRuleResponse
s {$sel:registryId:CreatePullThroughCacheRuleResponse' :: Maybe Text
registryId = Maybe Text
a} :: CreatePullThroughCacheRuleResponse)

-- | The upstream registry URL associated with the pull through cache rule.
createPullThroughCacheRuleResponse_upstreamRegistryUrl :: Lens.Lens' CreatePullThroughCacheRuleResponse (Prelude.Maybe Prelude.Text)
createPullThroughCacheRuleResponse_upstreamRegistryUrl :: Lens' CreatePullThroughCacheRuleResponse (Maybe Text)
createPullThroughCacheRuleResponse_upstreamRegistryUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePullThroughCacheRuleResponse' {Maybe Text
upstreamRegistryUrl :: Maybe Text
$sel:upstreamRegistryUrl:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
upstreamRegistryUrl} -> Maybe Text
upstreamRegistryUrl) (\s :: CreatePullThroughCacheRuleResponse
s@CreatePullThroughCacheRuleResponse' {} Maybe Text
a -> CreatePullThroughCacheRuleResponse
s {$sel:upstreamRegistryUrl:CreatePullThroughCacheRuleResponse' :: Maybe Text
upstreamRegistryUrl = Maybe Text
a} :: CreatePullThroughCacheRuleResponse)

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

instance
  Prelude.NFData
    CreatePullThroughCacheRuleResponse
  where
  rnf :: CreatePullThroughCacheRuleResponse -> ()
rnf CreatePullThroughCacheRuleResponse' {Int
Maybe Text
Maybe POSIX
httpStatus :: Int
upstreamRegistryUrl :: Maybe Text
registryId :: Maybe Text
ecrRepositoryPrefix :: Maybe Text
createdAt :: Maybe POSIX
$sel:httpStatus:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Int
$sel:upstreamRegistryUrl:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
$sel:registryId:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
$sel:ecrRepositoryPrefix:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe Text
$sel:createdAt:CreatePullThroughCacheRuleResponse' :: CreatePullThroughCacheRuleResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ecrRepositoryPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
registryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
upstreamRegistryUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus