gogol-core-0.2.0.1: Core data types and functionality for Gogol libraries.

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

Network.Google.Types

Description

 

Synopsis

Documentation

data AltJSON Source #

Constructors

AltJSON 

Instances

Eq AltJSON Source # 

Methods

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

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

Ord AltJSON Source # 
Read AltJSON Source # 
Show AltJSON Source # 
Generic AltJSON Source # 

Associated Types

type Rep AltJSON :: * -> * #

Methods

from :: AltJSON -> Rep AltJSON x #

to :: Rep AltJSON x -> AltJSON #

ToHttpApiData AltJSON Source # 
type Rep AltJSON Source # 
type Rep AltJSON = D1 (MetaData "AltJSON" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" False) (C1 (MetaCons "AltJSON" PrefixI False) U1)

data AltMedia Source #

Constructors

AltMedia 

Instances

Eq AltMedia Source # 
Ord AltMedia Source # 
Read AltMedia Source # 
Show AltMedia Source # 
Generic AltMedia Source # 

Associated Types

type Rep AltMedia :: * -> * #

Methods

from :: AltMedia -> Rep AltMedia x #

to :: Rep AltMedia x -> AltMedia #

ToHttpApiData AltMedia Source # 
GoogleClient fn => GoogleClient ((:>) * * AltMedia fn) Source # 

Associated Types

type Fn ((:>) * * AltMedia fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) AltMedia fn) -> Request -> Fn ((* :> *) AltMedia fn) Source #

