Copyright | (c) 2015-2022 Brendan Hay <brendan.g.hay@gmail.com> |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | GHC2021 |
Gogol.Types
Description
Synopsis
- data AltJSON = AltJSON
- data AltMedia = AltMedia
- data Multipart = Multipart
- newtype OAuthScope = OAuthScope Text
- newtype AccessToken = AccessToken Text
- newtype RefreshToken = RefreshToken Text
- newtype ClientId = ClientId Text
- newtype ServiceId = ServiceId Text
- newtype GSecret = GSecret Text
- newtype MediaDownload a = MediaDownload a
- data MediaUpload a = MediaUpload a GBody
- _Coerce :: (Coercible a b, Coercible b a) => Iso' a b
- _Default :: Monoid a => Iso' (Maybe a) a
- type Stream = ConduitM () ByteString (ResourceT IO) ()
- data Error
- data SerializeError = SerializeError' {}
- data ServiceError = ServiceError' {
- _serviceId :: !ServiceId
- _serviceStatus :: !Status
- _serviceHeaders :: ![Header]
- _serviceBody :: !(Maybe ByteString)
- class AsError a where
- data ServiceConfig = ServiceConfig {
- _svcId :: !ServiceId
- _svcHost :: !ByteString
- _svcPath :: !Builder
- _svcPort :: !Int
- _svcSecure :: !Bool
- _svcTimeout :: !(Maybe Seconds)
- defaultService :: ServiceId -> ByteString -> ServiceConfig
- serviceHost :: Lens' ServiceConfig ByteString
- servicePort :: Lens' ServiceConfig Int
- servicePath :: Lens' ServiceConfig Builder
- serviceSecure :: Lens' ServiceConfig Bool
- serviceTimeout :: Lens' ServiceConfig (Maybe Seconds)
- data GBody = GBody !MediaType !RequestBody
- bodyContentType :: Lens' GBody MediaType
- data Request = Request {
- _rqPath :: !Builder
- _rqQuery :: !(DList (ByteString, Maybe ByteString))
- _rqHeaders :: !(DList (HeaderName, ByteString))
- _rqBody :: ![GBody]
- appendPath :: Request -> Builder -> Request
- appendPaths :: ToHttpApiData a => Request -> [a] -> Request
- appendQuery :: Request -> ByteString -> Maybe Text -> Request
- appendHeader :: Request -> HeaderName -> Maybe Text -> Request
- setBody :: Request -> [GBody] -> Request
- data GClient a = GClient {
- _cliAccept :: !(Maybe MediaType)
- _cliMethod :: !Method
- _cliCheck :: !(Status -> Bool)
- _cliService :: !ServiceConfig
- _cliRequest :: !Request
- _cliResponse :: !(Stream -> ResourceT IO (Either (String, ByteString) a))
- clientService :: forall a f. Functor f => (ServiceConfig -> f ServiceConfig) -> GClient a -> f (GClient a)
- mime :: forall {k} (c :: k) a. FromStream c a => Proxy c -> Method -> [Int] -> Request -> ServiceConfig -> GClient a
- discard :: Method -> [Int] -> Request -> ServiceConfig -> GClient ()
- gClient :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> ServiceConfig -> GClient a
- class Accept c => ToBody (c :: k) a where
- class Accept c => FromStream (c :: k) a where
- fromStream :: Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a)
- class GoogleRequest a where
- class GoogleClient (fn :: k) where
- type Fn (fn :: k)
- buildClient :: Proxy fn -> Request -> Fn fn
- data Captures (s :: Symbol) (a :: k)
- data CaptureMode (s :: Symbol) (m :: Symbol) (a :: k)
- data MultipartRelated (cs :: [Type]) (m :: k)
- sinkLBS :: Stream -> ResourceT IO ByteString
- buildText :: ToHttpApiData a => a -> Builder
- buildSymbol :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> Builder
- byteSymbol :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> ByteString
- newtype Seconds = Seconds Int
- seconds :: Seconds -> Int
- microseconds :: Seconds -> Int
- newtype FieldMask = FieldMask {}
Documentation
Constructors
AltJSON |
Instances
Generic AltJSON Source # | |
Defined in Gogol.Types | |
Read AltJSON Source # | |
Show AltJSON Source # | |
Eq AltJSON Source # | |
Ord AltJSON Source # | |
ToHttpApiData AltJSON Source # | |
Defined in Gogol.Types Methods toUrlPiece :: AltJSON -> Text # toEncodedUrlPiece :: AltJSON -> Builder # toHeader :: AltJSON -> ByteString # toQueryParam :: AltJSON -> Text # toEncodedQueryParam :: AltJSON -> Builder # | |
type Rep AltJSON Source # | |
Constructors
AltMedia |
Instances
Generic AltMedia Source # | |
Defined in Gogol.Types | |
Read AltMedia Source # | |
Show AltMedia Source # | |
Eq AltMedia Source # | |
Ord AltMedia Source # | |
Defined in Gogol.Types | |
ToHttpApiData AltMedia Source # | |
Defined in Gogol.Types Methods toUrlPiece :: AltMedia -> Text # toEncodedUrlPiece :: AltMedia -> Builder # toHeader :: AltMedia -> ByteString # toQueryParam :: AltMedia -> Text # toEncodedQueryParam :: AltMedia -> Builder # | |
GoogleClient fn => GoogleClient (AltMedia :> fn :: Type) Source # | |
type Rep AltMedia Source # | |
type Fn (AltMedia :> fn :: Type) Source # | |
Constructors
Multipart |
Instances
Generic Multipart Source # | |
Defined in Gogol.Types | |
Read Multipart Source # | |
Show Multipart Source # | |
Eq Multipart Source # | |
Ord Multipart Source # | |
ToHttpApiData Multipart Source # | |
Defined in Gogol.Types Methods toUrlPiece :: Multipart -> Text # toEncodedUrlPiece :: Multipart -> Builder # toHeader :: Multipart -> ByteString # toQueryParam :: Multipart -> Text # toEncodedQueryParam :: Multipart -> Builder # | |
type Rep Multipart Source # | |
newtype OAuthScope Source #
An OAuth2 scope.
Constructors
OAuthScope Text |
Instances
newtype AccessToken Source #
An OAuth2 access token.
Constructors
AccessToken Text |
Instances
FromJSON AccessToken Source # | |||||
Defined in Gogol.Types | |||||
ToJSON AccessToken Source # | |||||
Defined in Gogol.Types Methods toJSON :: AccessToken -> Value # toEncoding :: AccessToken -> Encoding # toJSONList :: [AccessToken] -> Value # toEncodingList :: [AccessToken] -> Encoding # omitField :: AccessToken -> Bool # | |||||
IsString AccessToken Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> AccessToken # | |||||
Generic AccessToken Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read AccessToken Source # | |||||
Defined in Gogol.Types Methods readsPrec :: Int -> ReadS AccessToken # readList :: ReadS [AccessToken] # readPrec :: ReadPrec AccessToken # readListPrec :: ReadPrec [AccessToken] # | |||||
Show AccessToken Source # | |||||
Defined in Gogol.Types Methods showsPrec :: Int -> AccessToken -> ShowS # show :: AccessToken -> String # showList :: [AccessToken] -> ShowS # | |||||
Eq AccessToken Source # | |||||
Defined in Gogol.Types | |||||
Ord AccessToken Source # | |||||
Defined in Gogol.Types Methods compare :: AccessToken -> AccessToken -> Ordering # (<) :: AccessToken -> AccessToken -> Bool # (<=) :: AccessToken -> AccessToken -> Bool # (>) :: AccessToken -> AccessToken -> Bool # (>=) :: AccessToken -> AccessToken -> Bool # max :: AccessToken -> AccessToken -> AccessToken # min :: AccessToken -> AccessToken -> AccessToken # | |||||
FromHttpApiData AccessToken Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text AccessToken # parseHeader :: ByteString -> Either Text AccessToken # parseQueryParam :: Text -> Either Text AccessToken # | |||||
ToHttpApiData AccessToken Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: AccessToken -> Text # toEncodedUrlPiece :: AccessToken -> Builder # toHeader :: AccessToken -> ByteString # toQueryParam :: AccessToken -> Text # | |||||
type Rep AccessToken Source # | |||||
Defined in Gogol.Types type Rep AccessToken = D1 ('MetaData "AccessToken" "Gogol.Types" "gogol-core-1.0.0.0-6X37EOsTod1GwsjdWl3qQA" 'True) (C1 ('MetaCons "AccessToken" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
newtype RefreshToken Source #
An OAuth2 refresh token.
Constructors
RefreshToken Text |
Instances
FromJSON RefreshToken Source # | |||||
Defined in Gogol.Types | |||||
ToJSON RefreshToken Source # | |||||
Defined in Gogol.Types Methods toJSON :: RefreshToken -> Value # toEncoding :: RefreshToken -> Encoding # toJSONList :: [RefreshToken] -> Value # toEncodingList :: [RefreshToken] -> Encoding # omitField :: RefreshToken -> Bool # | |||||
IsString RefreshToken Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> RefreshToken # | |||||
Generic RefreshToken Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read RefreshToken Source # | |||||
Defined in Gogol.Types Methods readsPrec :: Int -> ReadS RefreshToken # readList :: ReadS [RefreshToken] # | |||||
Show RefreshToken Source # | |||||
Defined in Gogol.Types Methods showsPrec :: Int -> RefreshToken -> ShowS # show :: RefreshToken -> String # showList :: [RefreshToken] -> ShowS # | |||||
Eq RefreshToken Source # | |||||
Defined in Gogol.Types | |||||
Ord RefreshToken Source # | |||||
Defined in Gogol.Types Methods compare :: RefreshToken -> RefreshToken -> Ordering # (<) :: RefreshToken -> RefreshToken -> Bool # (<=) :: RefreshToken -> RefreshToken -> Bool # (>) :: RefreshToken -> RefreshToken -> Bool # (>=) :: RefreshToken -> RefreshToken -> Bool # max :: RefreshToken -> RefreshToken -> RefreshToken # min :: RefreshToken -> RefreshToken -> RefreshToken # | |||||
FromHttpApiData RefreshToken Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text RefreshToken # parseHeader :: ByteString -> Either Text RefreshToken # parseQueryParam :: Text -> Either Text RefreshToken # | |||||
ToHttpApiData RefreshToken Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: RefreshToken -> Text # toEncodedUrlPiece :: RefreshToken -> Builder # toHeader :: RefreshToken -> ByteString # toQueryParam :: RefreshToken -> Text # | |||||
type Rep RefreshToken Source # | |||||
Defined in Gogol.Types type Rep RefreshToken = D1 ('MetaData "RefreshToken" "Gogol.Types" "gogol-core-1.0.0.0-6X37EOsTod1GwsjdWl3qQA" 'True) (C1 ('MetaCons "RefreshToken" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
A client identifier.
Instances
FromJSON ClientId Source # | |||||
Defined in Gogol.Types | |||||
ToJSON ClientId Source # | |||||
IsString ClientId Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> ClientId # | |||||
Generic ClientId Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read ClientId Source # | |||||
Show ClientId Source # | |||||
Eq ClientId Source # | |||||
Ord ClientId Source # | |||||
Defined in Gogol.Types | |||||
FromHttpApiData ClientId Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text ClientId # parseHeader :: ByteString -> Either Text ClientId # | |||||
ToHttpApiData ClientId Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: ClientId -> Text # toEncodedUrlPiece :: ClientId -> Builder # toHeader :: ClientId -> ByteString # toQueryParam :: ClientId -> Text # toEncodedQueryParam :: ClientId -> Builder # | |||||
type Rep ClientId Source # | |||||
Defined in Gogol.Types |
A service identifier.
Instances
FromJSON ServiceId Source # | |||||
Defined in Gogol.Types | |||||
ToJSON ServiceId Source # | |||||
IsString ServiceId Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> ServiceId # | |||||
Generic ServiceId Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read ServiceId Source # | |||||
Show ServiceId Source # | |||||
Eq ServiceId Source # | |||||
Ord ServiceId Source # | |||||
FromHttpApiData ServiceId Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text ServiceId # parseHeader :: ByteString -> Either Text ServiceId # | |||||
ToHttpApiData ServiceId Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: ServiceId -> Text # toEncodedUrlPiece :: ServiceId -> Builder # toHeader :: ServiceId -> ByteString # toQueryParam :: ServiceId -> Text # toEncodedQueryParam :: ServiceId -> Builder # | |||||
type Rep ServiceId Source # | |||||
Defined in Gogol.Types |
An opaque client secret.
Instances
FromJSON GSecret Source # | |||||
Defined in Gogol.Types | |||||
ToJSON GSecret Source # | |||||
IsString GSecret Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> GSecret # | |||||
Generic GSecret Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read GSecret Source # | |||||
Show GSecret Source # | |||||
Eq GSecret Source # | |||||
Ord GSecret Source # | |||||
FromHttpApiData GSecret Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text GSecret # parseHeader :: ByteString -> Either Text GSecret # | |||||
ToHttpApiData GSecret Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: GSecret -> Text # toEncodedUrlPiece :: GSecret -> Builder # toHeader :: GSecret -> ByteString # toQueryParam :: GSecret -> Text # toEncodedQueryParam :: GSecret -> Builder # | |||||
type Rep GSecret Source # | |||||
Defined in Gogol.Types |
newtype MediaDownload a Source #
Constructors
MediaDownload a |
data MediaUpload a Source #
Constructors
MediaUpload a GBody |
_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.
Instances
Exception Error Source # | |
Defined in Gogol.Types Methods toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Show Error Source # | |
AsError Error Source # | |
Defined in Gogol.Types |
data SerializeError Source #
Constructors
SerializeError' | |
Fields
|
Instances
Show SerializeError Source # | |
Defined in Gogol.Types Methods showsPrec :: Int -> SerializeError -> ShowS # show :: SerializeError -> String # showList :: [SerializeError] -> ShowS # | |
Eq SerializeError Source # | |
Defined in Gogol.Types Methods (==) :: SerializeError -> SerializeError -> Bool # (/=) :: SerializeError -> SerializeError -> Bool # |
data ServiceError Source #
Constructors
ServiceError' | |
Fields
|
Instances
Show ServiceError Source # | |
Defined in Gogol.Types Methods showsPrec :: Int -> ServiceError -> ShowS # show :: ServiceError -> String # showList :: [ServiceError] -> ShowS # | |
Eq ServiceError Source # | |
Defined in Gogol.Types |
class AsError a where Source #
Minimal complete definition
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.
Instances
AsError SomeException Source # | |
AsError Error Source # | |
Defined in Gogol.Types |
data ServiceConfig Source #
Constructors
ServiceConfig | |
Fields
|
defaultService :: ServiceId -> ByteString -> ServiceConfig Source #
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.
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
IsString GBody Source # | |
Defined in Gogol.Types Methods fromString :: String -> GBody # |
An intermediary request builder.
Constructors
Request | |
Fields
|
appendPaths :: ToHttpApiData a => Request -> [a] -> Request Source #
appendQuery :: Request -> ByteString -> Maybe Text -> Request Source #
appendHeader :: Request -> HeaderName -> Maybe Text -> Request Source #
A materialised 'http-client' request and associated response parser.
Constructors
GClient | |
Fields
|
clientService :: forall a f. Functor f => (ServiceConfig -> f ServiceConfig) -> GClient a -> f (GClient a) Source #
mime :: forall {k} (c :: k) a. FromStream c a => Proxy c -> Method -> [Int] -> Request -> ServiceConfig -> GClient a Source #
gClient :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> ServiceConfig -> GClient a Source #
class Accept c => ToBody (c :: k) a where Source #
Instances
ToJSON a => ToBody JSON a Source # | |
ToBody OctetStream ByteString Source # | |
Defined in Gogol.Types Methods toBody :: Proxy OctetStream -> ByteString -> GBody Source # | |
ToBody OctetStream ByteString Source # | |
Defined in Gogol.Types Methods toBody :: Proxy OctetStream -> ByteString -> GBody Source # | |
ToBody PlainText ByteString Source # | |
Defined in Gogol.Types | |
ToBody PlainText ByteString Source # | |
Defined in Gogol.Types |
class Accept c => FromStream (c :: k) a where Source #
Methods
fromStream :: Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a) Source #
Instances
FromJSON a => FromStream JSON a Source # | |
Defined in Gogol.Types | |
FromStream OctetStream Stream Source # | |
Defined in Gogol.Types Methods fromStream :: Proxy OctetStream -> Stream -> ResourceT IO (Either (String, ByteString) Stream) Source # |
class GoogleRequest a where Source #
Methods
requestClient :: a -> GClient (Rs a) Source #
class GoogleClient (fn :: k) where Source #
Instances
(GoogleClient a, GoogleClient b) => GoogleClient (a :<|> b :: Type) Source # | |||||||||
GoogleClient (Delete (c ': cs) () :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
FromStream c a => GoogleClient (Delete (c ': cs) a :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
GoogleClient (Get (c ': cs) () :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
FromStream c a => GoogleClient (Get (c ': cs) a :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
GoogleClient (Patch (c ': cs) () :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
FromStream c a => GoogleClient (Patch (c ': cs) a :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
GoogleClient (Post cs () :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
(FromStream c a, cs' ~ (c ': cs)) => GoogleClient (Post cs' a :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
GoogleClient (Put (c ': cs) () :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
FromStream c a => GoogleClient (Put (c ': cs) a :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
| |||||||||
(KnownSymbol s, GoogleClient fn) => GoogleClient (s :> fn :: Type) Source # | |||||||||
GoogleClient fn => GoogleClient (AltMedia :> fn :: Type) Source # | |||||||||
(KnownSymbol s, KnownSymbol m, ToHttpApiData a, GoogleClient fn) => GoogleClient (CaptureMode s m a :> fn :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
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 :: Type) Source # | |||||||||
(ToBody c m, GoogleClient fn) => GoogleClient (MultipartRelated (c ': cs) m :> fn :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
Methods buildClient :: Proxy (MultipartRelated (c ': cs) m :> fn) -> Request -> Fn (MultipartRelated (c ': cs) m :> fn) Source # | |||||||||
(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient (Capture s a :> fn :: Type) Source # | |||||||||
(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient (Header s a :> fn :: Type) Source # | |||||||||
(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient (QueryParam s a :> fn :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
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 :: Type) Source # | |||||||||
Defined in Gogol.Types Associated Types
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 :: Type) Source # | |||||||||
data Captures (s :: Symbol) (a :: k) Source #
Instances
(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient (Captures s a :> fn :: Type) Source # | |
type Fn (Captures s a :> fn :: Type) Source # | |
data CaptureMode (s :: Symbol) (m :: Symbol) (a :: k) Source #
Instances
(KnownSymbol s, KnownSymbol m, ToHttpApiData a, GoogleClient fn) => GoogleClient (CaptureMode s m a :> fn :: Type) Source # | |||||
Defined in Gogol.Types Associated Types
Methods buildClient :: Proxy (CaptureMode s m a :> fn) -> Request -> Fn (CaptureMode s m a :> fn) Source # | |||||
type Fn (CaptureMode s m a :> fn :: Type) Source # | |||||
Defined in Gogol.Types |
data MultipartRelated (cs :: [Type]) (m :: k) Source #
Instances
(ToBody c m, GoogleClient fn) => GoogleClient (MultipartRelated (c ': cs) m :> fn :: Type) Source # | |||||
Defined in Gogol.Types Associated Types
Methods buildClient :: Proxy (MultipartRelated (c ': cs) m :> fn) -> Request -> Fn (MultipartRelated (c ': cs) m :> fn) Source # | |||||
type Fn (MultipartRelated (c ': cs) m :> fn :: Type) Source # | |||||
Defined in Gogol.Types |
buildText :: ToHttpApiData a => a -> Builder Source #
buildSymbol :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> Builder Source #
byteSymbol :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> ByteString Source #
An integral value representing seconds.
Instances
Bounded Seconds Source # | |||||
Enum Seconds Source # | |||||
Generic Seconds Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Num Seconds Source # | |||||
Read Seconds Source # | |||||
Integral Seconds Source # | |||||
Defined in Gogol.Types | |||||
Real Seconds Source # | |||||
Defined in Gogol.Types Methods toRational :: Seconds -> Rational # | |||||
Show Seconds Source # | |||||
Eq Seconds Source # | |||||
Ord Seconds Source # | |||||
type Rep Seconds Source # | |||||
Defined in Gogol.Types |
microseconds :: Seconds -> Int Source #
Constructors
FieldMask | |
Fields |
Instances
FromJSON FieldMask Source # | |||||
Defined in Gogol.Types | |||||
ToJSON FieldMask Source # | |||||
IsString FieldMask Source # | |||||
Defined in Gogol.Types Methods fromString :: String -> FieldMask # | |||||
Generic FieldMask Source # | |||||
Defined in Gogol.Types Associated Types
| |||||
Read FieldMask Source # | |||||
Show FieldMask Source # | |||||
Eq FieldMask Source # | |||||
Ord FieldMask Source # | |||||
FromHttpApiData FieldMask Source # | |||||
Defined in Gogol.Types Methods parseUrlPiece :: Text -> Either Text FieldMask # parseHeader :: ByteString -> Either Text FieldMask # | |||||
ToHttpApiData FieldMask Source # | |||||
Defined in Gogol.Types Methods toUrlPiece :: FieldMask -> Text # toEncodedUrlPiece :: FieldMask -> Builder # toHeader :: FieldMask -> ByteString # toQueryParam :: FieldMask -> Text # toEncodedQueryParam :: FieldMask -> Builder # | |||||
type Rep FieldMask Source # | |||||
Defined in Gogol.Types |