Copyright | (c) 2015 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
- newtype AuthKey = AuthKey Text
- newtype OAuthScope = OAuthScope {
- scopeToText :: Text
- newtype OAuthToken = OAuthToken {}
- newtype MediaDownload a = MediaDownload a
- data MediaUpload a = MediaUpload a RequestBody
- _Coerce :: (Coercible a b, Coercible b a) => Iso' a b
- _Default :: Monoid a => Iso' (Maybe a) a
- type Stream = ResumableSource (ResourceT IO) ByteString
- newtype ClientId = ClientId {}
- newtype ServiceId = ServiceId {}
- data Error
- data SerializeError = SerializeError' {}
- data ServiceError = ServiceError' {
- _serviceId :: !ServiceId
- _serviceStatus :: !Status
- _serviceHeaders :: ![Header]
- _serviceBody :: !(Maybe ByteString)
- class AsError a where
- data Service = Service {
- _svcId :: !ServiceId
- _svcHost :: !ByteString
- _svcPath :: !Builder
- _svcPort :: !Int
- _svcSecure :: !Bool
- _svcTimeout :: !(Maybe Seconds)
- defaultService :: ServiceId -> ByteString -> Service
- serviceHost :: Lens' Service ByteString
- servicePath :: Lens' Service Builder
- servicePort :: Lens' Service Int
- serviceSecure :: Lens' Service Bool
- serviceTimeout :: Lens' Service (Maybe Seconds)
- data Part = Part MediaType [(HeaderName, ByteString)] RequestBody
- data Payload
- = Body !MediaType !RequestBody
- | Related ![Part]
- data Request = Request {
- _rqPath :: !Builder
- _rqQuery :: !(DList (ByteString, Maybe ByteString))
- _rqHeaders :: !(DList (HeaderName, ByteString))
- _rqBody :: !(Maybe Payload)
- appendPath :: Request -> Builder -> Request
- appendPaths :: ToText a => Request -> [a] -> Request
- appendQuery :: Request -> ByteString -> Maybe Text -> Request
- appendHeader :: Request -> HeaderName -> Maybe Text -> Request
- setBody :: Request -> MediaType -> RequestBody -> Request
- setRelated :: Request -> [Part] -> Request
- data Client a = Client {
- _cliAccept :: !(Maybe MediaType)
- _cliMethod :: !Method
- _cliCheck :: !(Status -> Bool)
- _cliService :: !Service
- _cliRequest :: !Request
- _cliResponse :: !(Stream -> ResourceT IO (Either (String, ByteString) a))
- clientService :: Lens' (Client a) Service
- mime :: FromStream c a => Proxy c -> Method -> [Int] -> Request -> Service -> Client a
- discard :: Method -> [Int] -> Request -> Service -> Client ()
- client :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> Service -> Client a
- class Accept c => ToBody c a where
- toBody :: Proxy c -> a -> RequestBody
- class Accept c => FromStream c a where
- fromStream :: Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a)
- class GoogleRequest a where
- type Rs a :: *
- requestClient :: a -> Client (Rs a)
- class GoogleClient fn where
- type Fn fn :: *
- buildClient :: Proxy fn -> Request -> Fn fn
- data Captures s a
- data CaptureMode s m a
- data MultipartRelated cs m b
- sinkLBS :: Stream -> ResourceT IO ByteString
- buildText :: ToText 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
Documentation
newtype OAuthScope Source
newtype OAuthToken Source
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' | |
|
_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.
Service | |
|
defaultService :: ServiceId -> ByteString -> Service Source
A single part of a multipart message.
An intermediary request builder.
Request | |
|
appendPath :: Request -> Builder -> Request Source
appendPaths :: ToText a => Request -> [a] -> Request Source
appendQuery :: Request -> ByteString -> Maybe Text -> Request Source
appendHeader :: Request -> HeaderName -> Maybe Text -> Request Source
setRelated :: Request -> [Part] -> Request Source
A materialised 'http-client' request and associated response parser.
Client | |
|
clientService :: Lens' (Client a) Service Source
client :: (Stream -> ResourceT IO (Either (String, ByteString) a)) -> Maybe MediaType -> Method -> [Int] -> Request -> Service -> Client a Source
class Accept c => FromStream c a where Source
fromStream :: Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a) Source
class GoogleClient fn where Source
buildClient :: Proxy fn -> Request -> Fn fn Source
(KnownSymbol s, ToText a, GoogleClient fn) => GoogleClient ((:>) * * (Captures s a) fn) Source | |
type Fn ((:>) * * (Captures s a) fn) = [a] -> Fn fn Source |
data CaptureMode s m a Source
(KnownSymbol s, KnownSymbol m, ToText a, GoogleClient fn) => GoogleClient ((:>) * * (CaptureMode s m a) fn) Source | |
type Fn ((:>) * * (CaptureMode s m a) fn) = a -> Fn fn Source |
data MultipartRelated cs m b Source
(ToBody c m, ToBody OctetStream b, GoogleClient fn) => GoogleClient ((:>) * * (MultipartRelated ((:) * c cs) m b) fn) Source | |
type Fn ((:>) * * (MultipartRelated ((:) * c cs) m b) fn) = m -> b -> Fn fn 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