type Rep AltMedia Source # 
type Rep AltMedia = D1 (MetaData "AltMedia" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" False) (C1 (MetaCons "AltMedia" PrefixI False) U1)
type Fn ((:>) * * AltMedia fn) Source # 
type Fn ((:>) * * AltMedia fn) = Body -> Fn fn

newtype OAuthScope Source #

An OAuth2 scope.

Constructors

OAuthScope Text 

Instances

Eq OAuthScope Source # 
Ord OAuthScope Source # 
Read OAuthScope Source # 
Show OAuthScope Source # 
IsString OAuthScope Source # 
Generic OAuthScope Source # 

Associated Types

type Rep OAuthScope :: * -> * #

ToJSON OAuthScope Source # 
FromJSON OAuthScope Source # 
ToHttpApiData OAuthScope Source # 
FromHttpApiData OAuthScope Source # 
type Rep OAuthScope Source # 
type Rep OAuthScope = D1 (MetaData "OAuthScope" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "OAuthScope" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype AccessToken Source #

An OAuth2 access token.

Constructors

AccessToken Text 

Instances

Eq AccessToken Source # 
Ord AccessToken Source # 
Read AccessToken Source # 
Show AccessToken Source # 
IsString AccessToken Source # 
Generic AccessToken Source # 

Associated Types

type Rep AccessToken :: * -> * #

ToJSON AccessToken Source # 
FromJSON AccessToken Source # 
ToHttpApiData AccessToken Source # 
FromHttpApiData AccessToken Source # 
type Rep AccessToken Source # 
type Rep AccessToken = D1 (MetaData "AccessToken" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "AccessToken" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype RefreshToken Source #

An OAuth2 refresh token.

Constructors

RefreshToken Text 

Instances

Eq RefreshToken Source # 
Ord RefreshToken Source # 
Read RefreshToken Source # 
Show RefreshToken Source # 
IsString RefreshToken Source # 
Generic RefreshToken Source # 

Associated Types

type Rep RefreshToken :: * -> * #

ToJSON RefreshToken Source # 
FromJSON RefreshToken Source # 
ToHttpApiData RefreshToken Source # 
FromHttpApiData RefreshToken Source # 
type Rep RefreshToken Source # 
type Rep RefreshToken = D1 (MetaData "RefreshToken" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "RefreshToken" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ClientId Source #

A client identifier.

Constructors

ClientId Text 

Instances

Eq ClientId Source # 
Ord ClientId Source # 
Read ClientId Source # 
Show ClientId Source # 
IsString ClientId Source # 
Generic ClientId Source # 

Associated Types

type Rep ClientId :: * -> * #

Methods

from :: ClientId -> Rep ClientId x #

to :: Rep ClientId x -> ClientId #

ToJSON ClientId Source # 
FromJSON ClientId Source # 
ToHttpApiData ClientId Source # 
FromHttpApiData ClientId Source # 
type Rep ClientId Source # 
type Rep ClientId = D1 (MetaData "ClientId" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "ClientId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ServiceId Source #

A service identifier.

Constructors

ServiceId Text 

Instances

Eq ServiceId Source # 
Ord ServiceId Source # 
Read ServiceId Source # 
Show ServiceId Source # 
IsString ServiceId Source # 
Generic ServiceId Source # 

Associated Types

type Rep ServiceId :: * -> * #

ToJSON ServiceId Source # 
FromJSON ServiceId Source # 
ToHttpApiData ServiceId Source # 
FromHttpApiData ServiceId Source # 
type Rep ServiceId Source # 
type Rep ServiceId = D1 (MetaData "ServiceId" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "ServiceId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Secret Source #

An opaque client secret.

Constructors

Secret Text 

Instances

Eq Secret Source # 

Methods

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

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

Ord Secret Source # 
Read Secret Source # 
Show Secret Source # 
IsString Secret Source # 

Methods

fromString :: String -> Secret #

Generic Secret Source # 

Associated Types

type Rep Secret :: * -> * #

Methods

from :: Secret -> Rep Secret x #

to :: Rep Secret x -> Secret #

ToJSON Secret Source # 
FromJSON Secret Source # 
ToHttpApiData Secret Source # 
FromHttpApiData Secret Source # 
type Rep Secret Source # 
type Rep Secret = D1 (MetaData "Secret" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "Secret" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype MediaDownload a Source #

Constructors

MediaDownload a 

data MediaUpload a Source #

Constructors

MediaUpload a Body 

_Coerce :: (Coercible a b, Coercible b a) => Iso' a b Source #

_Default :: Monoid a => Iso' (Maybe a) a Source #

Invalid Iso, exists for ease of composition with the current 'Lens . Iso' chaining to hide internal types from the user.

class AsError a where Source #

Minimal complete definition

_Error

Methods

_Error :: Prism' a Error Source #

A general Amazonka error.

_TransportError :: Prism' a HttpException Source #

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

_SerializeError :: Prism' a SerializeError Source #

A serialisation error occured when attempting to deserialise a response.

_ServiceError :: Prism' a ServiceError Source #

A service specific error returned by the remote service.

serviceHost :: Lens' ServiceConfig ByteString Source #

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

servicePort :: Lens' ServiceConfig Int Source #

The remote port to connect to.

Defaults to 443.

servicePath :: Lens' ServiceConfig Builder Source #

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

Defaults to mempty.

serviceSecure :: Lens' ServiceConfig Bool Source #

Whether to use HTTPS/SSL.

Defaults to True.

serviceTimeout :: Lens' ServiceConfig (Maybe Seconds) Source #

Number of seconds to wait for a response.

data Body Source #

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

bodyContentType :: Lens' Body MediaType Source #

A lens into the MediaType of a request Body.

data Request Source #

An intermediary request builder.

data Client a Source #

A materialised 'http-client' request and associated response parser.

class GoogleRequest a where Source #

Minimal complete definition

requestClient

Associated Types

type Rs a :: * Source #

type Scopes a :: [Symbol] Source #

Methods

requestClient :: a -> Client (Rs a) Source #

class GoogleClient fn where Source #

Minimal complete definition

buildClient

Associated Types

type Fn fn :: * Source #

Methods

buildClient :: Proxy fn -> Request -> Fn fn Source #

Instances

(GoogleClient a, GoogleClient b) => GoogleClient ((:<|>) a b) Source # 

Associated Types

type Fn ((:<|>) a b) :: * Source #

Methods

buildClient :: Proxy * (a :<|> b) -> Request -> Fn (a :<|> b) Source #

FromStream c a => GoogleClient (Get * ((:) * c cs) a) Source # 

Associated Types

type Fn (Get * ((:) * c cs) a) :: * Source #

Methods

buildClient :: Proxy * (Get * ((* ': c) cs) a) -> Request -> Fn (Get * ((* ': c) cs) a) Source #

GoogleClient (Get * ((:) * c cs) ()) Source # 

Associated Types

type Fn (Get * ((:) * c cs) ()) :: * Source #

Methods

buildClient :: Proxy * (Get * ((* ': c) cs) ()) -> Request -> Fn (Get * ((* ': c) cs) ()) Source #

GoogleClient (Post * cs ()) Source # 

Associated Types

type Fn (Post * cs ()) :: * Source #

Methods

buildClient :: Proxy * (Post * cs ()) -> Request -> Fn (Post * cs ()) Source #

(FromStream c a, (~) [*] cs' ((:) * c cs)) => GoogleClient (Post * cs' a) Source # 

Associated Types

type Fn (Post * cs' a) :: * Source #

Methods

buildClient :: Proxy * (Post * cs' a) -> Request -> Fn (Post * cs' a) Source #

FromStream c a => GoogleClient (Put * ((:) * c cs) a) Source # 

Associated Types

type Fn (Put * ((:) * c cs) a) :: * Source #

Methods

buildClient :: Proxy * (Put * ((* ': c) cs) a) -> Request -> Fn (Put * ((* ': c) cs) a) Source #

GoogleClient (Put * ((:) * c cs) ()) Source # 

Associated Types

type Fn (Put * ((:) * c cs) ()) :: * Source #

Methods

buildClient :: Proxy * (Put * ((* ': c) cs) ()) -> Request -> Fn (Put * ((* ': c) cs) ()) Source #

FromStream c a => GoogleClient (Delete * ((:) * c cs) a) Source # 

Associated Types

type Fn (Delete * ((:) * c cs) a) :: * Source #

Methods

buildClient :: Proxy * (Delete * ((* ': c) cs) a) -> Request -> Fn (Delete * ((* ': c) cs) a) Source #

GoogleClient (Delete * ((:) * c cs) ()) Source # 

Associated Types

type Fn (Delete * ((:) * c cs) ()) :: * Source #

Methods

buildClient :: Proxy * (Delete * ((* ': c) cs) ()) -> Request -> Fn (Delete * ((* ': c) cs) ()) Source #

FromStream c a => GoogleClient (Patch * ((:) * c cs) a) Source # 

Associated Types

type Fn (Patch * ((:) * c cs) a) :: * Source #

Methods

buildClient :: Proxy * (Patch * ((* ': c) cs) a) -> Request -> Fn (Patch * ((* ': c) cs) a) Source #

GoogleClient (Patch * ((:) * c cs) ()) Source # 

Associated Types

type Fn (Patch * ((:) * c cs) ()) :: * Source #

Methods

buildClient :: Proxy * (Patch * ((* ': c) cs) ()) -> Request -> Fn (Patch * ((* ': c) cs) ()) Source #

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (Capture * s a) fn) Source # 

Associated Types

type Fn ((:>) * * (Capture * s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (Capture * s a) fn) -> Request -> Fn ((* :> *) (Capture * s a) fn) Source #

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (Header s a) fn) Source # 

Associated Types

type Fn ((:>) * * (Header s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (Header s a) fn) -> Request -> Fn ((* :> *) (Header s a) fn) Source #

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (QueryParam * s a) fn) Source # 

Associated Types

type Fn ((:>) * * (QueryParam * s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (QueryParam * s a) fn) -> Request -> Fn ((* :> *) (QueryParam * s a) fn) Source #

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (QueryParams * s a) fn) Source # 

Associated Types

type Fn ((:>) * * (QueryParams * s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (QueryParams * s a) fn) -> Request -> Fn ((* :> *) (QueryParams * s a) fn) Source #

(ToBody c a, GoogleClient fn) => GoogleClient ((:>) * * (ReqBody * ((:) * c cs) a) fn) Source # 

Associated Types

type Fn ((:>) * * (ReqBody * ((:) * c cs) a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (ReqBody * ((* ': c) cs) a) fn) -> Request -> Fn ((* :> *) (ReqBody * ((* ': c) cs) a) fn) Source #

(ToBody c m, GoogleClient fn) => GoogleClient ((:>) * * (MultipartRelated ((:) * c cs) m) fn) Source # 

Associated Types

type Fn ((:>) * * (MultipartRelated ((:) * c cs) m) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (MultipartRelated ((* ': c) cs) m) fn) -> Request -> Fn ((* :> *) (MultipartRelated ((* ': c) cs) m) fn) Source #

(KnownSymbol s, KnownSymbol m, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (CaptureMode s m a) fn) Source # 

Associated Types

type Fn ((:>) * * (CaptureMode s m a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (CaptureMode s m a) fn) -> Request -> Fn ((* :> *) (CaptureMode s m a) fn) Source #

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (Captures s a) fn) Source # 

Associated Types

type Fn ((:>) * * (Captures s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (Captures s a) fn) -> Request -> Fn ((* :> *) (Captures s a) fn) Source #

GoogleClient fn => GoogleClient ((:>) * * AltMedia fn) Source # 

Associated Types

type Fn ((:>) * * AltMedia fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) AltMedia fn) -> Request -> Fn ((* :> *) AltMedia fn) Source #

(KnownSymbol s, GoogleClient fn) => GoogleClient ((:>) * Symbol s fn) Source # 

Associated Types

type Fn ((:>) * Symbol s fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> Symbol) s fn) -> Request -> Fn ((* :> Symbol) s fn) Source #

data Captures s a Source #

Multiple path captures, with [xs] forming x1x2x2....

Instances

(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (Captures s a) fn) Source # 

Associated Types

type Fn ((:>) * * (Captures s a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (Captures s a) fn) -> Request -> Fn ((* :> *) (Captures s a) fn) Source #

type Fn ((:>) * * (Captures s a) fn) Source # 
type Fn ((:>) * * (Captures s a) fn) = [a] -> Fn fn

data CaptureMode s m a Source #

Form a Google style sub-resource, such as /capture:mode.

Instances

(KnownSymbol s, KnownSymbol m, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (CaptureMode s m a) fn) Source # 

Associated Types

type Fn ((:>) * * (CaptureMode s m a) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (CaptureMode s m a) fn) -> Request -> Fn ((* :> *) (CaptureMode s m a) fn) Source #

type Fn ((:>) * * (CaptureMode s m a) fn) Source # 
type Fn ((:>) * * (CaptureMode s m a) fn) = a -> Fn fn

data MultipartRelated cs m Source #

Instances

(ToBody c m, GoogleClient fn) => GoogleClient ((:>) * * (MultipartRelated ((:) * c cs) m) fn) Source # 

Associated Types

type Fn ((:>) * * (MultipartRelated ((:) * c cs) m) fn) :: * Source #

Methods

buildClient :: Proxy * ((* :> *) (MultipartRelated ((* ': c) cs) m) fn) -> Request -> Fn ((* :> *) (MultipartRelated ((* ': c) cs) m) fn) Source #

type Fn ((:>) * * (MultipartRelated ((:) * c cs) m) fn) Source # 
type Fn ((:>) * * (MultipartRelated ((:) * c cs) m) fn) = m -> Body -> Fn fn

buildSymbol :: forall n proxy. KnownSymbol n => proxy n -> Builder Source #

byteSymbol :: forall n proxy. KnownSymbol n => proxy n -> ByteString Source #

newtype Seconds Source #

An integral value representing seconds.

Constructors

Seconds Int 

Instances

Bounded Seconds Source # 
Enum Seconds Source # 
Eq Seconds Source # 

Methods

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

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

Integral Seconds Source # 
Data Seconds Source # 

Methods

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

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

toConstr :: Seconds -> Constr #

dataTypeOf :: Seconds -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Seconds Source # 
Ord Seconds Source # 
Read Seconds Source # 
Real Seconds Source # 
Show Seconds Source # 
Generic Seconds Source # 

Associated Types

type Rep Seconds :: * -> * #

Methods

from :: Seconds -> Rep Seconds x #

to :: Rep Seconds x -> Seconds #

type Rep Seconds Source # 
type Rep Seconds = D1 (MetaData "Seconds" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "Seconds" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype FieldMask Source #

Constructors

FieldMask Text 

Instances

Eq FieldMask Source # 
Data FieldMask Source # 

Methods

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

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

toConstr :: FieldMask -> Constr #

dataTypeOf :: FieldMask -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FieldMask Source # 
Read FieldMask Source # 
Show FieldMask Source # 
IsString FieldMask Source # 
Generic FieldMask Source # 

Associated Types

type Rep FieldMask :: * -> * #

ToJSON FieldMask Source # 
FromJSON FieldMask Source # 
ToHttpApiData FieldMask Source # 
FromHttpApiData FieldMask Source # 
type Rep FieldMask Source # 
type Rep FieldMask = D1 (MetaData "FieldMask" "Network.Google.Types" "gogol-core-0.2.0.1-DMRjkGcCN5oIvwmxsfDOv8" True) (C1 (MetaCons "FieldMask" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))