{-# 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.DataSync.Types.LocationListEntry
-- 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.DataSync.Types.LocationListEntry 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

-- | Represents a single entry in a list of locations. @LocationListEntry@
-- returns an array that contains a list of locations when the
-- <https://docs.aws.amazon.com/datasync/latest/userguide/API_ListLocations.html ListLocations>
-- operation is called.
--
-- /See:/ 'newLocationListEntry' smart constructor.
data LocationListEntry = LocationListEntry'
  { -- | The Amazon Resource Name (ARN) of the location. For Network File System
    -- (NFS) or Amazon EFS, the location is the export path. For Amazon S3, the
    -- location is the prefix path that you want to mount and use as the root
    -- of the location.
    LocationListEntry -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | Represents a list of URIs of a location. @LocationUri@ returns an array
    -- that contains a list of locations when the
    -- <https://docs.aws.amazon.com/datasync/latest/userguide/API_ListLocations.html ListLocations>
    -- operation is called.
    --
    -- Format: @TYPE:\/\/GLOBAL_ID\/SUBDIR@.
    --
    -- TYPE designates the type of location (for example, @nfs@ or @s3@).
    --
    -- GLOBAL_ID is the globally unique identifier of the resource that backs
    -- the location. An example for EFS is @us-east-2.fs-abcd1234@. An example
    -- for Amazon S3 is the bucket name, such as @myBucket@. An example for NFS
    -- is a valid IPv4 address or a hostname that is compliant with Domain Name
    -- Service (DNS).
    --
    -- SUBDIR is a valid file system path, delimited by forward slashes as is
    -- the *nix convention. For NFS and Amazon EFS, it\'s the export path to
    -- mount the location. For Amazon S3, it\'s the prefix path that you mount
    -- to and treat as the root of the location.
    LocationListEntry -> Maybe Text
locationUri :: Prelude.Maybe Prelude.Text
  }
  deriving (LocationListEntry -> LocationListEntry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocationListEntry -> LocationListEntry -> Bool
$c/= :: LocationListEntry -> LocationListEntry -> Bool
== :: LocationListEntry -> LocationListEntry -> Bool
$c== :: LocationListEntry -> LocationListEntry -> Bool
Prelude.Eq, ReadPrec [LocationListEntry]
ReadPrec LocationListEntry
Int -> ReadS LocationListEntry
ReadS [LocationListEntry]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LocationListEntry]
$creadListPrec :: ReadPrec [LocationListEntry]
readPrec :: ReadPrec LocationListEntry
$creadPrec :: ReadPrec LocationListEntry
readList :: ReadS [LocationListEntry]
$creadList :: ReadS [LocationListEntry]
readsPrec :: Int -> ReadS LocationListEntry
$creadsPrec :: Int -> ReadS LocationListEntry
Prelude.Read, Int -> LocationListEntry -> ShowS
[LocationListEntry] -> ShowS
LocationListEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LocationListEntry] -> ShowS
$cshowList :: [LocationListEntry] -> ShowS
show :: LocationListEntry -> String
$cshow :: LocationListEntry -> String
showsPrec :: Int -> LocationListEntry -> ShowS
$cshowsPrec :: Int -> LocationListEntry -> ShowS
Prelude.Show, forall x. Rep LocationListEntry x -> LocationListEntry
forall x. LocationListEntry -> Rep LocationListEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LocationListEntry x -> LocationListEntry
$cfrom :: forall x. LocationListEntry -> Rep LocationListEntry x
Prelude.Generic)

-- |
-- Create a value of 'LocationListEntry' 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:
--
-- 'locationArn', 'locationListEntry_locationArn' - The Amazon Resource Name (ARN) of the location. For Network File System
-- (NFS) or Amazon EFS, the location is the export path. For Amazon S3, the
-- location is the prefix path that you want to mount and use as the root
-- of the location.
--
-- 'locationUri', 'locationListEntry_locationUri' - Represents a list of URIs of a location. @LocationUri@ returns an array
-- that contains a list of locations when the
-- <https://docs.aws.amazon.com/datasync/latest/userguide/API_ListLocations.html ListLocations>
-- operation is called.
--
-- Format: @TYPE:\/\/GLOBAL_ID\/SUBDIR@.
--
-- TYPE designates the type of location (for example, @nfs@ or @s3@).
--
-- GLOBAL_ID is the globally unique identifier of the resource that backs
-- the location. An example for EFS is @us-east-2.fs-abcd1234@. An example
-- for Amazon S3 is the bucket name, such as @myBucket@. An example for NFS
-- is a valid IPv4 address or a hostname that is compliant with Domain Name
-- Service (DNS).
--
-- SUBDIR is a valid file system path, delimited by forward slashes as is
-- the *nix convention. For NFS and Amazon EFS, it\'s the export path to
-- mount the location. For Amazon S3, it\'s the prefix path that you mount
-- to and treat as the root of the location.
newLocationListEntry ::
  LocationListEntry
