{-# 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.DataSync.CreateLocationFsxOpenZfs
-- 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 an endpoint for an Amazon FSx for OpenZFS file system that
-- DataSync can access for a transfer. For more information, see
-- <https://docs.aws.amazon.com/datasync/latest/userguide/create-openzfs-location.html Creating a location for FSx for OpenZFS>.
--
-- Request parameters related to @SMB@ aren\'t supported with the
-- @CreateLocationFsxOpenZfs@ operation.
module Amazonka.DataSync.CreateLocationFsxOpenZfs
  ( -- * Creating a Request
    CreateLocationFsxOpenZfs (..),
    newCreateLocationFsxOpenZfs,

    -- * Request Lenses
    createLocationFsxOpenZfs_subdirectory,
    createLocationFsxOpenZfs_tags,
    createLocationFsxOpenZfs_fsxFilesystemArn,
    createLocationFsxOpenZfs_protocol,
    createLocationFsxOpenZfs_securityGroupArns,

    -- * Destructuring the Response
    CreateLocationFsxOpenZfsResponse (..),
    newCreateLocationFsxOpenZfsResponse,

    -- * Response Lenses
    createLocationFsxOpenZfsResponse_locationArn,
    createLocationFsxOpenZfsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateLocationFsxOpenZfs' smart constructor.
data CreateLocationFsxOpenZfs = CreateLocationFsxOpenZfs'
  { -- | A subdirectory in the location\'s path that must begin with @\/fsx@.
    -- DataSync uses this subdirectory to read or write data (depending on
    -- whether the file system is a source or destination location).
    CreateLocationFsxOpenZfs -> Maybe Text
subdirectory :: Prelude.Maybe Prelude.Text,
    -- | The key-value pair that represents a tag that you want to add to the
    -- resource. The value can be an empty string. This value helps you manage,
    -- filter, and search for your resources. We recommend that you create a
    -- name tag for your location.
    CreateLocationFsxOpenZfs -> Maybe [TagListEntry]
tags :: Prelude.Maybe [TagListEntry],
    -- | The Amazon Resource Name (ARN) of the FSx for OpenZFS file system.
    CreateLocationFsxOpenZfs -> Text
fsxFilesystemArn :: Prelude.Text,
    -- | The type of protocol that DataSync uses to access your file system.
    CreateLocationFsxOpenZfs -> FsxProtocol
protocol :: FsxProtocol,
    -- | The ARNs of the security groups that are used to configure the FSx for
    -- OpenZFS file system.
    CreateLocationFsxOpenZfs -> NonEmpty Text
securityGroupArns :: Prelude.NonEmpty Prelude.Text
  }
  deriving (CreateLocationFsxOpenZfs -> CreateLocationFsxOpenZfs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLocationFsxOpenZfs -> CreateLocationFsxOpenZfs -> Bool
$c/= :: CreateLocationFsxOpenZfs -> CreateLocationFsxOpenZfs -> Bool
== :: CreateLocationFsxOpenZfs -> CreateLocationFsxOpenZfs -> Bool
$c== :: CreateLocationFsxOpenZfs -> CreateLocationFsxOpenZfs -> Bool
Prelude.Eq, Int -> CreateLocationFsxOpenZfs -> ShowS
[CreateLocationFsxOpenZfs] -> ShowS
CreateLocationFsxOpenZfs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLocationFsxOpenZfs] -> ShowS
$cshowList :: [CreateLocationFsxOpenZfs] -> ShowS
show :: CreateLocationFsxOpenZfs -> String
$cshow :: CreateLocationFsxOpenZfs -> String
showsPrec :: Int -> CreateLocationFsxOpenZfs -> ShowS
$cshowsPrec :: Int -> CreateLocationFsxOpenZfs -> ShowS
Prelude.Show, forall x.
Rep CreateLocationFsxOpenZfs x -> CreateLocationFsxOpenZfs
forall x.
CreateLocationFsxOpenZfs -> Rep CreateLocationFsxOpenZfs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLocationFsxOpenZfs x -> CreateLocationFsxOpenZfs
$cfrom :: forall x.
CreateLocationFsxOpenZfs -> Rep CreateLocationFsxOpenZfs x
Prelude.Generic)

-- |
-- Create a value of 'CreateLocationFsxOpenZfs' 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:
--
-- 'subdirectory', 'createLocationFsxOpenZfs_subdirectory' - A subdirectory in the location\'s path that must begin with @\/fsx@.
-- DataSync uses this subdirectory to read or write data (depending on
-- whether the file system is a source or destination location).
--
-- 'tags', 'createLocationFsxOpenZfs_tags' - The key-value pair that represents a tag that you want to add to the
-- resource. The value can be an empty string. This value helps you manage,
-- filter, and search for your resources. We recommend that you create a
-- name tag for your location.
--
-- 'fsxFilesystemArn', 'createLocationFsxOpenZfs_fsxFilesystemArn' - The Amazon Resource Name (ARN) of the FSx for OpenZFS file system.
--
-- 'protocol', 'createLocationFsxOpenZfs_protocol' - The type of protocol that DataSync uses to access your file system.
--
-- 'securityGroupArns', 'createLocationFsxOpenZfs_securityGroupArns' - The ARNs of the security groups that are used to configure the FSx for
-- OpenZFS file system.
newCreateLocationFsxOpenZfs ::
  -- | 'fsxFilesystemArn'
  Prelude.Text ->
  -- | 'protocol'
  FsxProtocol ->
  -- | 'securityGroupArns'
  Prelude.NonEmpty Prelude.Text ->
  CreateLocationFsxOpenZfs
newCreateLocationFsxOpenZfs :: Text -> FsxProtocol -> NonEmpty Text -> CreateLocationFsxOpenZfs
newCreateLocationFsxOpenZfs
  Text
pFsxFilesystemArn_
  FsxProtocol
pProtocol_
  NonEmpty Text
pSecurityGroupArns_ =
    CreateLocationFsxOpenZfs'
      { $sel:subdirectory:CreateLocationFsxOpenZfs' :: Maybe Text
subdirectory =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateLocationFsxOpenZfs' :: Maybe [TagListEntry]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: Text
fsxFilesystemArn = Text
pFsxFilesystemArn_,
        $sel:protocol:CreateLocationFsxOpenZfs' :: FsxProtocol
protocol = FsxProtocol
pProtocol_,
        $sel:securityGroupArns:CreateLocationFsxOpenZfs' :: NonEmpty Text
securityGroupArns =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pSecurityGroupArns_
      }

-- | A subdirectory in the location\'s path that must begin with @\/fsx@.
-- DataSync uses this subdirectory to read or write data (depending on
-- whether the file system is a source or destination location).
createLocationFsxOpenZfs_subdirectory :: Lens.Lens' CreateLocationFsxOpenZfs (Prelude.Maybe Prelude.Text)
createLocationFsxOpenZfs_subdirectory :: Lens' CreateLocationFsxOpenZfs (Maybe Text)
createLocationFsxOpenZfs_subdirectory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfs' {Maybe Text
subdirectory :: Maybe Text
$sel:subdirectory:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe Text
subdirectory} -> Maybe Text
subdirectory) (\s :: CreateLocationFsxOpenZfs
s@CreateLocationFsxOpenZfs' {} Maybe Text
a -> CreateLocationFsxOpenZfs
s {$sel:subdirectory:CreateLocationFsxOpenZfs' :: Maybe Text
subdirectory = Maybe Text
a} :: CreateLocationFsxOpenZfs)

-- | The key-value pair that represents a tag that you want to add to the
-- resource. The value can be an empty string. This value helps you manage,
-- filter, and search for your resources. We recommend that you create a
-- name tag for your location.
createLocationFsxOpenZfs_tags :: Lens.Lens' CreateLocationFsxOpenZfs (Prelude.Maybe [TagListEntry])
createLocationFsxOpenZfs_tags :: Lens' CreateLocationFsxOpenZfs (Maybe [TagListEntry])
createLocationFsxOpenZfs_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfs' {Maybe [TagListEntry]
tags :: Maybe [TagListEntry]
$sel:tags:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe [TagListEntry]
tags} -> Maybe [TagListEntry]
tags) (\s :: CreateLocationFsxOpenZfs
s@CreateLocationFsxOpenZfs' {} Maybe [TagListEntry]
a -> CreateLocationFsxOpenZfs
s {$sel:tags:CreateLocationFsxOpenZfs' :: Maybe [TagListEntry]
tags = Maybe [TagListEntry]
a} :: CreateLocationFsxOpenZfs) 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 Amazon Resource Name (ARN) of the FSx for OpenZFS file system.
createLocationFsxOpenZfs_fsxFilesystemArn :: Lens.Lens' CreateLocationFsxOpenZfs Prelude.Text
createLocationFsxOpenZfs_fsxFilesystemArn :: Lens' CreateLocationFsxOpenZfs Text
createLocationFsxOpenZfs_fsxFilesystemArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfs' {Text
fsxFilesystemArn :: Text
$sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Text
fsxFilesystemArn} -> Text
fsxFilesystemArn) (\s :: CreateLocationFsxOpenZfs
s@CreateLocationFsxOpenZfs' {} Text
a -> CreateLocationFsxOpenZfs
s {$sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: Text
fsxFilesystemArn = Text
a} :: CreateLocationFsxOpenZfs)

