{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.Directory.Users.Get
(
UsersGetResource
, usersGet
, UsersGet
, ugViewType
, ugCustomFieldMask
, ugProjection
, ugUserKey
) where
import Network.Google.Directory.Types
import Network.Google.Prelude
type UsersGetResource =
"admin" :>
"directory" :>
"v1" :>
"users" :>
Capture "userKey" Text :>
QueryParam "viewType" UsersGetViewType :>
QueryParam "customFieldMask" Text :>
QueryParam "projection" UsersGetProjection :>
QueryParam "alt" AltJSON :> Get '[JSON] User
data UsersGet = UsersGet'
{ _ugViewType :: !UsersGetViewType
, _ugCustomFieldMask :: !(Maybe Text)
, _ugProjection :: !UsersGetProjection
, _ugUserKey :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
usersGet
:: Text
-> UsersGet
usersGet pUgUserKey_ =
UsersGet'
{ _ugViewType = UGVTAdminView
, _ugCustomFieldMask = Nothing
, _ugProjection = UGPBasic
, _ugUserKey = pUgUserKey_
}
ugViewType :: Lens' UsersGet UsersGetViewType
ugViewType
= lens _ugViewType (\ s a -> s{_ugViewType = a})
ugCustomFieldMask :: Lens' UsersGet (Maybe Text)
ugCustomFieldMask
= lens _ugCustomFieldMask
(\ s a -> s{_ugCustomFieldMask = a})
ugProjection :: Lens' UsersGet UsersGetProjection
ugProjection
= lens _ugProjection (\ s a -> s{_ugProjection = a})
ugUserKey :: Lens' UsersGet Text
ugUserKey
= lens _ugUserKey (\ s a -> s{_ugUserKey = a})
instance GoogleRequest UsersGet where
type Rs UsersGet = User
type Scopes UsersGet =
'["https://www.googleapis.com/auth/admin.directory.user",
"https://www.googleapis.com/auth/admin.directory.user.readonly"]
requestClient UsersGet'{..}
= go _ugUserKey (Just _ugViewType) _ugCustomFieldMask
(Just _ugProjection)
(Just AltJSON)
directoryService
where go
= buildClient (Proxy :: Proxy UsersGetResource)
mempty