Copyright | (c) 2015-2016 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 | Haskell2010 |
- 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 Secret = Secret Text
- newtype MediaDownload a = MediaDownload a
- data MediaUpload a = MediaUpload a Body
- _Coerce :: (Coercible a b, Coercible b a) => Iso' a b
- _Default :: Monoid a => Iso' (Maybe a) a
- type Stream = ResumableSource (ResourceT IO) ByteString
- 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 Body = Body !MediaType !RequestBody
- bodyContentType :: Lens' Body MediaType
- data Request = Request {
- _rqPath :: !Builder
- _rqQuery :: !(DList (ByteString, Maybe ByteString))
- _rqHeaders :: !(DList (HeaderName, ByteString))
- _rqBody :: ![Body]
- appendPath :: Request -> Builder -> Request
- appendPaths :: ToHttpApiData a => Request -> [a] -> Request
- appendQuery :: Request -> ByteString -> Maybe Text -> Request
- appendHeader :: Request -> HeaderName -> Maybe Text -> Request
- setBody :: Request -> [Body] -> Request
- data Client a = Client {
- _cliAccept :: !(Maybe MediaType)
- _cliMethod :: !Method
- _cliCheck :: !(Status -> Bool)
- _cliService :: !ServiceConfig
- _cliRequest :: !Request
- _cliResponse :: !(Stream -> ResourceT IO (Either (String, ByteString) a))
- clientService :: Lens' (Client a) ServiceConfig
- mime :: FromStream c a => Proxy c -> Method -> [Int] -> Request -> ServiceConfig -> Client a
- discard :: Method -> [Int] -> Request -> ServiceConfig -> Client ()
- client :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> ServiceConfig -> Client a
- class Accept c => ToBody c a where
- class Accept c => FromStream c a where
- class GoogleRequest a where
- class GoogleClient fn where
- data Captures s a
- data CaptureMode s m a
- data MultipartRelated cs m
- sinkLBS :: Stream -> ResourceT IO ByteString
- buildText :: ToHttpApiData a => a -> Builder
- buildSymbol :: forall n proxy. KnownSymbol n => proxy n -> Builder
- byteSymbol :: forall n proxy. KnownSymbol n => proxy n -> ByteString
- newtype Seconds = Seconds Int
- seconds :: Seconds -> Int
- microseconds :: Seconds -> Int
- newtype FieldMask = FieldMask Text
Documentation
newtype OAuthScope Source #
An OAuth2 scope.
newtype AccessToken Source #
An OAuth2 access token.
newtype RefreshToken Source #
An OAuth2 refresh token.
A client identifier.
A service identifier.
An opaque client secret.
newtype MediaDownload a Source #
data MediaUpload a 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.
type Stream = ResumableSource (ResourceT IO) ByteString Source #
data SerializeError Source #
SerializeError' | |
|
data ServiceError Source #
ServiceError' | |
|
class AsError a where Source #
_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.
data ServiceConfig Source #
ServiceConfig | |
|
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.
An intermediary request builder.
Request | |
|
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.
Client | |
|
clientService :: Lens' (Client a) ServiceConfig Source #
mime :: FromStream c a => Proxy c -> Method -> [Int] -> Request -> ServiceConfig -> Client a Source #
client :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> ServiceConfig -> Client a Source #
class Accept c => FromStream c a where Source #
fromStream :: Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a) Source #
FromJSON a => FromStream JSON a Source # | |
FromStream OctetStream Stream Source # | |
class GoogleRequest a where Source #
requestClient :: a -> Client (Rs a) Source #
class GoogleClient fn where Source #
(KnownSymbol s, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (Captures s a) fn) Source # | |
type Fn ((:>) * * (Captures s a) fn) Source # | |
data CaptureMode s m a Source #
(KnownSymbol s, KnownSymbol m, ToHttpApiData a, GoogleClient fn) => GoogleClient ((:>) * * (CaptureMode s m a) fn) Source # | |
type Fn ((:>) * * (CaptureMode s m a) fn) Source # | |
data MultipartRelated cs m Source #
(ToBody c m, GoogleClient fn) => GoogleClient ((:>) * * (MultipartRelated ((:) * c cs) m) fn) Source # | |
type Fn ((:>) * * (MultipartRelated ((:) * c cs) m) fn) Source # | |
buildText :: ToHttpApiData a => a -> Builder Source #
buildSymbol :: forall n proxy. KnownSymbol n => proxy n -> Builder Source #
byteSymbol :: forall n proxy. KnownSymbol n => proxy n -> ByteString Source #
An integral value representing seconds.
microseconds :: Seconds -> Int Source #