gogol-oslogin-0.4.0: Google Cloud OS Login SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.OSLogin.Types

Contents

Description

 
Synopsis

Service Configuration

oSLoginService :: ServiceConfig Source #

Default request referring to version v1 of the Cloud OS Login API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

computeScope :: Proxy '["https://www.googleapis.com/auth/compute"] Source #

View and manage your Google Compute Engine resources

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

PosixAccountOperatingSystemType

data PosixAccountOperatingSystemType Source #

The operating system type where this account applies.

Constructors

OperatingSystemTypeUnspecified

OPERATING_SYSTEM_TYPE_UNSPECIFIED The operating system type associated with the user account information is unspecified.

Linux

LINUX Linux user account information.

Windows

WINDOWS Windows user account information.

Instances
Enum PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Eq PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Data PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosixAccountOperatingSystemType -> c PosixAccountOperatingSystemType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosixAccountOperatingSystemType #

toConstr :: PosixAccountOperatingSystemType -> Constr #

dataTypeOf :: PosixAccountOperatingSystemType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PosixAccountOperatingSystemType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosixAccountOperatingSystemType) #

gmapT :: (forall b. Data b => b -> b) -> PosixAccountOperatingSystemType -> PosixAccountOperatingSystemType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosixAccountOperatingSystemType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosixAccountOperatingSystemType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosixAccountOperatingSystemType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosixAccountOperatingSystemType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosixAccountOperatingSystemType -> m PosixAccountOperatingSystemType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosixAccountOperatingSystemType -> m PosixAccountOperatingSystemType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosixAccountOperatingSystemType -> m PosixAccountOperatingSystemType #

Ord PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Read PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Show PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Generic PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Associated Types

type Rep PosixAccountOperatingSystemType :: Type -> Type #

Hashable PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

ToJSON PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

FromJSON PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

FromHttpApiData PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

ToHttpApiData PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

type Rep PosixAccountOperatingSystemType Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

type Rep PosixAccountOperatingSystemType = D1 (MetaData "PosixAccountOperatingSystemType" "Network.Google.OSLogin.Types.Sum" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" False) (C1 (MetaCons "OperatingSystemTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Linux" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Windows" PrefixI False) (U1 :: Type -> Type)))

LoginProFileSSHPublicKeys

data LoginProFileSSHPublicKeys Source #

A map from SSH public key fingerprint to the associated key object.

See: loginProFileSSHPublicKeys smart constructor.

Instances
Eq LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Data LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoginProFileSSHPublicKeys -> c LoginProFileSSHPublicKeys #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LoginProFileSSHPublicKeys #

toConstr :: LoginProFileSSHPublicKeys -> Constr #

dataTypeOf :: LoginProFileSSHPublicKeys -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LoginProFileSSHPublicKeys) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LoginProFileSSHPublicKeys) #

gmapT :: (forall b. Data b => b -> b) -> LoginProFileSSHPublicKeys -> LoginProFileSSHPublicKeys #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoginProFileSSHPublicKeys -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoginProFileSSHPublicKeys -> r #

gmapQ :: (forall d. Data d => d -> u) -> LoginProFileSSHPublicKeys -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LoginProFileSSHPublicKeys -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoginProFileSSHPublicKeys -> m LoginProFileSSHPublicKeys #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoginProFileSSHPublicKeys -> m LoginProFileSSHPublicKeys #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoginProFileSSHPublicKeys -> m LoginProFileSSHPublicKeys #

Show LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Generic LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep LoginProFileSSHPublicKeys :: Type -> Type #

ToJSON LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep LoginProFileSSHPublicKeys Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep LoginProFileSSHPublicKeys = D1 (MetaData "LoginProFileSSHPublicKeys" "Network.Google.OSLogin.Types.Product" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" True) (C1 (MetaCons "LoginProFileSSHPublicKeys'" PrefixI True) (S1 (MetaSel (Just "_lpfspkAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text SSHPublicKey))))

loginProFileSSHPublicKeys Source #

Creates a value of LoginProFileSSHPublicKeys with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

Empty

data Empty Source #

A generic empty message that you can re-use to avoid defining duplicated empty messages in your APIs. A typical example is to use it as the request or the response type of an API method. For instance: service Foo { rpc Bar(google.protobuf.Empty) returns (google.protobuf.Empty); } The JSON representation for `Empty` is empty JSON object `{}`.

See: empty smart constructor.

Instances
Eq Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

(==) :: Empty -> Empty -> Bool #

(/=) :: Empty -> Empty -> Bool #

Data Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Empty -> c Empty #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Empty #

toConstr :: Empty -> Constr #

dataTypeOf :: Empty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Empty) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Empty) #

gmapT :: (forall b. Data b => b -> b) -> Empty -> Empty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Empty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Empty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty #

Show Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep Empty :: Type -> Type #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

ToJSON Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep Empty Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep Empty = D1 (MetaData "Empty" "Network.Google.OSLogin.Types.Product" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" False) (C1 (MetaCons "Empty'" PrefixI False) (U1 :: Type -> Type))

empty :: Empty Source #

Creates a value of Empty with the minimum fields required to make a request.

LoginProFile

data LoginProFile Source #

The user profile information used for logging in to a virtual machine on Google Compute Engine.

See: loginProFile smart constructor.

Instances
Eq LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Data LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoginProFile -> c LoginProFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LoginProFile #

toConstr :: LoginProFile -> Constr #

dataTypeOf :: LoginProFile -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LoginProFile) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LoginProFile) #

gmapT :: (forall b. Data b => b -> b) -> LoginProFile -> LoginProFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoginProFile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoginProFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> LoginProFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LoginProFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoginProFile -> m LoginProFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoginProFile -> m LoginProFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoginProFile -> m LoginProFile #

Show LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Generic LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep LoginProFile :: Type -> Type #

ToJSON LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep LoginProFile Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep LoginProFile = D1 (MetaData "LoginProFile" "Network.Google.OSLogin.Types.Product" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" False) (C1 (MetaCons "LoginProFile'" PrefixI True) (S1 (MetaSel (Just "_lpfPosixAccounts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PosixAccount])) :*: (S1 (MetaSel (Just "_lpfSSHPublicKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LoginProFileSSHPublicKeys)) :*: S1 (MetaSel (Just "_lpfName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

loginProFile :: LoginProFile Source #

Creates a value of LoginProFile with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lpfPosixAccounts :: Lens' LoginProFile [PosixAccount] Source #

The list of POSIX accounts associated with the user.

lpfSSHPublicKeys :: Lens' LoginProFile (Maybe LoginProFileSSHPublicKeys) Source #

A map from SSH public key fingerprint to the associated key object.

lpfName :: Lens' LoginProFile (Maybe Text) Source #

A unique user ID.

ImportSSHPublicKeyResponse

data ImportSSHPublicKeyResponse Source #

A response message for importing an SSH public key.

See: importSSHPublicKeyResponse smart constructor.

Instances
Eq ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Data ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSSHPublicKeyResponse -> c ImportSSHPublicKeyResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSSHPublicKeyResponse #

toConstr :: ImportSSHPublicKeyResponse -> Constr #

dataTypeOf :: ImportSSHPublicKeyResponse -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSSHPublicKeyResponse) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSSHPublicKeyResponse) #

gmapT :: (forall b. Data b => b -> b) -> ImportSSHPublicKeyResponse -> ImportSSHPublicKeyResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSSHPublicKeyResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSSHPublicKeyResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportSSHPublicKeyResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSSHPublicKeyResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSSHPublicKeyResponse -> m ImportSSHPublicKeyResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSSHPublicKeyResponse -> m ImportSSHPublicKeyResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSSHPublicKeyResponse -> m ImportSSHPublicKeyResponse #

Show ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Generic ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep ImportSSHPublicKeyResponse :: Type -> Type #

ToJSON ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep ImportSSHPublicKeyResponse Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep ImportSSHPublicKeyResponse = D1 (MetaData "ImportSSHPublicKeyResponse" "Network.Google.OSLogin.Types.Product" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" True) (C1 (MetaCons "ImportSSHPublicKeyResponse'" PrefixI True) (S1 (MetaSel (Just "_ispkrLoginProFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LoginProFile))))

importSSHPublicKeyResponse :: ImportSSHPublicKeyResponse Source #

Creates a value of ImportSSHPublicKeyResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ispkrLoginProFile :: Lens' ImportSSHPublicKeyResponse (Maybe LoginProFile) Source #

The login profile information for the user.

SSHPublicKey

data SSHPublicKey Source #

The SSH public key information associated with a Google account.

See: sshPublicKey smart constructor.

Instances
Eq SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Data SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSHPublicKey -> c SSHPublicKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSHPublicKey #

toConstr :: SSHPublicKey -> Constr #

dataTypeOf :: SSHPublicKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SSHPublicKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSHPublicKey) #

gmapT :: (forall b. Data b => b -> b) -> SSHPublicKey -> SSHPublicKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSHPublicKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSHPublicKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSHPublicKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSHPublicKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSHPublicKey -> m SSHPublicKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSHPublicKey -> m SSHPublicKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSHPublicKey -> m SSHPublicKey #

Show SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Generic SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep SSHPublicKey :: Type -> Type #

ToJSON SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep SSHPublicKey Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep SSHPublicKey = D1 (MetaData "SSHPublicKey" "Network.Google.OSLogin.Types.Product" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" False) (C1 (MetaCons "SSHPublicKey'" PrefixI True) (S1 (MetaSel (Just "_spkFingerprint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_spkKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_spkExpirationTimeUsec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

sshPublicKey :: SSHPublicKey Source #

Creates a value of SSHPublicKey with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

spkFingerprint :: Lens' SSHPublicKey (Maybe Text) Source #

Output only. The SHA-256 fingerprint of the SSH public key.

spkKey :: Lens' SSHPublicKey (Maybe Text) Source #

Public key text in SSH format, defined by RFC4253 section 6.6.

spkExpirationTimeUsec :: Lens' SSHPublicKey (Maybe Int64) Source #

An expiration time in microseconds since epoch.

PosixAccount

data PosixAccount Source #

The POSIX account information associated with a Google account.

See: posixAccount smart constructor.

Instances
Eq PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Data PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosixAccount -> c PosixAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PosixAccount #

toConstr :: PosixAccount -> Constr #

dataTypeOf :: PosixAccount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PosixAccount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PosixAccount) #

gmapT :: (forall b. Data b => b -> b) -> PosixAccount -> PosixAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosixAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosixAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> PosixAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PosixAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosixAccount -> m PosixAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosixAccount -> m PosixAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosixAccount -> m PosixAccount #

Show PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Generic PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

Associated Types

type Rep PosixAccount :: Type -> Type #

ToJSON PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

FromJSON PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

type Rep PosixAccount Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Product

posixAccount :: PosixAccount Source #

Creates a value of PosixAccount with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

paGecos :: Lens' PosixAccount (Maybe Text) Source #

The GECOS (user information) entry for this account.

paUsername :: Lens' PosixAccount (Maybe Text) Source #

The username of the POSIX account.

paShell :: Lens' PosixAccount (Maybe Text) Source #

The path to the logic shell for this account.

paPrimary :: Lens' PosixAccount (Maybe Bool) Source #

Only one POSIX account can be marked as primary.

paAccountId :: Lens' PosixAccount (Maybe Text) Source #

Output only. A POSIX account identifier.

paGid :: Lens' PosixAccount (Maybe Int64) Source #

The default group ID.

paOperatingSystemType :: Lens' PosixAccount (Maybe PosixAccountOperatingSystemType) Source #

The operating system type where this account applies.

paSystemId :: Lens' PosixAccount (Maybe Text) Source #

System identifier for which account the username or uid applies to. By default, the empty value is used.

paHomeDirectory :: Lens' PosixAccount (Maybe Text) Source #

The path to the home directory for this account.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances
Enum Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

(==) :: Xgafv -> Xgafv -> Bool #

(/=) :: Xgafv -> Xgafv -> Bool #

Data Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xgafv -> c Xgafv #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xgafv #

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Xgafv) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xgafv) #

gmapT :: (forall b. Data b => b -> b) -> Xgafv -> Xgafv #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQ :: (forall d. Data d => d -> u) -> Xgafv -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Xgafv -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

Ord Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

(>=) :: Xgafv -> Xgafv -> Bool #

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Associated Types

type Rep Xgafv :: Type -> Type #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.OSLogin.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.OSLogin.Types.Sum" "gogol-oslogin-0.4.0-9ml7apG4s8bGCArs7cIh9t" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))