| Copyright | (c) 2015-2016 Brendan Hay |
|---|---|
| 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 |
Network.Google.Auth
Contents
Description
Explicitly specify your Google credentials, or retrieve them from the underlying OS.
- data Credentials s
- = FromMetadata !ServiceId
- | FromClient !OAuthClient !(OAuthCode s)
- | FromAccount !ServiceAccount
- | FromUser !AuthorizedUser
- getApplicationDefault :: (MonadIO m, MonadCatch m) => Manager -> m (Credentials s)
- fromWellKnownPath :: (MonadIO m, MonadCatch m) => m (Credentials s)
- fromFilePath :: (MonadIO m, MonadCatch m) => FilePath -> m (Credentials s)
- installedApplication :: OAuthClient -> OAuthCode s -> Credentials s
- formURL :: AllowScopes s => OAuthClient -> proxy s -> Text
- authorize :: (MonadIO m, MonadCatch m, AllowScopes s) => Request -> Store s -> Logger -> Manager -> m Request
- data Store s
- initStore :: (MonadIO m, MonadCatch m, AllowScopes s) => Credentials s -> Logger -> Manager -> m (Store s)
- data Auth s = Auth {
- _credentials :: !(Credentials s)
- _token :: !(OAuthToken s)
- exchange :: forall m s. (MonadIO m, MonadCatch m, AllowScopes s) => Credentials s -> Logger -> Manager -> m (Auth s)
- refresh :: forall m s. (MonadIO m, MonadCatch m, AllowScopes s) => Auth s -> Logger -> Manager -> m (Auth s)
- checkGCEVar :: String
- cloudSDKConfigDir :: String
- defaultCredentialsFile :: String
- class AsAuthError a where
- _AuthError :: Prism' a AuthError
- _RetrievalError :: Prism' a HttpException
- _MissingFileError :: Prism' a FilePath
- _InvalidFileError :: Prism' a (FilePath, Text)
- _TokenRefreshError :: Prism' a (Status, Text, Maybe Text)
- data AuthError
- = RetrievalError HttpException
- | MissingFileError FilePath
- | InvalidFileError FilePath Text
- | TokenRefreshError Status Text (Maybe Text)
- data OAuthClient = OAuthClient {
- _clientId :: !ClientId
- _clientSecret :: !Secret
- data OAuthToken s = OAuthToken {
- _tokenAccess :: !AccessToken
- _tokenRefresh :: !(Maybe RefreshToken)
- _tokenExpiry :: !UTCTime
- newtype OAuthCode s = OAuthCode Text
- newtype OAuthScope :: * = OAuthScope Text
- newtype AccessToken :: * = AccessToken Text
- newtype RefreshToken :: * = RefreshToken Text
- newtype Secret :: * = Secret Text
- newtype ServiceId :: * = ServiceId Text
- newtype ClientId :: * = ClientId Text
- module Network.Google.Auth.Scope
Credentials
data Credentials s Source
The supported credential mechanisms.
Constructors
| FromMetadata !ServiceId | Obtain and refresh access tokens from the underlying GCE host metadata
at |
| 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 A |
| FromUser !AuthorizedUser | Use the specified An |
Instances
| AllowScopes [Symbol] s => AllowScopes * (Credentials s) Source |
Application Default Credentials
getApplicationDefault :: (MonadIO m, MonadCatch m) => Manager -> m (Credentials s) Source
Performs credentials discovery in the following order:
- Read the default credentials from a file specified by
the environment variable
GOOGLE_APPLICATION_CREDENTIALSif it exists. - Read the platform equivalent of
~/.config/gcloud/application_default_credentials.jsonif it exists. The~/.configcomponent of the path can be overriden by the environment variableCLOUDSDK_CONFIGif it exists. - Retrieve the default service account application credentials if
running on GCE. The environment variable
NO_GCE_CHECKcan be used to skip this check if set to a truthy value such as1ortrue.
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.
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.
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.
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 System.Exit (exitFailure) import System.Info (os) import System.Process (rawSystem)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy.Char8 as LBS8
redirectPrompt :: forall s. OAuthClient -> proxy s -> IO (OAuthCode s)
redirectPrompt c p = do
let url = LBS8.unpack (formURL c (Proxy :: Proxy s))
putStrLn $ "Opening URL " ++ url
case os of
"darwin" -> rawSystem "open" [url]
"linux" -> rawSystem "xdg-open" [url]
_ -> putStrLn "Unsupported OS" >> exitFailure
putStrLn "Please input the authorisation code: "
OAuthCode . LBS.fromStrict <$> BS.getLineThis ensures the scopes passed to formURL and the type of OAuthCode s
are correct.
formURL :: AllowScopes s => 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
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.
An OAuthToken that can potentially be expired, with the original
credentials that can be used to perform a refresh.
Constructors
| Auth | |
Fields
| |
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 using
Default Constants
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
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.
Instances
An error thrown when attempting to read AuthN/AuthZ information.
Constructors
| RetrievalError HttpException | |
| MissingFileError FilePath | |
| InvalidFileError FilePath Text | |
| TokenRefreshError Status Text (Maybe Text) |
OAuth Types
data OAuthClient Source
A client identifier and accompanying secret used to obtain/refresh a token.
Constructors
| OAuthClient | |
Fields
| |
Instances
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.
Constructors
| OAuthToken | |
Fields
| |
Instances
| Eq (OAuthToken s) Source | |
| Show (OAuthToken s) Source | |
| FromJSON (UTCTime -> OAuthToken s) Source |
An OAuth client authorization code.
newtype OAuthScope :: *
Constructors
| OAuthScope Text |
Instances
| Eq OAuthScope | |
| Ord OAuthScope | |
| Read OAuthScope | |
| Show OAuthScope | |
| IsString OAuthScope | |
| Generic OAuthScope | |
| ToJSON OAuthScope | |
| FromJSON OAuthScope | |
| ToHttpApiData OAuthScope | |
| FromHttpApiData OAuthScope | |
| type Rep OAuthScope = D1 D1OAuthScope (C1 C1_0OAuthScope (S1 NoSelector (Rec0 Text))) |
Re-exported Types
newtype AccessToken :: *
Constructors
| AccessToken Text |
Instances
| Eq AccessToken | |
| Ord AccessToken | |
| Read AccessToken | |
| Show AccessToken | |
| IsString AccessToken | |
| Generic AccessToken | |
| ToJSON AccessToken | |
| FromJSON AccessToken | |
| ToHttpApiData AccessToken | |
| FromHttpApiData AccessToken | |
| type Rep AccessToken = D1 D1AccessToken (C1 C1_0AccessToken (S1 NoSelector (Rec0 Text))) |
newtype RefreshToken :: *
Constructors
| RefreshToken Text |
Instances
| Eq RefreshToken | |
| Ord RefreshToken | |
| Read RefreshToken | |
| Show RefreshToken | |
| IsString RefreshToken | |
| Generic RefreshToken | |
| ToJSON RefreshToken | |
| FromJSON RefreshToken | |
| ToHttpApiData RefreshToken | |
| FromHttpApiData RefreshToken | |
| type Rep RefreshToken = D1 D1RefreshToken (C1 C1_0RefreshToken (S1 NoSelector (Rec0 Text))) |
newtype Secret :: *
newtype ServiceId :: *
newtype ClientId :: *
Re-exported Modules
module Network.Google.Auth.Scope