gogol-0.3.0: Comprehensive Google Services SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.Auth

Contents

Description

Explicitly specify your Google credentials, or retrieve them from the underlying OS.

Synopsis

Credentials

data Credentials s Source #

The supported credential mechanisms.

Constructors

FromMetadata !ServiceId

Obtain and refresh access tokens from the underlying GCE host metadata at http://169.254.169.254.

FromClient !OAuthClient !(OAuthCode s)

Obtain and refresh access tokens using the specified client secret and authorization code obtained from.

See the OAuth2 Installed Application documentation for more information.

FromAccount !ServiceAccount

Use the specified service_account and scopes to sign and request an access token. The ServiceAccount will also be used for subsequent token refreshes.

A ServiceAccount is typically generated through the Google Developer Console.

FromUser !AuthorizedUser

Use the specified authorized_user to obtain and refresh access tokens.

An AuthorizedUser is typically created by the gcloud init command of the Google CloudSDK Tools.

Instances

Application Default Credentials

getApplicationDefault :: (MonadIO m, MonadCatch m) => Manager -> m (Credentials s) Source #

Performs credentials discovery in the following order:

  1. Read the default credentials from a file specified by the environment variable GOOGLE_APPLICATION_CREDENTIALS if it exists.
  2. Read the platform equivalent of ~/.config/gcloud/application_default_credentials.json if it exists. The ~/.config component of the path can be overriden by the environment variable CLOUDSDK_CONFIG if it exists.
  3. Retrieve the default service account application credentials if running on GCE. The environment variable NO_GCE_CHECK can be used to skip this check if set to a truthy value such as 1 or true.

The specified Scopes are used to authorize any service_account that is found with the appropriate OAuth2 scopes, otherwise they are not used. See the top-level module of each individual gogol-* library for a list of available scopes, such as Network.Google.Compute.computeScope.

See: Application Default Credentials

fromWellKnownPath :: (MonadIO m, MonadCatch m) => m (Credentials s) Source #

Attempt to load either a service_account or authorized_user formatted file to obtain the credentials neccessary to perform a token refresh.

The specified Scopes are used to authorize any service_account that is found with the appropriate scopes, otherwise they are not used. See the top-level module of each individual gogol-* library for a list of available scopes, such as Network.Google.Compute.computeScope.

See: cloudSDKConfigPath, defaultCredentialsPath.

fromFilePath :: (MonadIO m, MonadCatch m) => FilePath -> m (Credentials s) Source #

Attempt to load either a service_account or authorized_user formatted file to obtain the credentials neccessary to perform a token refresh from the specified file.

The specified Scopes are used to authorize any service_account that is found with the appropriate scopes, otherwise they are not used. See the top-level module of each individual gogol-* library for a list of available scopes, such as Network.Google.Compute.computeScope.

saveAuthorizedUserToWellKnownPath Source #

Arguments

:: (MonadIO m, MonadCatch m) 
=> Bool

Force to save if True

-> AuthorizedUser 
-> m () 

Save AuthorizedUser See: cloudSDKConfigPath, defaultCredentialsPath.

saveAuthorizedUser Source #

Arguments

:: (MonadIO m, MonadCatch m) 
=> FilePath 
-> Bool

Force to save if True

-> AuthorizedUser 
-> m () 

Save AuthorizedUser

Installed Application Credentials

installedApplication :: OAuthClient -> OAuthCode s -> Credentials s Source #

Create new Installed Application credentials.

Since it is intended that the user opens the URL generated by formURL in a browser and the resulting OAuthCode is then received out-of-band, you must ensure that the scopes passed to formURL and the type of OAuthCode correctly match, otherwise an authorization error will occur.

For example, doing this via getLine and copy-paste:

