{-# 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.WorkDocs.GetFolderPath
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the path information (the hierarchy from the root folder) for
-- the specified folder.
--
-- By default, Amazon WorkDocs returns a maximum of 100 levels upwards from
-- the requested folder and only includes the IDs of the parent folders in
-- the path. You can limit the maximum number of levels. You can also
-- request the parent folder names.
module Amazonka.WorkDocs.GetFolderPath
  ( -- * Creating a Request
    GetFolderPath (..),
    newGetFolderPath,

    -- * Request Lenses
    getFolderPath_authenticationToken,
    getFolderPath_fields,
    getFolderPath_limit,
    getFolderPath_marker,
    getFolderPath_folderId,

    -- * Destructuring the Response
    GetFolderPathResponse (..),
    newGetFolderPathResponse,

    -- * Response Lenses
    getFolderPathResponse_path,
    getFolderPathResponse_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.WorkDocs.Types

-- | /See:/ 'newGetFolderPath' smart constructor.
data GetFolderPath = GetFolderPath'
  { -- | Amazon WorkDocs authentication token. Not required when using AWS
    -- administrator credentials to access the API.
    GetFolderPath -> Maybe (Sensitive Text)
authenticationToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | A comma-separated list of values. Specify \"NAME\" to include the names
    -- of the parent folders.
    GetFolderPath -> Maybe Text
fields :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of levels in the hierarchy to return.
    GetFolderPath -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | This value is not supported.
    GetFolderPath -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The ID of the folder.
    GetFolderPath -> Text
folderId :: Prelude.Text
  }
  deriving (GetFolderPath -> GetFolderPath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFolderPath -> GetFolderPath -> Bool
$c/= :: GetFolderPath -> GetFolderPath -> Bool
== :: GetFolderPath -> GetFolderPath -> Bool
$c== :: GetFolderPath -> GetFolderPath -> Bool
Prelude.Eq, Int -> GetFolderPath -> ShowS
[GetFolderPath] -> ShowS
GetFolderPath -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFolderPath] -> ShowS
$cshowList :: [GetFolderPath] -> ShowS
show :: GetFolderPath -> String
$cshow :: GetFolderPath -> String
showsPrec :: Int -> GetFolderPath -> ShowS
$cshowsPrec :: Int -> GetFolderPath -> ShowS
Prelude.Show, forall x. Rep GetFolderPath x -> GetFolderPath
forall x. GetFolderPath -> Rep GetFolderPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFolderPath x -> GetFolderPath
$cfrom :: forall x. GetFolderPath -> Rep GetFolderPath x
Prelude.Generic)

-- |
-- Create a value of 'GetFolderPath' 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:
--
-- 'authenticationToken', 'getFolderPath_authenticationToken' - Amazon WorkDocs authentication token. Not required when using AWS
-- administrator credentials to access the API.
--
-- 'fields', 'getFolderPath_fields' - A comma-separated list of values. Specify \"NAME\" to include the names
-- of the parent folders.
--
-- 'limit', 'getFolderPath_limit' - The maximum number of levels in the hierarchy to return.
--
-- 'marker', 'getFolderPath_marker' - This value is not supported.
--
-- 'folderId', 'getFolderPath_folderId' - The ID of the folder.
newGetFolderPath ::
  -- | 'folderId'
  Prelude.Text ->
  GetFolderPath
newGetFolderPath :: Text -> GetFolderPath
newGetFolderPath Text
pFolderId_ =
  GetFolderPath'
    { $sel:authenticationToken:GetFolderPath' :: Maybe (Sensitive Text)
authenticationToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:fields:GetFolderPath' :: Maybe Text
fields = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:GetFolderPath' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:GetFolderPath' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:folderId:GetFolderPath' :: Text
folderId = Text
pFolderId_
    }

-- | Amazon WorkDocs authentication token. Not required when using AWS
-- administrator credentials to access the API.
getFolderPath_authenticationToken :: Lens.Lens' GetFolderPath (Prelude.Maybe Prelude.Text)
getFolderPath_authenticationToken :: Lens' GetFolderPath (Maybe Text)
getFolderPath_authenticationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPath' {Maybe (Sensitive Text)
authenticationToken :: Maybe (Sensitive Text)
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
authenticationToken} -> Maybe (Sensitive Text)
authenticationToken) (\s :: GetFolderPath
s@GetFolderPath' {} Maybe (Sensitive Text)
a -> GetFolderPath
s {$sel:authenticationToken:GetFolderPath' :: Maybe (Sensitive Text)
authenticationToken = Maybe (Sensitive Text)
a} :: GetFolderPath) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | A comma-separated list of values. Specify \"NAME\" to include the names
-- of the parent folders.
getFolderPath_fields :: Lens.Lens' GetFolderPath (Prelude.Maybe Prelude.Text)
getFolderPath_fields :: Lens' GetFolderPath (Maybe Text)
getFolderPath_fields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPath' {Maybe Text
fields :: Maybe Text
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
fields} -> Maybe Text
fields) (\s :: GetFolderPath
s@GetFolderPath' {} Maybe Text
a -> GetFolderPath
s {$sel:fields:GetFolderPath' :: Maybe Text
fields = Maybe Text
a} :: GetFolderPath)