-- | The type of protocol that DataSync uses to access your file system.
createLocationFsxOpenZfs_protocol :: Lens.Lens' CreateLocationFsxOpenZfs FsxProtocol
createLocationFsxOpenZfs_protocol :: Lens' CreateLocationFsxOpenZfs FsxProtocol
createLocationFsxOpenZfs_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfs' {FsxProtocol
protocol :: FsxProtocol
$sel:protocol:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> FsxProtocol
protocol} -> FsxProtocol
protocol) (\s :: CreateLocationFsxOpenZfs
s@CreateLocationFsxOpenZfs' {} FsxProtocol
a -> CreateLocationFsxOpenZfs
s {$sel:protocol:CreateLocationFsxOpenZfs' :: FsxProtocol
protocol = FsxProtocol
a} :: CreateLocationFsxOpenZfs)

-- | The ARNs of the security groups that are used to configure the FSx for
-- OpenZFS file system.
createLocationFsxOpenZfs_securityGroupArns :: Lens.Lens' CreateLocationFsxOpenZfs (Prelude.NonEmpty Prelude.Text)
createLocationFsxOpenZfs_securityGroupArns :: Lens' CreateLocationFsxOpenZfs (NonEmpty Text)
createLocationFsxOpenZfs_securityGroupArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfs' {NonEmpty Text
securityGroupArns :: NonEmpty Text
$sel:securityGroupArns:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> NonEmpty Text
securityGroupArns} -> NonEmpty Text
securityGroupArns) (\s :: CreateLocationFsxOpenZfs
s@CreateLocationFsxOpenZfs' {} NonEmpty Text
a -> CreateLocationFsxOpenZfs
s {$sel:securityGroupArns:CreateLocationFsxOpenZfs' :: NonEmpty Text
securityGroupArns = NonEmpty Text
a} :: CreateLocationFsxOpenZfs) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateLocationFsxOpenZfs where
  type
    AWSResponse CreateLocationFsxOpenZfs =
      CreateLocationFsxOpenZfsResponse
  request :: (Service -> Service)
-> CreateLocationFsxOpenZfs -> Request CreateLocationFsxOpenZfs
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 CreateLocationFsxOpenZfs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateLocationFsxOpenZfs)))
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 -> Int -> CreateLocationFsxOpenZfsResponse
CreateLocationFsxOpenZfsResponse'
            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
"LocationArn")
            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 CreateLocationFsxOpenZfs where
  hashWithSalt :: Int -> CreateLocationFsxOpenZfs -> Int
