gogol
Copyright(c) 2015-2022 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <[email protected]>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageGHC2021

Gogol

Description

This module provides a common set of operations which can be performed against the remote Google Service APIs. Typically you will import this module qualified along with modules from the various gogol-* libraries for 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 calling functions 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:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Control.Lens ((.~), (<&>), (?~))
import Control.Monad.Trans.Resource (liftResourceT)
import Data.Conduit (runConduit, (.|))
import qualified Data.Conduit.Binary as Conduit
import Data.Function ((&))
import Data.Generics.Labels ()
import Data.Proxy
import Data.Text
import qualified Data.Text as Text
import Gogol
import qualified Gogol.Storage as Storage
import System.IO (stdout)

import qualified Data.Text as Text

example :: IO Storage.Object
example = do
  lgr <- newLogger Debug stdout                                                                          -- (1)
  env <- newEnv <&> (envLogger .~ lgr) . (envScopes .~ (Proxy :: Proxy '[Storage.Devstorage'ReadWrite])) -- (2) (3)
  body <- sourceBody "/path/to/image.jpg"                                                                -- (4)
  let key = "image.jpg"
      bucket = "my-storage-bucket"

  runResourceT $                                                                                         -- (5)
    upload env (Storage.newStorageObjectsInsert bucket (Storage.newObject & #name ?~ 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 upload 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 which serialises the StorageObjectsInsert 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.

Environment

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

The environment containing the parameters required to make Google requests.

Instances

Instances details
HasEnv scopes (Env scopes) Source # 
Instance details

Defined in Gogol.Env

Methods

environment :: Lens' (Env scopes) (Env scopes) Source #

envOverride :: Lens' (Env scopes) (Dual (Endo ServiceConfig)) Source #

envLogger :: Lens' (Env scopes) Logger Source #

envManager :: Lens' (Env scopes) Manager Source #

envStore :: Lens' (Env scopes) (Store scopes) Source #

envScopes :: Lens' (Env scopes) (Proxy scopes) Source #

class HasEnv (scopes :: [Symbol]) a | a -> scopes where Source #

Minimal complete definition

environment

Methods

environment :: Lens' a (Env scopes) 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 scopes) Source #

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

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

The authorised OAuth2 scopes.

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

Instances

Instances details
HasEnv scopes (Env scopes) Source # 
Instance details

Defined in Gogol.Env

Methods

environment :: Lens' (Env scopes) (Env scopes) Source #

envOverride :: Lens' (Env scopes) (Dual (Endo ServiceConfig)) Source #

envLogger :: Lens' (Env scopes) Logger Source #

envManager :: Lens' (Env scopes) Manager Source #

envStore :: Lens' (Env scopes) (Store scopes) Source #

envScopes :: Lens' (Env scopes) (Proxy scopes) Source #

newEnv :: forall (scopes :: [Symbol]) m. (MonadIO m, MonadCatch m, KnownScopes scopes) => m (Env scopes) 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 Gogol.Compute.authComputeScope. Lenses from HasEnv can be used to further configure the resulting Env.

See: newEnvWith, getApplicationDefault.

newEnvWith :: forall (scopes :: [Symbol]) m. (MonadIO m, MonadCatch m, KnownScopes scopes) => Credentials scopes -> Logger -> Manager -> m (Env scopes) 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 Gogol.Auth for more information.

getApplicationDefault :: forall m (s :: [Symbol]). (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 Gogol.Compute.computeScope.

See: Application Default Credentials

Authorization

Each request within a particular send, upload or download context requires specific OAuth2 scopes to be have been authorized for the given credentials.

For example, the Google Storage StorageObjectsInsert 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 function call 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 Env. 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 @Gogol.*" and you can use the (!) combinator to combine these into a larger set.

For example:

import Control.Lens ((<&>), (.~))
import Gogol
import Gogol.Monitoring
import Gogol.Compute

main :: IO ()
main = do
    env <- newEnv <&> envScopes .~ (Proxy :: Proxy '[Monitoring'Read, Monitoring'Write, Compute'ReadOnly])
    ...
>>> :type env
Env '["https://www.googleapis.com/auth/monitoring.read", "https://www.googleapis.com/auth/monitoring.write", "https://www.googleapis.com/auth/compute.readonly"]

type AllowRequest a (scopes :: [Symbol]) = (GoogleRequest a, KnownScopes scopes, SatisfyScope (Scopes a) scopes) Source #

Constraint kind for proving the scopes context contains one of the scopes necessary for authenticating the request, a.

uploadAndDownloadFile
  :: ( AllowRequest StorageObjectsInsert scopes
     , AllowRequest StorageObjectsGet scopes
     )
  => Env scopes
  -> Text
  -> Object
  -> MediaType
  -> FilePath
  -> FilePath
  -> IO Object
uploadAndDownloadFile env bucket object media src dst = do
  let put = newStorageObjectsInsert bucket (object { bucket = Just bucket })
      get = newStorageObjectsGet bucket object

  body GBody media <$ HTTP.streamFile src

  runResourceT $ do
    _object <- upload env meta body
    stream <- download env meta

    Conduit.connect stream (Conduit.Combinators.sinkFileCautious dst)

See: SatisfyScope.

Sending Requests

send :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest a scopes) => Env scopes -> a -> m (Rs a) Source #

Send a request, returning the associated response if successful.

Throws Error.

sendEither :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest a scopes) => Env scopes -> a -> m (Either Error (Rs a)) Source #