-- | The maximum number of levels in the hierarchy to return.
getFolderPath_limit :: Lens.Lens' GetFolderPath (Prelude.Maybe Prelude.Natural)
getFolderPath_limit :: Lens' GetFolderPath (Maybe Natural)
getFolderPath_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPath' {Maybe Natural
limit :: Maybe Natural
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: GetFolderPath
s@GetFolderPath' {} Maybe Natural
a -> GetFolderPath
s {$sel:limit:GetFolderPath' :: Maybe Natural
limit = Maybe Natural
a} :: GetFolderPath)

-- | This value is not supported.
getFolderPath_marker :: Lens.Lens' GetFolderPath (Prelude.Maybe Prelude.Text)
getFolderPath_marker :: Lens' GetFolderPath (Maybe Text)
getFolderPath_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPath' {Maybe Text
marker :: Maybe Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
marker} -> Maybe Text
marker) (\s :: GetFolderPath
s@GetFolderPath' {} Maybe Text
a -> GetFolderPath
s {$sel:marker:GetFolderPath' :: Maybe Text
marker = Maybe Text
a} :: GetFolderPath)

-- | The ID of the folder.
getFolderPath_folderId :: Lens.Lens' GetFolderPath Prelude.Text
getFolderPath_folderId :: Lens' GetFolderPath Text
getFolderPath_folderId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPath' {Text
folderId :: Text
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
folderId} -> Text
folderId) (\s :: GetFolderPath
s@GetFolderPath' {} Text
a -> GetFolderPath
s {$sel:folderId:GetFolderPath' :: Text
folderId = Text
a} :: GetFolderPath)

instance Core.AWSRequest GetFolderPath where
  type
    AWSResponse GetFolderPath =
      GetFolderPathResponse
  request :: (Service -> Service) -> GetFolderPath -> Request GetFolderPath
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetFolderPath
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFolderPath)))
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 ResourcePath -> Int -> GetFolderPathResponse
GetFolderPathResponse'
            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
"Path")
            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 GetFolderPath where
  hashWithSalt :: Int -> GetFolderPath -> Int
hashWithSalt Int
_salt GetFolderPath' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
folderId :: Text
marker :: Maybe Text
limit :: Maybe Natural
fields :: Maybe Text
authenticationToken :: Maybe (Sensitive Text)
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
authenticationToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fields
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
folderId

instance Prelude.NFData GetFolderPath where
  rnf :: GetFolderPath -> ()
rnf GetFolderPath' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
folderId :: Text
marker :: Maybe Text
limit :: Maybe Natural
fields :: Maybe Text
authenticationToken :: Maybe (Sensitive Text)
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
authenticationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fields
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
folderId

instance Data.ToHeaders GetFolderPath where
  toHeaders :: GetFolderPath -> ResponseHeaders
toHeaders GetFolderPath' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
folderId :: Text
marker :: Maybe Text
limit :: Maybe Natural
fields :: Maybe Text
authenticationToken :: Maybe (Sensitive Text)
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"Authentication" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe (Sensitive Text)
authenticationToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToPath GetFolderPath where
  toPath :: GetFolderPath -> ByteString
toPath GetFolderPath' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
folderId :: Text
marker :: Maybe Text
limit :: Maybe Natural
fields :: Maybe Text
authenticationToken :: Maybe (Sensitive Text)
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/api/v1/folders/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
folderId, ByteString
"/path"]

instance Data.ToQuery GetFolderPath where
  toQuery :: GetFolderPath -> QueryString