{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy     (Proxy (..))
import Data.Text      as T
import Data.Text.IO   as T
import System.Exit    (exitFailure)
import System.Info    (os)
import System.Process (rawSystem)
redirectPrompt :: AllowScopes (s :: [Symbol]) => OAuthClient -> proxy s -> IO (OAuthCode s)
redirectPrompt c p = do
  let url = formURL c p
  T.putStrLn $ "Opening URL " `T.append` url
  _ <- case os of
    "darwin" -> rawSystem "open"     [unpack url]
    "linux"  -> rawSystem "xdg-open" [unpack url]
    _        -> T.putStrLn "Unsupported OS" >> exitFailure
  T.putStrLn "Please input the authorisation code: "
  OAuthCode <$> T.getLine

This ensures the scopes passed to formURL and the type of OAuthCode s are correct.

formURL :: AllowScopes (s :: [Symbol]) => OAuthClient -> proxy s -> Text Source #

Given an OAuthClient and a list of scopes to authorize, construct a URL that can be used to obtain the OAuthCode.

See: Forming the URL.

Authorizing Requests

authorize :: (MonadIO m, MonadCatch m, AllowScopes s) => Request -> Store s -> Logger -> Manager -> m Request Source #

Apply the (by way of possible token refresh) a bearer token to the authentication header of a request.

Thread-safe Storage

data Store s Source #

Data store which ensures thread-safe access of credentials.

initStore :: (MonadIO m, MonadCatch m, AllowScopes s) => Credentials s -> Logger -> Manager -> m (Store s) Source #

Construct storage containing the credentials which have not yet been exchanged or refreshed.

retrieveAuthFromStore :: (MonadIO m, MonadCatch m, AllowScopes s) => Store s -> m (Auth s) Source #

Retrieve auth from storage

data Auth s Source #

An OAuthToken that can potentially be expired, with the original credentials that can be used to perform a refresh.

Constructors

Auth 

Fields

authToAuthorizedUser :: AllowScopes s => Auth s -> Either Text AuthorizedUser Source #

authToAuthorizedUser converts Auth into an AuthorizedUser by returning Right if there is a FromClient-constructed Credentials and a refreshed token; otherwise, returning Left with error message.

exchange :: forall m s. (MonadIO m, MonadCatch m, AllowScopes s) => Credentials s -> Logger -> Manager -> m (Auth s) Source #

Perform the initial credentials exchange to obtain a valid OAuthToken suitable for authorizing requests.

refresh :: forall m s. (MonadIO m, MonadCatch m, AllowScopes s) => Auth s -> Logger -> Manager -> m (Auth s) Source #

Refresh an existing OAuthToken.

Default Constants

checkGCEVar :: String Source #

The NO_GCE_CHECK environment variable.

cloudSDKConfigDir :: String Source #

The environment variable name which is used to specify the directory containing the application_default_credentials.json generated by gcloud init.

defaultCredentialsFile :: String Source #

The environment variable pointing the file with local Application Default Credentials.

Handling Errors

class AsAuthError a where Source #

Minimal complete definition

_AuthError

Methods

_AuthError :: Prism' a AuthError Source #

A general authentication error.

_RetrievalError :: Prism' a HttpException Source #

An error occured while communicating over HTTP with either then local metadata or remote accounts.google.com endpoints.

_MissingFileError :: Prism' a FilePath Source #

The specified default credentials file could not be found.

_InvalidFileError :: Prism' a (FilePath, Text) Source #

An error occured parsing the default credentials file.

_TokenRefreshError :: Prism' a (Status, Text, Maybe Text) Source #

An error occured when attempting to refresh a token.

OAuth Types

data OAuthClient Source #

A client identifier and accompanying secret used to obtain/refresh a token.

Constructors

OAuthClient 

data OAuthToken s Source #

An OAuth bearer type token of the following form:

{
  \"token_type\": \"Bearer\",
  \"access_token\": \"eyJhbGci...\",
  \"refresh_token\": \"1/B3gq9K...\",
  \"expires_in\": 3600,
  ...
}

The _tokenAccess field will be inserted verbatim into the Authorization: Bearer ... header for all HTTP requests.

newtype OAuthCode s Source #

An OAuth client authorization code.

Constructors

OAuthCode Text 

Instances

Eq (OAuthCode s) Source # 

Methods

(==) :: OAuthCode s -> OAuthCode s -> Bool #

(/=) :: OAuthCode s -> OAuthCode s -> Bool #

Ord (OAuthCode s) Source # 
Read (OAuthCode s) Source # 
Show (OAuthCode s) Source # 
IsString (OAuthCode s) Source # 

Methods

fromString :: String -> OAuthCode s #

Generic (OAuthCode s) Source # 

Associated Types

type Rep (OAuthCode s) :: * -> * #

Methods

from :: OAuthCode s -> Rep (OAuthCode s) x #

to :: Rep (OAuthCode s) x -> OAuthCode s #

ToJSON (OAuthCode s) Source # 
FromJSON (OAuthCode s) Source # 
ToHttpApiData (OAuthCode s) Source # 
type Rep (OAuthCode s) Source # 
type Rep (OAuthCode s) = D1 (MetaData "OAuthCode" "Network.Google.Internal.Auth" "gogol-0.3.0-8FoReT1WqFDEy1GCNsi9p9" True) (C1 (MetaCons "OAuthCode" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype OAuthScope :: * #

An OAuth2 scope.

Constructors

OAuthScope Text 

Instances

Eq OAuthScope 
Ord OAuthScope 
Read OAuthScope 
Show OAuthScope 
IsString OAuthScope 
Generic OAuthScope 

Associated Types

type Rep OAuthScope :: * -> * #

ToJSON OAuthScope 
FromJSON OAuthScope 
FromHttpApiData OAuthScope 
ToHttpApiData OAuthScope 
type Rep OAuthScope 
type Rep OAuthScope = D1 (MetaData "OAuthScope" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "OAuthScope" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Re-exported Types

newtype AccessToken :: * #

An OAuth2 access token.

Constructors

AccessToken Text 

Instances

Eq AccessToken 
Ord AccessToken 
Read AccessToken 
Show AccessToken 
IsString AccessToken 
Generic AccessToken 

Associated Types

type Rep AccessToken :: * -> * #

ToJSON AccessToken 
FromJSON AccessToken 
FromHttpApiData AccessToken 
ToHttpApiData AccessToken 
type Rep AccessToken 
type Rep AccessToken = D1 (MetaData "AccessToken" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "AccessToken" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype RefreshToken :: * #

An OAuth2 refresh token.

Constructors

RefreshToken Text 

Instances

Eq RefreshToken 
Ord RefreshToken 
Read RefreshToken 
Show RefreshToken 
IsString RefreshToken 
Generic RefreshToken 

Associated Types

type Rep RefreshToken :: * -> * #

ToJSON RefreshToken 
FromJSON RefreshToken 
FromHttpApiData RefreshToken 
ToHttpApiData RefreshToken 
type Rep RefreshToken 
type Rep RefreshToken = D1 (MetaData "RefreshToken" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "RefreshToken" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Secret :: * #

An opaque client secret.

Constructors

Secret Text 

Instances

Eq Secret 

Methods

(==) :: Secret -> Secret -> Bool #

(/=) :: Secret -> Secret -> Bool #

Ord Secret 
Read Secret 
Show Secret 
IsString Secret 

Methods

fromString :: String -> Secret #

Generic Secret 

Associated Types

type Rep Secret :: * -> * #

Methods

from :: Secret -> Rep Secret x #

to :: Rep Secret x -> Secret #

ToJSON Secret 
FromJSON Secret 
FromHttpApiData Secret 
ToHttpApiData Secret 
type Rep Secret 
type Rep Secret = D1 (MetaData "Secret" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "Secret" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ServiceId :: * #

A service identifier.

Constructors

ServiceId Text 

Instances

Eq ServiceId 
Ord ServiceId 
Read ServiceId 
Show ServiceId 
IsString ServiceId 
Generic ServiceId 

Associated Types

type Rep ServiceId :: * -> * #

ToJSON ServiceId 
FromJSON ServiceId 
FromHttpApiData ServiceId 
ToHttpApiData ServiceId 
type Rep ServiceId 
type Rep ServiceId = D1 (MetaData "ServiceId" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "ServiceId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ClientId :: * #

A client identifier.

Constructors

ClientId Text 

Instances

Eq ClientId 
Ord ClientId 
Read ClientId 
Show ClientId 
IsString ClientId 
Generic ClientId 

Associated Types

type Rep ClientId :: * -> * #

Methods

from :: ClientId -> Rep ClientId x #

to :: Rep ClientId x -> ClientId #

ToJSON ClientId 
FromJSON ClientId 
FromHttpApiData ClientId 
ToHttpApiData ClientId 
type Rep ClientId 
type Rep ClientId = D1 (MetaData "ClientId" "Network.Google.Types" "gogol-core-0.3.0-KIuP5pfcke6i6zK2Oqg2s" True) (C1 (MetaCons "ClientId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Re-exported Modules