gogol-tpu-0.4.0: Google Cloud TPU 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.TPU.Types

Contents

Description

 
Synopsis

Service Configuration

tPUService :: ServiceConfig Source #

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

OAuth Scopes

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

View and manage your data across Google Cloud Platform services

Status

data Status Source #

The `Status` type defines a logical error model that is suitable for different programming environments, including REST APIs and RPC APIs. It is used by gRPC. The error model is designed to be: - Simple to use and understand for most users - Flexible enough to meet unexpected needs # Overview The `Status` message contains three pieces of data: error code, error message, and error details. The error code should be an enum value of google.rpc.Code, but it may accept additional error codes if needed. The error message should be a developer-facing English message that helps developers *understand* and *resolve* the error. If a localized user-facing error message is needed, put the localized message in the error details or localize it in the client. The optional error details may contain arbitrary information about the error. There is a predefined set of error detail types in the package `google.rpc` that can be used for common error conditions. # Language mapping The `Status` message is the logical representation of the error model, but it is not necessarily the actual wire format. When the `Status` message is exposed in different client libraries and different wire protocols, it can be mapped differently. For example, it will likely be mapped to some exceptions in Java, but more likely mapped to some error codes in C. # Other uses The error model and the `Status` message can be used in a variety of environments, either with or without APIs, to provide a consistent developer experience across different environments. Example uses of this error model include: - Partial errors. If a service needs to return partial errors to the client, it may embed the `Status` in the normal response to indicate the partial errors. - Workflow errors. A typical workflow has multiple steps. Each step may have a `Status` message for error reporting. - Batch operations. If a client uses batch request and batch response, the `Status` message should be used directly inside batch response, one for each error sub-response. - Asynchronous operations. If an API call embeds asynchronous operation results in its response, the status of those operations should be represented directly using the `Status` message. - Logging. If some API errors are stored in logs, the message `Status` could be used directly after any stripping needed for security/privacy reasons.

See: status smart constructor.

Instances
Eq Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