toQuery GetFolderPath' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
folderId :: Text
marker :: Maybe Text
limit :: Maybe Natural
fields :: Maybe Text
authenticationToken :: Maybe (Sensitive Text)
$sel:folderId:GetFolderPath' :: GetFolderPath -> Text
$sel:marker:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:limit:GetFolderPath' :: GetFolderPath -> Maybe Natural
$sel:fields:GetFolderPath' :: GetFolderPath -> Maybe Text
$sel:authenticationToken:GetFolderPath' :: GetFolderPath -> Maybe (Sensitive Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"fields" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
fields,
        ByteString
"limit" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
limit,
        ByteString
"marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker
      ]

-- | /See:/ 'newGetFolderPathResponse' smart constructor.
data GetFolderPathResponse = GetFolderPathResponse'
  { -- | The path information.
    GetFolderPathResponse -> Maybe ResourcePath
path :: Prelude.Maybe ResourcePath,
    -- | The response's http status code.
    GetFolderPathResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFolderPathResponse -> GetFolderPathResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFolderPathResponse -> GetFolderPathResponse -> Bool
$c/= :: GetFolderPathResponse -> GetFolderPathResponse -> Bool
== :: GetFolderPathResponse -> GetFolderPathResponse -> Bool
$c== :: GetFolderPathResponse -> GetFolderPathResponse -> Bool
Prelude.Eq, ReadPrec [GetFolderPathResponse]
ReadPrec GetFolderPathResponse
Int -> ReadS GetFolderPathResponse
ReadS [GetFolderPathResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFolderPathResponse]
$creadListPrec :: ReadPrec [GetFolderPathResponse]
readPrec :: ReadPrec GetFolderPathResponse
$creadPrec :: ReadPrec GetFolderPathResponse
readList :: ReadS [GetFolderPathResponse]
$creadList :: ReadS [GetFolderPathResponse]
readsPrec :: Int -> ReadS GetFolderPathResponse
$creadsPrec :: Int -> ReadS GetFolderPathResponse
Prelude.Read, Int -> GetFolderPathResponse -> ShowS
[GetFolderPathResponse] -> ShowS
GetFolderPathResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFolderPathResponse] -> ShowS
$cshowList :: [GetFolderPathResponse] -> ShowS
show :: GetFolderPathResponse -> String
$cshow :: GetFolderPathResponse -> String
showsPrec :: Int -> GetFolderPathResponse -> ShowS
$cshowsPrec :: Int -> GetFolderPathResponse -> ShowS
Prelude.Show, forall x. Rep GetFolderPathResponse x -> GetFolderPathResponse
forall x. GetFolderPathResponse -> Rep GetFolderPathResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFolderPathResponse x -> GetFolderPathResponse
$cfrom :: forall x. GetFolderPathResponse -> Rep GetFolderPathResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFolderPathResponse' 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:
--
-- 'path', 'getFolderPathResponse_path' - The path information.
--
-- 'httpStatus', 'getFolderPathResponse_httpStatus' - The response's http status code.
newGetFolderPathResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFolderPathResponse
newGetFolderPathResponse :: Int -> GetFolderPathResponse
newGetFolderPathResponse Int
pHttpStatus_ =
  GetFolderPathResponse'
    { $sel:path:GetFolderPathResponse' :: Maybe ResourcePath
path = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFolderPathResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The path information.
getFolderPathResponse_path :: Lens.Lens' GetFolderPathResponse (Prelude.Maybe ResourcePath)
getFolderPathResponse_path :: Lens' GetFolderPathResponse (Maybe ResourcePath)
getFolderPathResponse_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFolderPathResponse' {Maybe ResourcePath
path :: Maybe ResourcePath
$sel:path:GetFolderPathResponse' :: GetFolderPathResponse -> Maybe ResourcePath
path} -> Maybe ResourcePath
path) (\s :: GetFolderPathResponse
s@GetFolderPathResponse' {} Maybe ResourcePath
a -> GetFolderPathResponse
s {$sel:path:GetFolderPathResponse' :: Maybe ResourcePath
path = Maybe ResourcePath
a} :: GetFolderPathResponse)

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

instance Prelude.NFData GetFolderPathResponse where
  rnf :: GetFolderPathResponse -> ()
rnf GetFolderPathResponse' {Int
Maybe ResourcePath
httpStatus :: Int
path :: Maybe ResourcePath
$sel:httpStatus:GetFolderPathResponse' :: GetFolderPathResponse -> Int
$sel:path:GetFolderPathResponse' :: GetFolderPathResponse -> Maybe ResourcePath
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourcePath
path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus