goggles-0.2: Interface to Google Cloud APIs

Safe HaskellNone
LanguageHaskell2010

Network.Goggles

Contents

Description

Dependencies

The examples require the following declarations (which in turn mean that the req and bytestring libraries are imported by the user's project). You will also need the OverloadedStrings language extension :

import qualified Data.ByteString.Lazy as LB
import Network.HTTP.Req (responseBody)
import Network.Goggles

Examples

This first example, listBucket, reads content from a cloud storage bucket:

  1. it loads the GCP credentials (username and RSA key),
  2. retrieves a token via OAuth2,
  3. performs a single call to the Cloud Storage API endpoint that lists the metadata related to the contents of a storage bucket, and
  4. returns the raw API data to the user as a lazy ByteString.
listBucket :: IO LB.ByteString
listBucket = do
  let usr = "...iam.gserviceaccount.com"
      bucket = "<my-gcs-bucket>"
      key = "<rsa_key>"
  pvtkey <- parseRSAPrivateKey key
  let creds = GCPServiceAccount pvtkey usr Nothing ""
  hdl <- createHandle creds scopesDefault
  responseBody <$> evalWebApiIO hdl (listObjects bucket)

Synopsis

Running WebApiM programs

createHandle :: HasCredentials c => Credentials c -> Options c -> IO (Handle c) Source #

Create a Handle with an empty token

evalWebApiIO :: Handle c -> WebApiM c a -> IO a Source #

Evaluate a WebApiM action, given a Handle.

NB : Assumes all exceptions are handled by throwM

Lifting IO programs into WebApiM

liftWebApiIO :: HasCredentials c => IO a -> WebApiM c a Source #

Lift an `IO a` action into the WebApiM monad, and catch synchronous exceptions, while rethrowing the asynchronous ones to IO

Types

newtype WebApiM c a Source #

The main type of the library. It can easily be re-used in libraries that interface with more than one cloud API provider because its type parameter c lets us be declare distinct behaviours for each.

Constructors

WebApiM 

Fields

Instances

Monad (WebApiM c) Source # 

Methods

(>>=) :: WebApiM c a -> (a -> WebApiM c b) -> WebApiM c b #

(>>) :: WebApiM c a -> WebApiM c b -> WebApiM c b #

return :: a -> WebApiM c a #

fail :: String -> WebApiM c a #

Functor (WebApiM c) Source # 

Methods

fmap :: (a -> b) -> WebApiM c a -> WebApiM c b #

(<$) :: a -> WebApiM c b -> WebApiM c a #

Applicative (WebApiM c) Source # 

Methods

pure :: a -> WebApiM c a #

(<*>) :: WebApiM c (a -> b) -> WebApiM c a -> WebApiM c b #

liftA2 :: (a -> b -> c) -> WebApiM c a -> WebApiM c b -> WebApiM c c #

(*>) :: WebApiM c a -> WebApiM c b -> WebApiM c b #

(<*) :: WebApiM c a -> WebApiM c b -> WebApiM c a #

HasCredentials c => Alternative (WebApiM c) Source # 

Methods

empty :: WebApiM c a #

(<|>) :: WebApiM c a -> WebApiM c a -> WebApiM c a #

some :: WebApiM c a -> WebApiM c [a] #

many :: WebApiM c a -> WebApiM c [a] #

HasCredentials c => MonadIO (WebApiM c) Source # 

Methods

liftIO :: IO a -> WebApiM c a #

HasCredentials c => MonadRandom (WebApiM c) Source #

the whole point of this parametrization is to have a distinct MonadHttp for each API provider/DSP

instance HasCredentials c => MonadHttp (Boo c) where handleHttpException = throwM

Methods

getRandomBytes :: ByteArray byteArray => Int -> WebApiM c byteArray #

HasCredentials c => MonadThrow (WebApiM c) Source # 

Methods

throwM :: Exception e => e -> WebApiM c a #

HasCredentials c => MonadCatch (WebApiM c) Source # 

Methods

catch :: Exception e => WebApiM c a -> (e -> WebApiM c a) -> WebApiM c a #

HasCredentials c => MonadReader (Handle c) (WebApiM c) Source # 

Methods

ask :: WebApiM c (Handle c) #

local :: (Handle c -> Handle c) -> WebApiM c a -> WebApiM c a #

reader :: (Handle c -> a) -> WebApiM c a #

Authentication

class HasCredentials c where Source #

This class

Minimal complete definition

tokenFetch

Associated Types

type Credentials c Source #

type Options c Source #

type TokenContent c Source #

Methods

tokenFetch :: WebApiM c (Token c) Source #

data Token c Source #

An authentication Token with an expiry date

Constructors

Token 

Fields

data Handle c Source #

A Handle contains all information necessary to communicating with a cloud API provider:

  • Authentication credentials (e.g. username/password)
  • Authentication token (used to authenticate every API call)
  • Options (e.g. GCP authentication scopes)

Constructors

Handle 

Instances

HasCredentials c => MonadReader (Handle c) (WebApiM c) Source # 

Methods

ask :: WebApiM c (Handle c) #

local :: (Handle c -> Handle c) -> WebApiM c a -> WebApiM c a #

reader :: (Handle c -> a) -> WebApiM c a #

Private key

parseRSAPrivateKey :: MonadThrow m => Text -> m PrivateKey Source #

Parse a chunk of text into an RSA private key. For Google Cloud Platform , this is the private key associated with the user's "service account" (for server-to-server API use)

https://console.cloud.google.com/apis/credentials

Note: do not supply the RSA header and footer or any newlines (they will be inserted by this function).

Exceptions