gogol-0.4.0: Comprehensive Google Services SDK.

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

Network.Google

Contents

Description

This module provides a Google monad and common set of operations which can be performed against the remote Google Service APIs. Typically you will import this module along with modules from various gogol-* libraries for the services you wish to communicate with.

Synopsis

Usage

The request and response types provided by the various gogol-* libraries can be used with either send, upload, or download, depending upon the request's purpose. Namely, send is the function you will most commonly use to send requests, with upload and download as convenience when dealing with streaming requests and responses respectively.

To get started we will need to specify our Google Service credentials and create an Env environment containing configuration which will be used by runGoogle to perform any actions. Your Google Credentials can be supplied in a number of ways, by having Gogol retrieve Application Default Credentials for use on Google App Engine and Google Compute Engine, or by explicitly supplying your credentials. See the Credentials section for information about supported credential mechanisms.

The following example demonstrates uploading a file to Google Cloud Storage using ObjectsInsert from gogol-storage:

import Control.Lens           ((&), (.~), (<&>), (?~))
import Data.Text              (Text)
import Network.Google
import Network.Google.Storage
import System.IO              (stdout)

import qualified Data.Text as Text

example :: IO Object
example = do
    lgr  <- newLogger Debug stdout                                               -- (1)
    env  <- newEnv <&> (envLogger .~ lgr) . (envScopes .~ storageReadWriteScope) -- (2) (3)
    body <- sourceBody "/path/to/image.jpg"                                      -- (4)

    let key = "image.jpg"
        bkt = "my-storage-bucket"

    runResourceT . runGoogle env $                                               -- (5)
        upload (objectsInsert bkt object' & oiName ?~ key) body

Breaking down the above example, we have the following points of interest:

  1. A new Logger to replace the default noop logger is created, set to print debug information and errors to stdout.
  2. The Env is created using newEnv. This creates a new HTTP Manager and retrieves the application default Credentials.
  3. The lenses envLogger and envScopes are used to set the newly created Logger and authorised OAuth2 scopes, respectively. Explicitly annotating the Env with the scopes ensures that any mismatch between the remote operations performed in runGoogle and the credential scopes are raised as errors at compile time. See the Authorization section for more information.
  4. The streaming body for the object is retrieved from a FilePath, and the MIME type is calculated from the file extension. The MIME type is used as the object's Content-Type in Cloud Storage, and can be overriden using the bodyContentType lens as follows:

    import Network.HTTP.Media ((//))
    
    body <- sourceBody f <&> bodyContentType .~ "application" // "json"
  5. Finally, we run the Google computation using runResourceT . runGoogle which serialises the ObjectsInsert type to a HTTP request and sets the streaming Body. The resulting Object metadata is then parsed from a successful HTTP response. 1 Additional examples can be found can be found in the Gogol project's source control.

The Google Monad

newtype Google s a Source #

The Google monad containing configuration environment and tracks resource allocation via ResourceT. The functions in Network.Google are generalised

Constructors

Google 

Fields

Instances
AllowScopes s => MonadGoogle s (Google s) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> Google s a Source #

Monad (Google s) Source # 
Instance details

Defined in Network.Google

Methods

(>>=) :: Google s a -> (a -> Google s b) -> Google s b #

(>>) :: Google s a -> Google s b -> Google s b #

return :: a -> Google s a #

fail :: String -> Google s a #

Functor (Google s) Source # 
Instance details

Defined in Network.Google

Methods

fmap :: (a -> b) -> Google s a -> Google s b #

(<$) :: a -> Google s b -> Google s a #

Applicative (Google s) Source # 
Instance details

Defined in Network.Google

Methods

pure :: a -> Google s a #

(<*>) :: Google s (a -> b) -> Google s a -> Google s b #

liftA2 :: (a -> b -> c) -> Google s a -> Google s b -> Google s c #

(*>) :: Google s a -> Google s b -> Google s b #

(<*) :: Google s a -> Google s b -> Google s a #

Alternative (Google s) Source # 
Instance details

Defined in Network.Google

Methods

empty :: Google s a #

(<|>) :: Google s a -> Google s a -> Google s a #

some :: Google s a -> Google s [a] #

many :: Google s a -> Google s [a] #

MonadPlus (Google s) Source # 
Instance details

Defined in Network.Google

Methods

mzero :: Google s a #

mplus :: Google s a -> Google s a -> Google s a #

MonadIO (Google s) Source # 
Instance details

Defined in Network.Google

Methods

liftIO :: IO a -> Google s a #

MonadUnliftIO (Google s) Source # 
Instance details

Defined in Network.Google

Methods

askUnliftIO :: Google s (UnliftIO (Google s)) #

withRunInIO :: ((forall a. Google s a -> IO a) -> IO b) -> Google s b #

MonadResource (Google s) Source # 
Instance details

Defined in Network.Google

Methods

liftResourceT :: ResourceT IO a -> Google s a #

MonadThrow (Google s) Source # 
Instance details

Defined in Network.Google

Methods

throwM :: Exception e => e -> Google s a #

MonadCatch (Google s) Source # 
Instance details

Defined in Network.Google

Methods

catch :: Exception e => Google s a -> (e -> Google s a) -> Google s a #

MonadMask (Google s) Source # 
Instance details

Defined in Network.Google

Methods

mask :: ((forall a. Google s a -> Google s a) -> Google s b) -> Google s b #

uninterruptibleMask :: ((forall a. Google s a -> Google s a) -> Google s b) -> Google s b #

generalBracket :: Google s a -> (a -> ExitCase b -> Google s c) -> (a -> Google s b) -> Google s (b, c) #

MonadReader (Env s) (Google s) Source # 
Instance details

Defined in Network.Google

Methods

ask :: Google s (Env s) #

local :: (Env s -> Env s) -> Google s a -> Google s a #

reader :: (Env s -> a) -> Google s a #

class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m, AllowScopes s) => MonadGoogle s m | m -> s where Source #

Monads in which Google actions may be embedded.

The functions in Network.Google have MonadGoogle constraints to provide automatic lifting when embedding Google as a layer inside your own application stack.

Methods

liftGoogle :: Google s a -> m a Source #

Lift a computation to the Google monad.

Instances
MonadGoogle s m => MonadGoogle s (MaybeT m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> MaybeT m a Source #

MonadGoogle s m => MonadGoogle s (ListT m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> ListT m a Source #

AllowScopes s => MonadGoogle s (Google s) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> Google s a Source #

(Monoid w, MonadGoogle s m) => MonadGoogle s (WriterT w m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> WriterT w m a Source #

(Monoid w, MonadGoogle s m) => MonadGoogle s (WriterT w m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> WriterT w m a Source #

MonadGoogle s m => MonadGoogle s (StateT s' m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> StateT s' m a Source #

MonadGoogle s m => MonadGoogle s (StateT s' m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> StateT s' m a Source #

MonadGoogle s m => MonadGoogle s (ExceptT e m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> ExceptT e m a Source #

MonadGoogle s m => MonadGoogle s (IdentityT m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> IdentityT m a Source #

MonadGoogle s m => MonadGoogle s (ReaderT r m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> ReaderT r m a Source #

(Monoid w, MonadGoogle s m) => MonadGoogle s (RWST r w s' m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> RWST r w s' m a Source #

(Monoid w, MonadGoogle s m) => MonadGoogle s (RWST r w s' m) Source # 
Instance details

Defined in Network.Google

Methods

liftGoogle :: Google s a -> RWST r w s' m a Source #

runGoogle :: (MonadResource m, HasEnv s r) => r -> Google s a -> m a Source #

Run a Google action using the specified environment and credentials annotated with sufficient authorization scopes.

runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #

Unwrap a ResourceT transformer, and call all registered release actions.

Note that there is some reference counting involved due to resourceForkIO. If multiple threads are sharing the same collection of resources, only the last call to runResourceT will deallocate the resources.

NOTE Since version 1.2.0, this function will throw a ResourceCleanupException if any of the cleanup functions throw an exception.

Since: resourcet-0.3.0

Environment

data Env (s :: [Symbol]) Source #

The environment containing the parameters required to make Google requests.

Instances
HasEnv s (Env s) Source # 
Instance details

Defined in Network.Google.Env

MonadReader (Env s) (Google s) Source # 
Instance details

Defined in Network.Google

Methods

ask :: Google s (Env s) #

local :: (Env s -> Env s) -> Google s a -> Google s a #

reader :: (Env s -> a) -> Google s a #

class HasEnv s a | a -> s where Source #

Minimal complete definition

environment

Methods

environment :: Lens' a (Env s) Source #

envOverride :: Lens' a (Dual (Endo ServiceConfig)) Source #

The currently applied overrides to all Service configuration.

envLogger :: Lens' a Logger Source #

The function used to output log messages.

envManager :: Lens' a Manager Source #

The Manager used to create and manage open HTTP connections.

envStore :: Lens' a (Store s) Source #

The credential store used to sign requests for authentication with Google.

envScopes :: Lens' a (Proxy s) Source #

The authorised OAuth2 scopes.

See: allow, !, and the related scopes available for each service.

newEnv :: (MonadIO m, MonadCatch m, AllowScopes s) => m (Env s) Source #

Creates a new environment with a newly initialized Manager, without logging. and Credentials that are determined by calling getApplicationDefault. Use newEnvWith to supply custom credentials such as an OAuthClient and OAuthCode.

The Allowed OAuthScopes are used to authorize any service_account that is found with the appropriate scopes. See the top-level module of each individual gogol-* library for a list of available scopes, such as Network.Google.Compute.authComputeScope. Lenses from HasEnv can be used to further configure the resulting Env.

See: newEnvWith, getApplicationDefault.

newEnvWith :: (MonadIO m, MonadCatch m, AllowScopes s) => Credentials s -> Logger -> Manager -> m (Env s) Source #

Create a new environment.

See: newEnv.

Credentials

By default newEnv uses getApplicationDefault to discover credentials from the underlying, following Google's official library behaviour. If you wish to manually specify Credentials via newEnvWith, you can use one of the following supported credential mechanisms:

See Network.Google.Auth for more information.

getApplicationDefault :: (MonadIO m, MonadCatch m) => Manager -> m (Credentials s) Source #

Performs credentials discovery in the following order:

  1. Read the default credentials from a file specified by the environment variable GOOGLE_APPLICATION_CREDENTIALS if it exists.
  2. Read the platform equivalent of ~/.config/gcloud/application_default_credentials.json if it exists. The ~/.config component of the path can be overriden by the environment variable CLOUDSDK_CONFIG if it exists.
  3. Retrieve the default service account application credentials if running on GCE. The environment variable NO_GCE_CHECK can be used to skip this check if set to a truthy value such as 1 or true.

The specified Scopes are used to authorize any service_account that is found with the appropriate OAuth2 scopes, otherwise they are not used. See the top-level module of each individual gogol-* library for a list of available scopes, such as Network.Google.Compute.computeScope.

See: Application Default Credentials

Authorization

Each request within a particular runGoogle context requires specific OAuth2 scopes to be have been authorized for the given credentials.

For example, the Google Storage ObjectsInsert has the associated scopes of:

type Scopes ObjectsInsert =
     '["https://www.googleapis.com/auth/cloud-platform",
       "https://www.googleapis.com/auth/devstorage.full_control",
       "https://www.googleapis.com/auth/devstorage.read_write"]

Multiple differing requests within a given runGoogle context will then require the credentials to have a minimal set of these associated request scopes. This authorization information is represented as a type-level set, the s type parameter of Google and MonadGoogle. A mismatch of the sent request scopes and the Env credential scopes results in a informative compile error.

You can use allow or the envScopes lens to specify the Envs set of scopes. The various gogol-* libraries export their individual scopes from @Network.Google.*" and you can use the '(!)' combinator to combine these into a larger set.

For example:

import Control.Lens ((<&>), (.~))
import Network.Google
import Network.Google.Monitoring

main :: IO ()
main = do
    env <- newEnv <&> envScopes .~ (monitoringReadScope ! monitoringWriteScope ! computeReadOnlyScope)
    ...
>>> :type env
Env '["https://www.googleapis.com/auth/monitoring.read", "https://www.googleapis.com/auth/monitoring.write", "https://www.googleapis.com/auth/compute.readonly"]

(!) :: proxy xs -> proxy ys -> Proxy (Nub (xs ++ ys)) Source #

Append two sets of scopes.

See: allow.

allow :: proxy s -> k s -> k s Source #

Annotate credentials with the specified scopes. This exists to allow users to choose between using newEnv with a Proxy constructed by !, or explicitly specifying scopes via a type annotation.

See: !, envScopes, and the scopes available for each service.

class AllowScopes a Source #

Minimal complete definition

allowScopes

Instances
AllowScopes ([] :: [k]) Source # 
Instance details

Defined in Network.Google.Auth.Scope

Methods

allowScopes :: proxy [] -> [OAuthScope] Source #

AllowScopes s => AllowScopes (Credentials s :: Type) Source # 
Instance details

Defined in Network.Google.Auth.Scope

Methods

allowScopes :: proxy (Credentials s) -> [OAuthScope] Source #

(KnownSymbol x, AllowScopes xs) => AllowScopes (x ': xs :: [Symbol]) Source # 
Instance details

Defined in Network.Google.Auth.Scope

Methods

allowScopes :: proxy (x ': xs) -> [OAuthScope] Source #

type family HasScope (s :: [Symbol]) a :: Constraint where ... Source #

Determine if _any_ of the scopes a request requires is listed in the scopes the credentials supports.

For error message/presentation purposes, this wraps the result of the HasScope membership check to show both lists of scopes before reduction.

Equations

HasScope s a = (s `HasScope'` Scopes a) ~ True 

Sending Requests

send :: (MonadGoogle s m, HasScope s a, GoogleRequest a) => a -> m (Rs a) Source #

Send a request, returning the associated response if successful.

Throws LogLevel.

Streaming Media

download :: (MonadGoogle s m, HasScope s (MediaDownload a), GoogleRequest (MediaDownload a)) => a -> m (Rs (MediaDownload a)) Source #

Send a request returning the associated streaming media response if successful.

Some request data types have two possible responses, the JSON metadata and a streaming media response. Use send to retrieve the metadata and download to retrieve the streaming media.

Equivalent to:

send . MediaDownload

Throws LogLevel.

upload :: (MonadGoogle s m, HasScope s (MediaUpload a), GoogleRequest (MediaUpload a)) => a -> Body -> m (Rs (MediaUpload a)) Source #

Send a request with an attached multipart/related media upload.

Equivalent to:

send . MediaUpload

Throws LogLevel.

data Body #

A single part of a (potentially multipart) request body.

Note: The IsString instance defaults to a text/plain MIME type.

Constructors

Body !MediaType !RequestBody 
Instances
IsString Body 
Instance details

Defined in Network.Google.Types

Methods

fromString :: String -> Body #

bodyContentType :: Lens' Body MediaType #

A lens into the MediaType of a request Body.

sourceBody :: MonadIO m => FilePath -> m Body Source #

Construct a Body from a FilePath.

This uses getMIMEType to calculate the MIME type from the file extension, you can use bodyContentType to set a MIME type explicitly.

getMIMEType :: FilePath -> MediaType Source #

Attempt to calculate the MIME type based on file extension.

Defaults to application/octet-stream if no file extension is recognised.

Service Configuration

Each service has its own configuration such as host, port, path prefix, and timeout which can be customized independent of other services. It can be desirable to customize this when mocking service endpoints or adjusting HTTP response timeouts for a specific request.

For example, to point all calls to Google Compute to https://localhost instead of the actual remote endpoint, we can use Control.Monad.Reader.local in conjunction with override:

import Control.Lens ((&), (.~))
import Control.Monad.Reader (local)
import Network.Google
import Network.Google.Compute

local (override (computeService & serviceHost .~ "localhost")) $ do
   _ <- send $ instancesGet "project" "zone" "instance-id"
   ...

Overriding Defaults

configure :: HasEnv s a => (ServiceConfig -> ServiceConfig) -> a -> a Source #

Provide a function which will be added to the stack of overrides, which are applied to all service configurations. This provides a way to configure any request that is sent using the modified Env.

See: override.

override :: HasEnv s a => ServiceConfig -> a -> a Source #

Override a specific ServiceConfig. All requests belonging to the supplied service will use this configuration instead of the default.

Typically you would override a modified version of the default ServiceConfig for the desired service:

override (gmailService & serviceHost .~ "localhost") env

Or when using Network.Google with Control.Monad.Reader or Control.Lens.Zoom and the ServiceConfig lenses:

local (override (computeService & serviceHost .~ "localhost")) $ do
   ...

See: configure.

timeout :: (MonadReader r m, HasEnv s r) => Seconds -> m a -> m a Source #

Scope an action such that any HTTP response will use this timeout value.

Default timeouts are chosen by considering:

  • This timeout, if set.
  • The related Service timeout for the sent request if set. (Default 70s)
  • The envManager timeout, if set.
  • The ClientRequest timeout. (Default 30s)

Lenses

serviceHost :: Lens' ServiceConfig ByteString #

The remote host name, used for both the IP address to connect to and the host request header.

servicePort :: Lens' ServiceConfig Int #

The remote port to connect to.

Defaults to 443.

servicePath :: Lens' ServiceConfig Builder #

A path prefix that is prepended to any sent HTTP request.

Defaults to mempty.

serviceSecure :: Lens' ServiceConfig Bool #

Whether to use HTTPS/SSL.

Defaults to True.

serviceTimeout :: Lens' ServiceConfig (Maybe Seconds) #

Number of seconds to wait for a response.

Handling Errors

class AsError a where #

Minimal complete definition

_Error

Methods

_Error :: Prism' a Error #

A general Amazonka error.

_TransportError :: Prism' a HttpException #

An error occured while communicating over HTTP with a remote service.

_SerializeError :: Prism' a SerializeError #

A serialisation error occured when attempting to deserialise a response.

_ServiceError :: Prism' a ServiceError #

A service specific error returned by the remote service.

class AsAuthError a where Source #

Minimal complete definition

_AuthError

Methods

_AuthError :: Prism' a AuthError Source #

A general authentication error.

_RetrievalError :: Prism' a HttpException Source #

An error occured while communicating over HTTP with either then local metadata or remote accounts.google.com endpoints.

_MissingFileError :: Prism' a FilePath Source #

The specified default credentials file could not be found.

_InvalidFileError :: Prism' a (FilePath, Text) Source #

An error occured parsing the default credentials file.

_TokenRefreshError :: Prism' a (Status, Text, Maybe Text) Source #

An error occured when attempting to refresh a token.

trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r) #

A variant of try that takes a ReifiedPrism (or any ReifiedFold) to select which exceptions are caught (c.f. tryJust, catchJust). If the Exception does not match the predicate, it is re-thrown.

trying :: MonadCatch m => Prism'     SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => Lens'      SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => Traversal' SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => Iso'       SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => ReifiedGetter     SomeException a -> m r -> m (Either a r)
trying :: MonadCatch m => ReifiedFold       SomeException a -> m r -> m (Either a r)

catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r #

Catch exceptions that match a given ReifiedPrism (or any ReifiedFold, really).

>>> catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching :: MonadCatch m => Prism' SomeException a     -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Lens' SomeException a      -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Traversal' SomeException a -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => Iso' SomeException a       -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => ReifiedGetter SomeException a     -> m r -> (a -> m r) -> m r
catching :: MonadCatch m => ReifiedFold SomeException a       -> m r -> (a -> m r) -> m r

Logging

The exposed logging interface is a primitive Logger function which gets threaded through service calls and serialisation routines. This allows the consuming library to output useful information and diagnostics.

The newLogger function can be used to construct a simple logger which writes output to a Handle, but in most production code you should probably consider using a more robust logging library such as tinylog or fast-logger.

type Logger = LogLevel -> Builder -> IO () Source #

A function threaded through various request and serialisation routines to log informational and debug messages.

data LogLevel Source #

Constructors

Info

Info messages supplied by the user - this level is not emitted by the library.

Error

Error messages only.

Debug

Useful debug information + info + error levels.

Trace

Includes potentially credentials metadata, and non-streaming response bodies.

Instances
Enum LogLevel Source # 
Instance details

Defined in Network.Google.Internal.Logger

Eq LogLevel Source # 
Instance details

Defined in Network.Google.Internal.Logger

Data LogLevel Source # 
Instance details

Defined in Network.Google.Internal.Logger

Methods

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

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

toConstr :: LogLevel -> Constr #

dataTypeOf :: LogLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LogLevel Source # 
Instance details

Defined in Network.Google.Internal.Logger

Show LogLevel Source # 
Instance details

Defined in Network.Google.Internal.Logger

Constructing a Logger

newLogger :: MonadIO m => LogLevel -> Handle -> m Logger Source #

This is a primitive logger which can be used to log builds to a Handle.

Note: A more sophisticated logging library such as tinylog or fast-logger should be used in production code.

Constructing a HTTP Manager

newManager :: ManagerSettings -> IO Manager #

Create a Manager. The Manager will be shut down automatically via garbage collection.

Creating a new Manager is a relatively expensive operation, you are advised to share a single Manager between requests instead.

The first argument to this function is often defaultManagerSettings, though add-on libraries may provide a recommended replacement.

Since 0.1.0

tlsManagerSettings :: ManagerSettings #

Default TLS-enabled manager settings

Running Asynchronous Actions

Requests can be sent asynchronously, but due to guarantees about resource closure require the use of lifted-async.

Compute Metadata

Google Compute metadata can be retrieve when running on GCE instances. See the documentation in Network.Google.Compute.Metadata for the available functions.

Re-exported Types