{-# 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.ChromeosDevices.Get
(
ChromeosDevicesGetResource
, chromeosDevicesGet
, ChromeosDevicesGet
, cdgCustomerId
, cdgDeviceId
, cdgProjection
) where
import Network.Google.Directory.Types
import Network.Google.Prelude
type ChromeosDevicesGetResource =
"admin" :>
"directory" :>
"v1" :>
"customer" :>
Capture "customerId" Text :>
"devices" :>
"chromeos" :>
Capture "deviceId" Text :>
QueryParam "projection" ChromeosDevicesGetProjection
:>
QueryParam "alt" AltJSON :>
Get '[JSON] ChromeOSDevice
data ChromeosDevicesGet = ChromeosDevicesGet'
{ _cdgCustomerId :: !Text
, _cdgDeviceId :: !Text
, _cdgProjection :: !(Maybe ChromeosDevicesGetProjection)
} deriving (Eq,Show,Data,Typeable,Generic)
chromeosDevicesGet
:: Text
-> Text
-> ChromeosDevicesGet
chromeosDevicesGet pCdgCustomerId_ pCdgDeviceId_ =
ChromeosDevicesGet'
{ _cdgCustomerId = pCdgCustomerId_
, _cdgDeviceId = pCdgDeviceId_
, _cdgProjection = Nothing
}
cdgCustomerId :: Lens' ChromeosDevicesGet Text
cdgCustomerId
= lens _cdgCustomerId
(\ s a -> s{_cdgCustomerId = a})
cdgDeviceId :: Lens' ChromeosDevicesGet Text
cdgDeviceId
= lens _cdgDeviceId (\ s a -> s{_cdgDeviceId = a})
cdgProjection :: Lens' ChromeosDevicesGet (Maybe ChromeosDevicesGetProjection)
cdgProjection
= lens _cdgProjection
(\ s a -> s{_cdgProjection = a})
instance GoogleRequest ChromeosDevicesGet where
type Rs ChromeosDevicesGet = ChromeOSDevice
type Scopes ChromeosDevicesGet =
'["https://www.googleapis.com/auth/admin.directory.device.chromeos",
"https://www.googleapis.com/auth/admin.directory.device.chromeos.readonly"]
requestClient ChromeosDevicesGet'{..}
= go _cdgCustomerId _cdgDeviceId _cdgProjection
(Just AltJSON)
directoryService
where go
= buildClient
(Proxy :: Proxy ChromeosDevicesGetResource)
mempty