goggles-0.1.0.2: Interface to Google Cloud APIs

Safe HaskellNone
LanguageHaskell2010

Network.Goggles

Contents

Description

This module is the entry point to the goggles library, which is a Haskell interface to the cloud services hosted by Google (e.g. storage, compute, mail, etc.: https://cloud.google.com/) .

Most Google Cloud Platform (GCP) functionality requires authentication, which must be obtained beforehand from the website either with a free trial or a paid plan.

From now on, we'll assume the user has such credentials and is able to load them alongside this library.

The examples require the following declarations (which in turn mean that the req and bytestring libraries are imported by the user's project):


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 <$> evalCloudIO hdl (listObjects bucket)

Synopsis

API endpoints

Google Cloud Storage

getObject :: Text -> Text -> Cloud GCP LbsResponse Source #

`getObject b p` retrieves the contents of a GCS object (of full path p) in bucket b

listObjects :: Text -> Cloud GCP LbsResponse Source #

`listObjects b` retrieves a list of objects stored in bucket b

putObject :: Text -> Text -> ByteString -> Cloud GCP LbsResponse Source #

`putObject b p body` uploads a bytestring body into a GCS object (of full path p) in bucket b

GCP Authentication scopes

scopesDefault :: [Text] Source #

OAuth2 scopes for the various Google Cloud Platform services.

Please refer to

https://developers.google.com/identity/protocols/googlescopes

for the full list

Running Cloud programs

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

Create a Handle with an empty token

evalCloudIO :: Handle c -> Cloud c a -> IO a Source #

Evaluate a Cloud action, given a Handle.

NB : Assumes all exceptions are handled by throwM

Executing IO actions within Cloud

liftCloudIO :: HasCredentials c => IO a -> Cloud c a Source #

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

Types

data GCP Source #

Instances

HasCredentials GCP Source # 

Associated Types

type Credentials GCP :: * Source #

type Options GCP :: * Source #

type TokenContent GCP :: * Source #

Show (Token GCP) Source # 
MonadHttp (Cloud GCP) Source #

We can provide a custom http exception handler rather than throwing exceptions with this instance

type Credentials GCP Source # 
type Options GCP Source # 
type Options GCP = [Text]
type TokenContent GCP Source # 

data GCPServiceAccount Source #

Credentials for Google Cloud Platform

Constructors

GCPServiceAccount 

Fields

newtype Cloud 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

Cloud 

Fields

Instances

Monad (Cloud c) Source # 

Methods

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

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

return :: a -> Cloud c a #

fail :: String -> Cloud c a #

Functor (Cloud c) Source # 

Methods

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

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

Applicative (Cloud c) Source # 

Methods

pure :: a -> Cloud c a #

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

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

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

HasCredentials c => Alternative (Cloud c) Source # 

Methods

empty :: Cloud c a #

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

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

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

HasCredentials c => MonadIO (Cloud c) Source # 

Methods

liftIO :: IO a -> Cloud c a #

HasCredentials c => MonadRandom (Cloud 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 -> Cloud c byteArray #

HasCredentials c => MonadThrow (Cloud c) Source # 

Methods

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

HasCredentials c => MonadCatch (Cloud c) Source # 

Methods

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

MonadHttp (Cloud GCP) #

We can provide a custom http exception handler rather than throwing exceptions with this instance

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

Methods

ask :: Cloud c (Handle c) #

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

reader :: (Handle c -> a) -> Cloud 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 :: Cloud c (Token c) Source #

Instances

data Token c Source #

An authentication Token with an expiry date

Constructors

Token 

Fields

Instances

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) (Cloud c) Source # 

Methods

ask :: Cloud c (Handle c) #

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

reader :: (Handle c -> a) -> Cloud 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