Send a request, returning the associated response if successful.

Streaming Media

download :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest (MediaDownload a) scopes) => Env scopes -> 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 Error.

downloadEither :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest (MediaDownload a) scopes) => Env scopes -> a -> m (Either Error (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:

sendEither . MediaDownload

upload :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest (MediaUpload a) scopes) => Env scopes -> a -> GBody -> m (Rs (MediaUpload a)) Source #

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

Equivalent to:

send . MediaUpload

Throws Error.

uploadEither :: forall m a (scopes :: [Symbol]). (MonadResource m, AllowRequest (MediaUpload a) scopes) => Env scopes -> a -> GBody -> m (Either Error (Rs (MediaUpload a))) Source #

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

Equivalent to:

sendEither . MediaUpload

For example:

uploadFile
  :: HasScope StorageObjectsInsert scopes
  => Env scopes
  -> Text
  -> Object
  -> MediaType
  -> FilePath
  -> IO (Either Error Object)
uploadFile env bucket object media path = do
  let meta = newStorageObjectsInsert bucket (object { bucket = Just bucket })

  body GBody media <$ Network.HTTP.Client.streamFile path

  runResourceT (upload env meta body)

data GBody #

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

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

Constructors

GBody !MediaType !RequestBody 

Instances

Instances details
IsString GBody # 
Instance details

Defined in Gogol.Types

Methods

fromString :: String -> GBody #

bodyContentType :: Lens' GBody MediaType #

A lens into the MediaType of a request Body.

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

Construct a GBody 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 Gogol
import Gogol.Compute

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

Overriding Defaults

configure :: forall (scopes :: [Symbol]) a. HasEnv scopes 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 :: forall (scopes :: [Symbol]) a. HasEnv scopes 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 Gogol with Control.Monad.Reader or Control.Lens.Zoom and the ServiceConfig lenses:

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

See: configure.

timeout :: forall r m (scopes :: [Symbol]) a. (MonadReader r m, HasEnv scopes 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.

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.

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 Gogol.Compute.Metadata for the available functions.

Re-exported Types

newtype Base64 #

Raw bytes that will be transparently base64 encoded/decoded on tramission to/from a remote API.

Constructors

Base64 

Instances

Instances details
FromJSON Base64 # 
Instance details

Defined in Gogol.Data.Base64

ToJSON Base64 # 
Instance details

Defined in Gogol.Data.Base64

Generic Base64 # 
Instance details

Defined in Gogol.Data.Base64

Associated Types

type Rep Base64 
Instance details

Defined in Gogol.Data.Base64

type Rep Base64 = D1 ('MetaData "Base64" "Gogol.Data.Base64" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Base64" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromBase64") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Methods

from :: Base64 -> Rep Base64 x #

to :: Rep Base64 x -> Base64 #

Read Base64 # 
Instance details

Defined in Gogol.Data.Base64

Show Base64 # 
Instance details

Defined in Gogol.Data.Base64

Eq Base64 # 
Instance details

Defined in Gogol.Data.Base64

Methods

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

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

Ord Base64 # 
Instance details

Defined in Gogol.Data.Base64

Hashable Base64 # 
Instance details

Defined in Gogol.Data.Base64

Methods

hashWithSalt :: Int -> Base64 -> Int #

hash :: Base64 -> Int #

FromHttpApiData Base64 # 
Instance details

Defined in Gogol.Data.Base64

ToHttpApiData Base64 # 
Instance details

Defined in Gogol.Data.Base64

type Rep Base64 # 
Instance details

Defined in Gogol.Data.Base64

type Rep Base64 = D1 ('MetaData "Base64" "Gogol.Data.Base64" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Base64" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromBase64") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype DateTime #

This SHOULD be a date in ISO 8601 format of YYYY-MM- DDThh:mm:ssZ in UTC time. This is the recommended form of date/timestamp.

Constructors

DateTime 

Fields

Instances

Instances details
FromJSON DateTime # 
Instance details

Defined in Gogol.Data.Time

ToJSON DateTime # 
Instance details

Defined in Gogol.Data.Time

Generic DateTime # 
Instance details

Defined in Gogol.Data.Time

Associated Types

type Rep DateTime 
Instance details

Defined in Gogol.Data.Time

type Rep DateTime = D1 ('MetaData "DateTime" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "DateTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDateTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))

Methods

from :: DateTime -> Rep DateTime x #

to :: Rep DateTime x -> DateTime #

Read DateTime # 
Instance details

Defined in Gogol.Data.Time

Show DateTime # 
Instance details

Defined in Gogol.Data.Time

Eq DateTime # 
Instance details

Defined in Gogol.Data.Time

Ord DateTime # 
Instance details

Defined in Gogol.Data.Time

FromHttpApiData DateTime # 
Instance details

Defined in Gogol.Data.Time

ToHttpApiData DateTime # 
Instance details

Defined in Gogol.Data.Time

type Rep DateTime # 
Instance details

Defined in Gogol.Data.Time

type Rep DateTime = D1 ('MetaData "DateTime" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "DateTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDateTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))

newtype Date #

This SHOULD be a date in the format of YYYY-MM-DD. It is recommended that you use the "date-time" format instead of "date" unless you need to transfer only the date part.

Constructors

Date 

Fields

Instances

Instances details
FromJSON Date # 
Instance details

Defined in Gogol.Data.Time

ToJSON Date # 
Instance details

Defined in Gogol.Data.Time

Generic Date # 
Instance details

Defined in Gogol.Data.Time

Associated Types

type Rep Date 
Instance details

Defined in Gogol.Data.Time

type Rep Date = D1 ('MetaData "Date" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Date" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)))

Methods

from :: Date -> Rep Date x #

to :: Rep Date x -> Date #

Read Date # 
Instance details

Defined in Gogol.Data.Time

Show Date # 
Instance details

Defined in Gogol.Data.Time

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Eq Date # 
Instance details

Defined in Gogol.Data.Time

Methods

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

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

Ord Date # 
Instance details

Defined in Gogol.Data.Time

Methods

compare :: Date -> Date -> Ordering #

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

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

(>) :: Date -> Date -> Bool #

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

FromHttpApiData Date # 
Instance details

Defined in Gogol.Data.Time

ToHttpApiData Date # 
Instance details

Defined in Gogol.Data.Time

type Rep Date # 
Instance details

Defined in Gogol.Data.Time

type Rep Date = D1 ('MetaData "Date" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Date" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)))

newtype Time #

This SHOULD be a time in the format of hh:mm:ss. It is recommended that you use the "date-time" format instead of "time" unless you need to transfer only the time part.

Constructors

Time 

Fields

Instances

Instances details
FromJSON Time # 
Instance details

Defined in Gogol.Data.Time

ToJSON Time # 
Instance details

Defined in Gogol.Data.Time

Generic Time # 
Instance details

Defined in Gogol.Data.Time

Associated Types

type Rep Time 
Instance details

Defined in Gogol.Data.Time

type Rep Time = D1 ('MetaData "Time" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Time" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay)))

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

Read Time # 
Instance details

Defined in Gogol.Data.Time

Show Time # 
Instance details

Defined in Gogol.Data.Time

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Eq Time # 
Instance details

Defined in Gogol.Data.Time

Methods

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

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

Ord Time # 
Instance details

Defined in Gogol.Data.Time

Methods

compare :: Time -> Time -> Ordering #

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

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

(>) :: Time -> Time -> Bool #

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

FromHttpApiData Time # 
Instance details

Defined in Gogol.Data.Time

ToHttpApiData Time # 
Instance details

Defined in Gogol.Data.Time

type Rep Time # 
Instance details

Defined in Gogol.Data.Time

type Rep Time = D1 ('MetaData "Time" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Time" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay)))

newtype Duration #

A duration in seconds with up to nine fractional digits, terminated by s.

Example: "3.5s".

Constructors

Duration 

Instances

Instances details
FromJSON Duration # 
Instance details

Defined in Gogol.Data.Time

ToJSON Duration # 
Instance details

Defined in Gogol.Data.Time

Generic Duration # 
Instance details

Defined in Gogol.Data.Time

Associated Types

type Rep Duration 
Instance details

Defined in Gogol.Data.Time

type Rep Duration = D1 ('MetaData "Duration" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Duration" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Scientific)))

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

Read Duration # 
Instance details

Defined in Gogol.Data.Time

Show Duration # 
Instance details

Defined in Gogol.Data.Time

Eq Duration # 
Instance details

Defined in Gogol.Data.Time

Ord Duration # 
Instance details

Defined in Gogol.Data.Time

FromHttpApiData Duration # 
Instance details

Defined in Gogol.Data.Time

ToHttpApiData Duration # 
Instance details

Defined in Gogol.Data.Time

type Rep Duration # 
Instance details

Defined in Gogol.Data.Time

type Rep Duration = D1 ('MetaData "Duration" "Gogol.Data.Time" "gogol-core-1.0.0.0-KiphtVHMtob6Ng8ixWEMmL" 'True) (C1 ('MetaCons "Duration" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Scientific)))

newtype AsText a #

Constructors

AsText 

Fields

Instances

Instances details
(FromJSON a, FromHttpApiData a) => FromJSON (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

ToHttpApiData a => ToJSON (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Num a => Num (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Methods

(+) :: AsText a -> AsText a -> AsText a #

(-) :: AsText a -> AsText a -> AsText a #

(*) :: AsText a -> AsText a -> AsText a #

negate :: AsText a -> AsText a #

abs :: AsText a -> AsText a #

signum :: AsText a -> AsText a #

fromInteger :: Integer -> AsText a #

Read a => Read (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Fractional a => Fractional (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Methods

(/) :: AsText a -> AsText a -> AsText a #

recip :: AsText a -> AsText a #

fromRational :: Rational -> AsText a #

Show a => Show (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Methods

showsPrec :: Int -> AsText a -> ShowS #

show :: AsText a -> String #

showList :: [AsText a] -> ShowS #

Eq a => Eq (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Methods

(==) :: AsText a -> AsText a -> Bool #

(/=) :: AsText a -> AsText a -> Bool #

Ord a => Ord (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Methods

compare :: AsText a -> AsText a -> Ordering #

(<) :: AsText a -> AsText a -> Bool #

(<=) :: AsText a -> AsText a -> Bool #

(>) :: AsText a -> AsText a -> Bool #

(>=) :: AsText a -> AsText a -> Bool #

max :: AsText a -> AsText a -> AsText a #

min :: AsText a -> AsText a -> AsText a #

FromHttpApiData a => FromHttpApiData (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

ToHttpApiData a => ToHttpApiData (AsText a) # 
Instance details

Defined in Gogol.Data.JSON

Re-exported Utilities

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