newLocationListEntry :: LocationListEntry
newLocationListEntry =
  LocationListEntry'
    { $sel:locationArn:LocationListEntry' :: Maybe Text
locationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:locationUri:LocationListEntry' :: Maybe Text
locationUri = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the location. For Network File System
-- (NFS) or Amazon EFS, the location is the export path. For Amazon S3, the
-- location is the prefix path that you want to mount and use as the root
-- of the location.
locationListEntry_locationArn :: Lens.Lens' LocationListEntry (Prelude.Maybe Prelude.Text)
locationListEntry_locationArn :: Lens' LocationListEntry (Maybe Text)
locationListEntry_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LocationListEntry' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:LocationListEntry' :: LocationListEntry -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: LocationListEntry
s@LocationListEntry' {} Maybe Text
a -> LocationListEntry
s {$sel:locationArn:LocationListEntry' :: Maybe Text
locationArn = Maybe Text
a} :: LocationListEntry)

-- | Represents a list of URIs of a location. @LocationUri@ returns an array
-- that contains a list of locations when the
-- <https://docs.aws.amazon.com/datasync/latest/userguide/API_ListLocations.html ListLocations>
-- operation is called.
--
-- Format: @TYPE:\/\/GLOBAL_ID\/SUBDIR@.
--
-- TYPE designates the type of location (for example, @nfs@ or @s3@).
--
-- GLOBAL_ID is the globally unique identifier of the resource that backs
-- the location. An example for EFS is @us-east-2.fs-abcd1234@. An example
-- for Amazon S3 is the bucket name, such as @myBucket@. An example for NFS
-- is a valid IPv4 address or a hostname that is compliant with Domain Name
-- Service (DNS).
--
-- SUBDIR is a valid file system path, delimited by forward slashes as is
-- the *nix convention. For NFS and Amazon EFS, it\'s the export path to
-- mount the location. For Amazon S3, it\'s the prefix path that you mount
-- to and treat as the root of the location.
locationListEntry_locationUri :: Lens.Lens' LocationListEntry (Prelude.Maybe Prelude.Text)
locationListEntry_locationUri :: Lens' LocationListEntry (Maybe Text)
locationListEntry_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LocationListEntry' {Maybe Text
locationUri :: Maybe Text
$sel:locationUri:LocationListEntry' :: LocationListEntry -> Maybe Text
locationUri} -> Maybe Text
locationUri) (\s :: LocationListEntry
s@LocationListEntry' {} Maybe Text
a -> LocationListEntry
s {$sel:locationUri:LocationListEntry' :: Maybe Text
locationUri = Maybe Text
a} :: LocationListEntry)

instance Data.FromJSON LocationListEntry where
  parseJSON :: Value -> Parser LocationListEntry
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"LocationListEntry"
      ( \Object
x ->
          Maybe Text -> Maybe Text -> LocationListEntry
LocationListEntry'
            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
"LocationArn")
            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
"LocationUri")
      )

instance Prelude.Hashable LocationListEntry where
  hashWithSalt :: Int -> LocationListEntry -> Int
hashWithSalt Int
_salt LocationListEntry' {Maybe Text
locationUri :: Maybe Text
locationArn :: Maybe Text
$sel:locationUri:LocationListEntry' :: LocationListEntry -> Maybe Text
$sel:locationArn:LocationListEntry' :: LocationListEntry -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
locationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
locationUri

instance Prelude.NFData LocationListEntry where
  rnf :: LocationListEntry -> ()
rnf LocationListEntry' {Maybe Text
locationUri :: Maybe Text
locationArn :: Maybe Text
$sel:locationUri:LocationListEntry' :: LocationListEntry -> Maybe Text
$sel:locationArn:LocationListEntry' :: LocationListEntry -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
locationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
locationUri