{-# LANGUAGE OverloadedStrings #-} {-| Module : Haste.GAPI Description : Entry Module for haste-gapi Copyright : (c) Jonathan Skårstedt, 2016 License : MIT Maintainer : jonathan.skarstedt@gmail.com Stability : experimental Portability : Haste Example of a login to the Google API. Note that @config@ is defined elsewhere. @ main :: IO () main = withGAPI config $ \token -> case token of OA2Success {} -> putStrLn $ show token OA2Error {errorMsg = e} -> putStrLn $ "Your success token is invalid (" ++ e ++ ")" @ The login starts with the @withGAPI@, which will load the Google API environment. If the script is compiled with @--onexec@ flag, the load will be significally faster as we don't have to wait until the script has fully loaded until we download the Google API hooks. When loading is done, a @OAuth2Token@ is generated, and we may inspect it to see wether the login is successful or not. On success, we continue with showing the token. If not, we print an error instead. Note that the @withGAPI@ function ought to only be invoked once. Example of a request: @ greet :: IO () greet = runR $ do response <- request "plus\/v1\/people\/me" def Just [name, pic] \<- sequence <$\> mapM (lookupVal response) [ "result.displayName", "result.image.url"] liftIO . putStrLn $ "Hello " ++ name ++ "! \
" ++ "You look like this: \
\" @ The reqeuest above will greet the user by name, fetched from the Google+ API. A response is generated by taking a Path and some Params to the @request@ function, which will execute it and return a response. After that we look up some fields in the result, namely /result.displayName/ and /result.image.url/. The first will be bound to name, and the second to pic. These two elements are both strings, by Haste.Foreign magic. After that we use @RequestM@s @liftIO@ (as it's an instance of the MonadIO class) and present a pretty HTML string! -} module Haste.GAPI ( -- | = Connecting to the Google API withGAPI, oa2success, getToken, Config(..), OAuth2Token(..), -- | = Creating Requests module Haste.GAPI.Request, -- | = Handling Results module Haste.GAPI.Result, -- | = Common types when working with Google API libraries module Haste.GAPI.Types ) where import Haste.Foreign hiding (get, has, hasAll) import qualified Haste.Foreign as FFI -- GHC 7.8 compatibility import Data.Functor ((<$>)) import Haste.GAPI.Request import Haste.GAPI.Result import Haste.GAPI.Types import Data.Default -- import Control.Monad import Control.Applicative -- Datatypes ----------------------------------------------------------------- -- | Google API configuration. For an in-detail description of what each field -- does, please see the , -- especially the methods @gapi.auth.authorize@ and @gapi.client.setApiKey@. data Config = Config { -- | Client ID to generate an authentification token from. clientID :: String, -- | The API key for your application apiKey :: String, -- | Here you enter the availiable scopes for your application. scopes :: String, -- | If true, the token an attempt will be made to refresh it behind the -- cenes immediate :: Bool } instance Show Config where show (Config cid key scopes' imm) = "\nConfig: " ++ concatMap (++ "\n\t") [cid, key, scopes', show imm] instance ToAny Config where toAny cfg = toObject [("clientID", toAny $ clientID cfg), ("apiKey", toAny $ apiKey cfg), ("scopes", toAny $ scopes cfg), ("immediate", toAny $ immediate cfg)] -- | OAuth2Token, the authentication tokens used by the Google API. data OAuth2Token = OA2Success { -- | Authenticated access token accessToken :: String, -- | Expiration of the token expiresIn :: String, -- | Google API Scopes related to this token. state :: String } | OA2Error { errorMsg :: String, state :: String } instance Show OAuth2Token where show t = if oa2success t then "Success Token: '" ++ shorten (accessToken t) ++ "'\n\t for scopes: '" ++ state t ++ "'\n\t expires in: "++ expiresIn t ++ "s" else "Failure Token: " ++ errorMsg t where shorten :: String -> String shorten str | length str < 16 = str | otherwise = take 32 str ++ "..." instance FromAny OAuth2Token where fromAny oa2 = do success <- FFI.has oa2 "access_token" if success then OA2Success <$> FFI.get oa2 "access_token" <*> FFI.get oa2 "expires_in" <*> FFI.get oa2 "state" else OA2Error <$> FFI.get oa2 "error" <*> FFI.get oa2 "state" -- Exported functions -------------------------------------------------------- -- | Returns true if the token represents a successful authentication oa2success :: OAuth2Token -> Bool oa2success OA2Success {} = True oa2success _ = False -- | Loads the Google API, inserts Google API headers and then executes -- an action. withGAPI :: Config -> (OAuth2Token -> IO ()) -> IO () withGAPI cfg handler = do loadGAPI cfg handler loadGAPIExternals "GAPILoader" -- | Exports and coordinate loading of the Google API. loadGAPI :: Config -> (OAuth2Token -> IO ()) -> IO () loadGAPI = loadGAPI' "GAPILoader" -- | Loads the Google API with a custom loader name loadGAPI' :: String -> Config -> (OAuth2Token -> IO ()) -> IO () loadGAPI' symbol cfg handler = exportLoaderSymbol symbol $ loadClient cfg $ auth cfg handler -- | Returns the token from the current Google API state getToken :: IO OAuth2Token getToken = ffi "(function() {return gapi.auth.getToken();})" -- | Loads the GAPI Client loadClient :: Config -> IO () -> IO () loadClient = ffi "(function(cfg, auth){\ \gapi.client.setApiKey(cfg.apiKey); \ \window.setTimeout(auth, 1);})" -- | Authenticates the user. Should be invoked by loadClient auth :: Config -> (OAuth2Token -> IO ()) -> IO () auth = ffi "(function(cfg, ah)\ \{gapi.auth.authorize({\ \'client_id': cfg.clientID, \ \'scope': cfg.scopes, \ \'immediate': cfg.immediate}, \ \ah);})" -- | Export the loader symbol exportLoaderSymbol :: String -> IO () -> IO () exportLoaderSymbol = ffi "(function(s, f) {window[s] = f;})" -- | Loads the external GAPI scripts loadGAPIExternals :: String -> IO () loadGAPIExternals = ffi "(function(sym) {\ \var s = document.createElement('script');\ \s.setAttribute('src', 'https://apis.google.com/js/client.js?onload=' + sym);\ \s.setAttribute('type', 'text/javascript');\ \document.head.appendChild(s);})"