| 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.InstalledApplication
Description
Credentials for applications that are installed on devices such as computers, cell phones, or a tablet. Installed apps are distributed to individual machines, and it is assumed that these apps securely store secrets.
These apps might access a Google service while the user is present at the application, or when the application is running in the background.
- installedApplication :: OAuthClient -> OAuthCode s -> Credentials s
- redirectURI :: Text
- formURL :: AllowScopes s => OAuthClient -> proxy s -> Text
- formURLWith :: OAuthClient -> [OAuthScope] -> Text
- exchangeCode :: (MonadIO m, MonadCatch m) => OAuthClient -> OAuthCode s -> Logger -> Manager -> m (OAuthToken s)
- refreshToken :: (MonadIO m, MonadCatch m) => OAuthClient -> OAuthToken s -> Logger -> Manager -> m (OAuthToken s)
Documentation
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.
Forming the URL
The redirection URI used in formURL: urn:ietf:wg:oauth:2.0:oob.
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.
formURLWith :: OAuthClient -> [OAuthScope] -> Text Source
Form a URL using OAuthScope values.
See: formURL.
Internal Exchange and Refresh
exchangeCode :: (MonadIO m, MonadCatch m) => OAuthClient -> OAuthCode s -> Logger -> Manager -> m (OAuthToken s) Source
Exchange OAuthClient details and the received OAuthCode for a new
OAuthToken.
See: Exchanging the code.
refreshToken :: (MonadIO m, MonadCatch m) => OAuthClient -> OAuthToken s -> Logger -> Manager -> m (OAuthToken s) Source
Perform a refresh to obtain a valid OAuthToken with a new expiry time.
See: Refreshing tokens.