Data Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Status Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Status = D1 (MetaData "Status" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "Status'" PrefixI True) (S1 (MetaSel (Just "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem])) :*: (S1 (MetaSel (Just "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

status :: Status Source #

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

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

sDetails :: Lens' Status [StatusDetailsItem] Source #

A list of messages that carry the error details. There is a common set of message types for APIs to use.

sCode :: Lens' Status (Maybe Int32) Source #

The status code, which should be an enum value of google.rpc.Code.

sMessage :: Lens' Status (Maybe Text) Source #

A developer-facing error message, which should be in English. Any user-facing error message should be localized and sent in the google.rpc.Status.details field, or localized by the client.

OperationSchema

data OperationSchema Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

See: operationSchema smart constructor.

Instances
Eq OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: OperationSchema -> Constr #

dataTypeOf :: OperationSchema -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep OperationSchema :: Type -> Type #

ToJSON OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep OperationSchema Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep OperationSchema = D1 (MetaData "OperationSchema" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "OperationSchema'" PrefixI True) (S1 (MetaSel (Just "_osAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationSchema Source #

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

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

osAddtional :: Lens' OperationSchema (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

ListLocationsResponse

data ListLocationsResponse Source #

The response message for Locations.ListLocations.

See: listLocationsResponse smart constructor.

Instances
Eq ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ListLocationsResponse -> Constr #

dataTypeOf :: ListLocationsResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ListLocationsResponse :: Type -> Type #

ToJSON ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListLocationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListLocationsResponse = D1 (MetaData "ListLocationsResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "ListLocationsResponse'" PrefixI True) (S1 (MetaSel (Just "_llrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_llrLocations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Location]))))

listLocationsResponse :: ListLocationsResponse Source #

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

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

llrNextPageToken :: Lens' ListLocationsResponse (Maybe Text) Source #

The standard List next-page token.

llrLocations :: Lens' ListLocationsResponse [Location] Source #

A list of locations that matches the specified filter in the request.

AcceleratorType

data AcceleratorType Source #

A accelerator type that a Node can be configured with.

See: acceleratorType smart constructor.

Instances
Eq AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: AcceleratorType -> Constr #

dataTypeOf :: AcceleratorType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep AcceleratorType :: Type -> Type #

ToJSON AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep AcceleratorType Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep AcceleratorType = D1 (MetaData "AcceleratorType" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "AcceleratorType'" PrefixI True) (S1 (MetaSel (Just "_atName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_atType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

acceleratorType :: AcceleratorType Source #

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

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

atName :: Lens' AcceleratorType (Maybe Text) Source #

The resource name.

atType :: Lens' AcceleratorType (Maybe Text) Source #

the accelerator type.

ListOperationsResponse

data ListOperationsResponse Source #

The response message for Operations.ListOperations.

See: listOperationsResponse smart constructor.

Instances
Eq ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ListOperationsResponse -> Constr #

dataTypeOf :: ListOperationsResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ListOperationsResponse :: Type -> Type #

ToJSON ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListOperationsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListOperationsResponse = D1 (MetaData "ListOperationsResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "ListOperationsResponse'" PrefixI True) (S1 (MetaSel (Just "_lorNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lorOperations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Operation]))))

listOperationsResponse :: ListOperationsResponse Source #

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

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

lorNextPageToken :: Lens' ListOperationsResponse (Maybe Text) Source #

The standard List next-page token.

lorOperations :: Lens' ListOperationsResponse [Operation] Source #

A list of operations that matches the specified filter in the request.

NodeState

data NodeState Source #

Output only. The current state for the TPU Node.

Constructors

StateUnspecified

STATE_UNSPECIFIED TPU node state is not known/set.

Creating

CREATING TPU node is being created.

Ready

READY TPU node has been created and is fully usable.

Restarting

RESTARTING TPU node is restarting.

Reimaging

REIMAGING TPU node is undergoing reimaging.

Deleting

DELETING TPU node is being deleted.

Repairing

REPAIRING TPU node is being repaired and may be unusable. Details can be found in the `help_description` field.

Stopped

STOPPED 7 - Reserved. Was SUSPENDED. TPU node is stopped.

Stopping

STOPPING TPU node is currently stopping.

Starting

STARTING TPU node is currently starting.

Preempted

PREEMPTED TPU node has been preempted. Only applies to Preemptible TPU Nodes.

Terminated

TERMINATED TPU node has been terminated due to maintenance or has reached the end of its life cycle (for preemptible nodes).

Instances
Enum NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Eq NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Data NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Methods

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

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

toConstr :: NodeState -> Constr #

dataTypeOf :: NodeState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Read NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Show NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Generic NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Associated Types

type Rep NodeState :: Type -> Type #

Hashable NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

ToJSON NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromJSON NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromHttpApiData NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

ToHttpApiData NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

type Rep NodeState Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

type Rep NodeState = D1 (MetaData "NodeState" "Network.Google.TPU.Types.Sum" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (((C1 (MetaCons "StateUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Creating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ready" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Restarting" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Reimaging" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Deleting" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Repairing" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Stopped" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Stopping" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Starting" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Preempted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Terminated" PrefixI False) (U1 :: Type -> Type)))))

ListAcceleratorTypesResponse

data ListAcceleratorTypesResponse Source #

Response for ListAcceleratorTypes.

See: listAcceleratorTypesResponse smart constructor.

Instances
Eq ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ListAcceleratorTypesResponse -> Constr #

dataTypeOf :: ListAcceleratorTypesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ListAcceleratorTypesResponse :: Type -> Type #

ToJSON ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListAcceleratorTypesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListAcceleratorTypesResponse = D1 (MetaData "ListAcceleratorTypesResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "ListAcceleratorTypesResponse'" PrefixI True) (S1 (MetaSel (Just "_latrAcceleratorTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AcceleratorType])) :*: S1 (MetaSel (Just "_latrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

listAcceleratorTypesResponse :: ListAcceleratorTypesResponse Source #

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

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

latrNextPageToken :: Lens' ListAcceleratorTypesResponse (Maybe Text) Source #

The next page token or empty if none.

Location

data Location Source #

A resource that represents Google Cloud Platform location.

See: location smart constructor.

Instances
Eq Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: Location -> Constr #

dataTypeOf :: Location -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

ToJSON Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Location Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

location :: Location Source #

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

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

lName :: Lens' Location (Maybe Text) Source #

Resource name for the location, which may vary between implementations. For example: `"projects/example-project/locations/us-east1"`

lMetadata :: Lens' Location (Maybe LocationMetadata) Source #

Service-specific metadata. For example the available capacity at the given location.

lDisplayName :: Lens' Location (Maybe Text) Source #

The friendly name for this location, typically a nearby city name. For example, "Tokyo".

lLabels :: Lens' Location (Maybe LocationLabels) Source #

Cross-service attributes for the location. For example {"cloud.googleapis.com/region": "us-east1"}

lLocationId :: Lens' Location (Maybe Text) Source #

The canonical id for this location. For example: `"us-east1"`.

Operation

data Operation Source #

This resource represents a long-running operation that is the result of a network API call.

See: operation smart constructor.

Instances
Eq Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: Operation -> Constr #

dataTypeOf :: Operation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep Operation :: Type -> Type #

ToJSON Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Operation Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

operation :: Operation Source #

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

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

oDone :: Lens' Operation (Maybe Bool) Source #

If the value is `false`, it means the operation is still in progress. If `true`, the operation is completed, and either `error` or `response` is available.

oError :: Lens' Operation (Maybe Status) Source #

The error result of the operation in case of failure or cancellation.

oResponse :: Lens' Operation (Maybe OperationResponse) Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

oName :: Lens' Operation (Maybe Text) Source #

The server-assigned name, which is only unique within the same service that originally returns it. If you use the default HTTP mapping, the `name` should have the format of `operations/some/unique/name`.

oMetadata :: Lens' Operation (Maybe OperationSchema) Source #

Service-specific metadata associated with the operation. It typically contains progress information and common metadata such as create time. Some services might not provide such metadata. Any method that returns a long-running operation should document the metadata type, if any.

NetworkEndpoint

data NetworkEndpoint Source #

A network endpoint over which a TPU worker can be reached.

See: networkEndpoint smart constructor.

Instances
Eq NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: NetworkEndpoint -> Constr #

dataTypeOf :: NetworkEndpoint -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep NetworkEndpoint :: Type -> Type #

ToJSON NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep NetworkEndpoint Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep NetworkEndpoint = D1 (MetaData "NetworkEndpoint" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "NetworkEndpoint'" PrefixI True) (S1 (MetaSel (Just "_neIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nePort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))

networkEndpoint :: NetworkEndpoint Source #

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

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

neIPAddress :: Lens' NetworkEndpoint (Maybe Text) Source #

The IP address of this network endpoint.

nePort :: Lens' NetworkEndpoint (Maybe Int32) Source #

The port of this network endpoint.

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.TPU.Types.Product

Methods

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

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

Data Empty Source # 
Instance details

Defined in Network.Google.TPU.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.TPU.Types.Product

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 
Instance details

Defined in Network.Google.TPU.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.TPU.Types.Product

FromJSON Empty Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Empty Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Empty = D1 (MetaData "Empty" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" 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.

Node

data Node Source #

A TPU instance.

See: node smart constructor.

Instances
Eq Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

Data Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

ToJSON Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Node Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep Node = D1 (MetaData "Node" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "Node'" PrefixI True) ((((S1 (MetaSel (Just "_nAcceleratorType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nIPAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_nState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NodeState)) :*: S1 (MetaSel (Just "_nNetwork") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_nHealth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NodeHealth)) :*: S1 (MetaSel (Just "_nServiceAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_nName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nSchedulingConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SchedulingConfig))))) :*: (((S1 (MetaSel (Just "_nHealthDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nCIdRBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_nLabels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NodeLabels)) :*: S1 (MetaSel (Just "_nNetworkEndpoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [NetworkEndpoint])))) :*: ((S1 (MetaSel (Just "_nDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nCreateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) :*: (S1 (MetaSel (Just "_nTensorflowVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_nPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

node :: Node Source #

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

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

nAcceleratorType :: Lens' Node (Maybe Text) Source #

The type of hardware accelerators associated with this node. Required.

nIPAddress :: Lens' Node (Maybe Text) Source #

Output only. DEPRECATED! Use network_endpoints instead. The network address for the TPU Node as visible to Compute Engine instances.

nState :: Lens' Node (Maybe NodeState) Source #

Output only. The current state for the TPU Node.

nNetwork :: Lens' Node (Maybe Text) Source #

The name of a network they wish to peer the TPU node to. It must be a preexisting Compute Engine network inside of the project on which this API has been activated. If none is provided, "default" will be used.

nHealth :: Lens' Node (Maybe NodeHealth) Source #

The health status of the TPU node.

nServiceAccount :: Lens' Node (Maybe Text) Source #

Output only. The service account used to run the tensor flow services within the node. To share resources, including Google Cloud Storage data, with the Tensorflow job running in the Node, this account must have permissions to that data.

nName :: Lens' Node (Maybe Text) Source #

Output only. The immutable name of the TPU

nHealthDescription :: Lens' Node (Maybe Text) Source #

Output only. If this field is populated, it contains a description of why the TPU Node is unhealthy.

nCIdRBlock :: Lens' Node (Maybe Text) Source #

The CIDR block that the TPU node will use when selecting an IP address. This CIDR block must be a /29 block; the Compute Engine networks API forbids a smaller block, and using a larger block would be wasteful (a node can only consume one IP address). Errors will occur if the CIDR block has already been used for a currently existing TPU node, the CIDR block conflicts with any subnetworks in the user's provided network, or the provided network is peered with another network that is using that CIDR block. Required.

nLabels :: Lens' Node (Maybe NodeLabels) Source #

Resource labels to represent user-provided metadata.

nNetworkEndpoints :: Lens' Node [NetworkEndpoint] Source #

Output only. The network endpoints where TPU workers can be accessed and sent work. It is recommended that Tensorflow clients of the node reach out to the 0th entry in this map first.

nDescription :: Lens' Node (Maybe Text) Source #

The user-supplied description of the TPU. Maximum of 512 characters.

nCreateTime :: Lens' Node (Maybe UTCTime) Source #

Output only. The time when the node was created.

nTensorflowVersion :: Lens' Node (Maybe Text) Source #

The version of Tensorflow running in the Node. Required.

nPort :: Lens' Node (Maybe Text) Source #

Output only. DEPRECATED! Use network_endpoints instead. The network port for the TPU Node as visible to Compute Engine instances.

StatusDetailsItem

data StatusDetailsItem Source #

Instances
Eq StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: StatusDetailsItem -> Constr #

dataTypeOf :: StatusDetailsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep StatusDetailsItem :: Type -> Type #

ToJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StatusDetailsItem Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just "_sdiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

statusDetailsItem Source #

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

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

sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

StopNodeRequest

data StopNodeRequest Source #

Request for StopNode.

See: stopNodeRequest smart constructor.

Instances
Eq StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: StopNodeRequest -> Constr #

dataTypeOf :: StopNodeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep StopNodeRequest :: Type -> Type #

ToJSON StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StopNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StopNodeRequest = D1 (MetaData "StopNodeRequest" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "StopNodeRequest'" PrefixI False) (U1 :: Type -> Type))

stopNodeRequest :: StopNodeRequest Source #

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

ReimageNodeRequest

data ReimageNodeRequest Source #

Request for ReimageNode.

See: reimageNodeRequest smart constructor.

Instances
Eq ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ReimageNodeRequest -> Constr #

dataTypeOf :: ReimageNodeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ReimageNodeRequest :: Type -> Type #

ToJSON ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ReimageNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ReimageNodeRequest = D1 (MetaData "ReimageNodeRequest" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "ReimageNodeRequest'" PrefixI True) (S1 (MetaSel (Just "_rnrTensorflowVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

reimageNodeRequest :: ReimageNodeRequest Source #

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

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

rnrTensorflowVersion :: Lens' ReimageNodeRequest (Maybe Text) Source #

The version for reimage to create.

NodeHealth

data NodeHealth Source #

The health status of the TPU node.

Constructors

HealthUnspecified

HEALTH_UNSPECIFIED Health status is unknown: not initialized or failed to retrieve.

Healthy

HEALTHY The resource is healthy.

Unhealthy

UNHEALTHY The resource is unhealthy.

Timeout

TIMEOUT The resource is unresponsive.

Instances
Enum NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Eq NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Data NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Methods

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

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

toConstr :: NodeHealth -> Constr #

dataTypeOf :: NodeHealth -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Read NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Show NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Generic NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Associated Types

type Rep NodeHealth :: Type -> Type #

Hashable NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

ToJSON NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromJSON NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromHttpApiData NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

ToHttpApiData NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

type Rep NodeHealth Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

type Rep NodeHealth = D1 (MetaData "NodeHealth" "Network.Google.TPU.Types.Sum" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) ((C1 (MetaCons "HealthUnspecified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Healthy" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Unhealthy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Timeout" PrefixI False) (U1 :: Type -> Type)))

ListNodesResponse

data ListNodesResponse Source #

Response for ListNodes.

See: listNodesResponse smart constructor.

Instances
Eq ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ListNodesResponse -> Constr #

dataTypeOf :: ListNodesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ListNodesResponse :: Type -> Type #

ToJSON ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListNodesResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListNodesResponse = D1 (MetaData "ListNodesResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "ListNodesResponse'" PrefixI True) (S1 (MetaSel (Just "_lnrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_lnrUnreachable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_lnrNodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Node])))))

listNodesResponse :: ListNodesResponse Source #

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

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

lnrNextPageToken :: Lens' ListNodesResponse (Maybe Text) Source #

The next page token or empty if none.

lnrUnreachable :: Lens' ListNodesResponse [Text] Source #

Locations that could not be reached.

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.TPU.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Methods

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

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

Data Xgafv Source # 
Instance details

Defined in Network.Google.TPU.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.TPU.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.TPU.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.TPU.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.TPU.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.TPU.Types.Sum

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

SchedulingConfig

data SchedulingConfig Source #

Instances
Eq SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: SchedulingConfig -> Constr #

dataTypeOf :: SchedulingConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep SchedulingConfig :: Type -> Type #

ToJSON SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep SchedulingConfig Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep SchedulingConfig = D1 (MetaData "SchedulingConfig" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "SchedulingConfig'" PrefixI True) (S1 (MetaSel (Just "_scPreemptible") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))

schedulingConfig :: SchedulingConfig Source #

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

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

NodeLabels

data NodeLabels Source #

Resource labels to represent user-provided metadata.

See: nodeLabels smart constructor.

Instances
Eq NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: NodeLabels -> Constr #

dataTypeOf :: NodeLabels -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep NodeLabels :: Type -> Type #

ToJSON NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep NodeLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep NodeLabels = D1 (MetaData "NodeLabels" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "NodeLabels'" PrefixI True) (S1 (MetaSel (Just "_nlAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

nodeLabels Source #

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

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

LocationLabels

data LocationLabels Source #

Cross-service attributes for the location. For example {"cloud.googleapis.com/region": "us-east1"}

See: locationLabels smart constructor.

Instances
Eq LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: LocationLabels -> Constr #

dataTypeOf :: LocationLabels -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep LocationLabels :: Type -> Type #

ToJSON LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep LocationLabels Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep LocationLabels = D1 (MetaData "LocationLabels" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "LocationLabels'" PrefixI True) (S1 (MetaSel (Just "_llAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

locationLabels Source #

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

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

LocationMetadata

data LocationMetadata Source #

Service-specific metadata. For example the available capacity at the given location.

See: locationMetadata smart constructor.

Instances
Eq LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: LocationMetadata -> Constr #

dataTypeOf :: LocationMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep LocationMetadata :: Type -> Type #

ToJSON LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep LocationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep LocationMetadata = D1 (MetaData "LocationMetadata" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "LocationMetadata'" PrefixI True) (S1 (MetaSel (Just "_lmAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

locationMetadata Source #

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

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

lmAddtional :: Lens' LocationMetadata (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

OperationMetadata

data OperationMetadata Source #

Represents the metadata of the long-running operation.

See: operationMetadata smart constructor.

Instances
Eq OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: OperationMetadata -> Constr #

dataTypeOf :: OperationMetadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep OperationMetadata :: Type -> Type #

ToJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep OperationMetadata Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

operationMetadata :: OperationMetadata Source #

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

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

omAPIVersion :: Lens' OperationMetadata (Maybe Text) Source #

Output only
API version used to start the operation.

omEndTime :: Lens' OperationMetadata (Maybe UTCTime) Source #

Output only
The time the operation finished running.

omStatusDetail :: Lens' OperationMetadata (Maybe Text) Source #

Output only
Human-readable status of the operation, if any.

omVerb :: Lens' OperationMetadata (Maybe Text) Source #

Output only
Name of the verb executed by the operation.

omCancelRequested :: Lens' OperationMetadata (Maybe Bool) Source #

Output only
Identifies whether the user has requested cancellation of the operation. Operations that have successfully been cancelled have Operation.error value with a google.rpc.Status.code of 1, corresponding to `Code.CANCELLED`.

omTarget :: Lens' OperationMetadata (Maybe Text) Source #

Output only
Server-defined resource path for the target of the operation.

omCreateTime :: Lens' OperationMetadata (Maybe UTCTime) Source #

Output only
The time the operation was created.

ListTensorFlowVersionsResponse

data ListTensorFlowVersionsResponse Source #

Response for ListTensorFlowVersions.

See: listTensorFlowVersionsResponse smart constructor.

Instances
Eq ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: ListTensorFlowVersionsResponse -> Constr #

dataTypeOf :: ListTensorFlowVersionsResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep ListTensorFlowVersionsResponse :: Type -> Type #

ToJSON ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListTensorFlowVersionsResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep ListTensorFlowVersionsResponse = D1 (MetaData "ListTensorFlowVersionsResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "ListTensorFlowVersionsResponse'" PrefixI True) (S1 (MetaSel (Just "_ltfvrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ltfvrTensorflowVersions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TensorFlowVersion]))))

listTensorFlowVersionsResponse :: ListTensorFlowVersionsResponse Source #

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

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

ltfvrNextPageToken :: Lens' ListTensorFlowVersionsResponse (Maybe Text) Source #

The next page token or empty if none.

OperationResponse

data OperationResponse Source #

The normal response of the operation in case of success. If the original method returns no data on success, such as `Delete`, the response is `google.protobuf.Empty`. If the original method is standard `Get`/`Create`/`Update`, the response should be the resource. For other methods, the response should have the type `XxxResponse`, where `Xxx` is the original method name. For example, if the original method name is `TakeSnapshot()`, the inferred response type is `TakeSnapshotResponse`.

See: operationResponse smart constructor.

Instances
Eq OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: OperationResponse -> Constr #

dataTypeOf :: OperationResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep OperationResponse :: Type -> Type #

ToJSON OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep OperationResponse Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep OperationResponse = D1 (MetaData "OperationResponse" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" True) (C1 (MetaCons "OperationResponse'" PrefixI True) (S1 (MetaSel (Just "_orAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

operationResponse Source #

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

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

orAddtional :: Lens' OperationResponse (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

TensorFlowVersion

data TensorFlowVersion Source #

A tensorflow version that a Node can be configured with.

See: tensorFlowVersion smart constructor.

Instances
Eq TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: TensorFlowVersion -> Constr #

dataTypeOf :: TensorFlowVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep TensorFlowVersion :: Type -> Type #

ToJSON TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep TensorFlowVersion Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep TensorFlowVersion = D1 (MetaData "TensorFlowVersion" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "TensorFlowVersion'" PrefixI True) (S1 (MetaSel (Just "_tfvName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_tfvVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

tensorFlowVersion :: TensorFlowVersion Source #

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

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

tfvVersion :: Lens' TensorFlowVersion (Maybe Text) Source #

the tensorflow version.

StartNodeRequest

data StartNodeRequest Source #

Request for StartNode.

See: startNodeRequest smart constructor.

Instances
Eq StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Data StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Methods

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

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

toConstr :: StartNodeRequest -> Constr #

dataTypeOf :: StartNodeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Generic StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

Associated Types

type Rep StartNodeRequest :: Type -> Type #

ToJSON StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

FromJSON StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StartNodeRequest Source # 
Instance details

Defined in Network.Google.TPU.Types.Product

type Rep StartNodeRequest = D1 (MetaData "StartNodeRequest" "Network.Google.TPU.Types.Product" "gogol-tpu-0.4.0-G6BPhvxEJs5BesDiyU5xd2" False) (C1 (MetaCons "StartNodeRequest'" PrefixI False) (U1 :: Type -> Type))

startNodeRequest :: StartNodeRequest Source #

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