hashWithSalt Int
_salt CreateLocationFsxOpenZfs' {Maybe [TagListEntry]
Maybe Text
NonEmpty Text
Text
FsxProtocol
securityGroupArns :: NonEmpty Text
protocol :: FsxProtocol
fsxFilesystemArn :: Text
tags :: Maybe [TagListEntry]
subdirectory :: Maybe Text
$sel:securityGroupArns:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> NonEmpty Text
$sel:protocol:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> FsxProtocol
$sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Text
$sel:tags:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe [TagListEntry]
$sel:subdirectory:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subdirectory
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TagListEntry]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fsxFilesystemArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` FsxProtocol
protocol
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
securityGroupArns

instance Prelude.NFData CreateLocationFsxOpenZfs where
  rnf :: CreateLocationFsxOpenZfs -> ()
rnf CreateLocationFsxOpenZfs' {Maybe [TagListEntry]
Maybe Text
NonEmpty Text
Text
FsxProtocol
securityGroupArns :: NonEmpty Text
protocol :: FsxProtocol
fsxFilesystemArn :: Text
tags :: Maybe [TagListEntry]
subdirectory :: Maybe Text
$sel:securityGroupArns:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> NonEmpty Text
$sel:protocol:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> FsxProtocol
$sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Text
$sel:tags:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe [TagListEntry]
$sel:subdirectory:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subdirectory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TagListEntry]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fsxFilesystemArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf FsxProtocol
protocol
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
securityGroupArns

instance Data.ToHeaders CreateLocationFsxOpenZfs where
  toHeaders :: CreateLocationFsxOpenZfs -> 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
"FmrsService.CreateLocationFsxOpenZfs" ::
                          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 CreateLocationFsxOpenZfs where
  toJSON :: CreateLocationFsxOpenZfs -> Value
toJSON CreateLocationFsxOpenZfs' {Maybe [TagListEntry]
Maybe Text
NonEmpty Text
Text
FsxProtocol
securityGroupArns :: NonEmpty Text
protocol :: FsxProtocol
fsxFilesystemArn :: Text
tags :: Maybe [TagListEntry]
subdirectory :: Maybe Text
$sel:securityGroupArns:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> NonEmpty Text
$sel:protocol:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> FsxProtocol
$sel:fsxFilesystemArn:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Text
$sel:tags:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe [TagListEntry]
$sel:subdirectory:CreateLocationFsxOpenZfs' :: CreateLocationFsxOpenZfs -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Subdirectory" 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
subdirectory,
            (Key
"Tags" 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 [TagListEntry]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"FsxFilesystemArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fsxFilesystemArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"Protocol" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= FsxProtocol
protocol),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SecurityGroupArns" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
securityGroupArns)
          ]
      )

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

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

-- | /See:/ 'newCreateLocationFsxOpenZfsResponse' smart constructor.
data CreateLocationFsxOpenZfsResponse = CreateLocationFsxOpenZfsResponse'
  { -- | The ARN of the FSx for OpenZFS file system location that you created.
    CreateLocationFsxOpenZfsResponse -> Maybe Text
locationArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateLocationFsxOpenZfsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateLocationFsxOpenZfsResponse
-> CreateLocationFsxOpenZfsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLocationFsxOpenZfsResponse
-> CreateLocationFsxOpenZfsResponse -> Bool
$c/= :: CreateLocationFsxOpenZfsResponse
-> CreateLocationFsxOpenZfsResponse -> Bool
== :: CreateLocationFsxOpenZfsResponse
-> CreateLocationFsxOpenZfsResponse -> Bool
$c== :: CreateLocationFsxOpenZfsResponse
-> CreateLocationFsxOpenZfsResponse -> Bool
Prelude.Eq, ReadPrec [CreateLocationFsxOpenZfsResponse]
ReadPrec CreateLocationFsxOpenZfsResponse
Int -> ReadS CreateLocationFsxOpenZfsResponse
ReadS [CreateLocationFsxOpenZfsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLocationFsxOpenZfsResponse]
$creadListPrec :: ReadPrec [CreateLocationFsxOpenZfsResponse]
readPrec :: ReadPrec CreateLocationFsxOpenZfsResponse
$creadPrec :: ReadPrec CreateLocationFsxOpenZfsResponse
readList :: ReadS [CreateLocationFsxOpenZfsResponse]
$creadList :: ReadS [CreateLocationFsxOpenZfsResponse]
readsPrec :: Int -> ReadS CreateLocationFsxOpenZfsResponse
$creadsPrec :: Int -> ReadS CreateLocationFsxOpenZfsResponse
Prelude.Read, Int -> CreateLocationFsxOpenZfsResponse -> ShowS
[CreateLocationFsxOpenZfsResponse] -> ShowS
CreateLocationFsxOpenZfsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLocationFsxOpenZfsResponse] -> ShowS
$cshowList :: [CreateLocationFsxOpenZfsResponse] -> ShowS
show :: CreateLocationFsxOpenZfsResponse -> String
$cshow :: CreateLocationFsxOpenZfsResponse -> String
showsPrec :: Int -> CreateLocationFsxOpenZfsResponse -> ShowS
$cshowsPrec :: Int -> CreateLocationFsxOpenZfsResponse -> ShowS
Prelude.Show, forall x.
Rep CreateLocationFsxOpenZfsResponse x
-> CreateLocationFsxOpenZfsResponse
forall x.
CreateLocationFsxOpenZfsResponse
-> Rep CreateLocationFsxOpenZfsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLocationFsxOpenZfsResponse x
-> CreateLocationFsxOpenZfsResponse
$cfrom :: forall x.
CreateLocationFsxOpenZfsResponse
-> Rep CreateLocationFsxOpenZfsResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateLocationFsxOpenZfsResponse' 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', 'createLocationFsxOpenZfsResponse_locationArn' - The ARN of the FSx for OpenZFS file system location that you created.
--
-- 'httpStatus', 'createLocationFsxOpenZfsResponse_httpStatus' - The response's http status code.
newCreateLocationFsxOpenZfsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLocationFsxOpenZfsResponse
newCreateLocationFsxOpenZfsResponse :: Int -> CreateLocationFsxOpenZfsResponse
newCreateLocationFsxOpenZfsResponse Int
pHttpStatus_ =
  CreateLocationFsxOpenZfsResponse'
    { $sel:locationArn:CreateLocationFsxOpenZfsResponse' :: Maybe Text
locationArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLocationFsxOpenZfsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the FSx for OpenZFS file system location that you created.
createLocationFsxOpenZfsResponse_locationArn :: Lens.Lens' CreateLocationFsxOpenZfsResponse (Prelude.Maybe Prelude.Text)
createLocationFsxOpenZfsResponse_locationArn :: Lens' CreateLocationFsxOpenZfsResponse (Maybe Text)
createLocationFsxOpenZfsResponse_locationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocationFsxOpenZfsResponse' {Maybe Text
locationArn :: Maybe Text
$sel:locationArn:CreateLocationFsxOpenZfsResponse' :: CreateLocationFsxOpenZfsResponse -> Maybe Text
locationArn} -> Maybe Text
locationArn) (\s :: CreateLocationFsxOpenZfsResponse
s@CreateLocationFsxOpenZfsResponse' {} Maybe Text
a -> CreateLocationFsxOpenZfsResponse
s {$sel:locationArn:CreateLocationFsxOpenZfsResponse' :: Maybe Text
locationArn = Maybe Text
a} :: CreateLocationFsxOpenZfsResponse)

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

instance
  Prelude.NFData
    CreateLocationFsxOpenZfsResponse
  where
  rnf :: CreateLocationFsxOpenZfsResponse -> ()
rnf CreateLocationFsxOpenZfsResponse' {Int
Maybe Text
httpStatus :: Int
locationArn :: Maybe Text
$sel:httpStatus:CreateLocationFsxOpenZfsResponse' :: CreateLocationFsxOpenZfsResponse -> Int
$sel:locationArn:CreateLocationFsxOpenZfsResponse' :: CreateLocationFsxOpenZfsResponse -> 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 Int
httpStatus