Bring back example application

And capture _all_ plugin providers in it.
This commit is contained in:
patrick brisbin 2018-02-07 07:51:30 -08:00
parent ef38c5c49d
commit 7fe409baa8
5 changed files with 123 additions and 45 deletions

36
.env.example Normal file
View File

@ -0,0 +1,36 @@
#
# Copy this file to .env and update the credentials for the providers you are
# trying to test. These variables must all have non-empty values for the
# application to boot, but you only need to set real values for those Providers
# you plan to try.
#
###
BATTLE_NET_CLIENT_ID=x
BATTLE_NET_CLIENT_SECRET=x
BITBUCKET_CLIENT_ID=x
BITBUCKET_CLIENT_SECRET=x
EVE_ONLINE_CLIENT_ID=x
EVE_ONLINE_CLIENT_SECRET=x
GITHUB_CLIENT_ID=x
GITHUB_CLIENT_SECRET=x
GOOGLE_CLIENT_ID=x
GOOGLE_CLIENT_SECRET=x
NYLAS_CLIENT_ID=x
NYLAS_CLIENT_SECRET=x
SALES_FORCE_CLIENT_ID=x
SALES_FORCE_CLIENT_SECRET=x
SLACK_CLIENT_ID=x
SLACK_CLIENT_SECRET=x
SPOTIFY_CLIENT_ID=x
SPOTIFY_CLIENT_SECRET=x
UPCASE_CLIENT_ID=x
UPCASE_CLIENT_SECRET=x

10
.gitignore vendored
View File

@ -1,4 +1,12 @@
*.cabal
.env*
.stack-work
# OAuth keys configuration for the example
.env*
!.env.example
# Created when running the example
client_session_key.aes
# Used by stack test --rerun
TESTREPORT

View File

@ -8,7 +8,9 @@ setup:
.PHONY: build
build:
stack build $(STACK_ARGUMENTS) --pedantic --test --no-run-tests
stack build $(STACK_ARGUMENTS) \
--flag yesod-auth-oauth2:example \
--pedantic --test --no-run-tests
.PHONY: test
test:

View File

@ -1,53 +1,48 @@
-- |
--
-- This is a single-file example of using yesod-auth-oauth2.
--
-- It can be run with:
--
-- > stack build --flag yesod-auth-oauth2:example
-- > stack exec yesod-auth-oauth2-example
-- > $BROWSER http://localhost:3000
--
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
-- |
--
-- This single-file Yesod app uses all plugins defined within this site, as a
-- means of manual verification that they work. When adding a new plugin, add
-- usage of it here and verify locally that it works.
--
-- To do so, see @.env.example@, then:
--
-- > stack build --flag yesod-auth-oauth2:example
-- > stack exec yesod-auth-oauth2-example
-- >
-- > $BROWSER http://localhost:3000
--
module Main where
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import LoadEnv
import Network.HTTP.Conduit
import Network.Wai.Handler.Warp (runEnv)
import System.Environment (getEnv)
import Yesod
import Yesod.Auth
import Yesod.Auth.OAuth2.BattleNet
import Yesod.Auth.OAuth2.Bitbucket
import Yesod.Auth.OAuth2.EveOnline
import Yesod.Auth.OAuth2.Github
import qualified Data.Text as T
data OAuthKeys = OAuthKeys
{ oauthKeysClientId :: Text
, oauthKeysClientSecret :: Text
}
loadOAuthKeysEnv :: String -> IO OAuthKeys
loadOAuthKeysEnv prefix = OAuthKeys
<$> (getEnvT $ prefix <> "_CLIENT_ID")
<*> (getEnvT $ prefix <> "_CLIENT_SECRET")
where
getEnvT = fmap T.pack . getEnv
import Yesod.Auth.OAuth2.Google
import Yesod.Auth.OAuth2.Nylas
import Yesod.Auth.OAuth2.Salesforce
import Yesod.Auth.OAuth2.Slack
import Yesod.Auth.OAuth2.Spotify
import Yesod.Auth.OAuth2.Upcase
data App = App
{ appHttpManager :: Manager
, appGithubKeys :: OAuthKeys
-- , appGoogleKeys :: OAuthKeys
-- , etc...
, appAuthPlugins :: [AuthPlugin App]
}
mkYesod "App" [parseRoutes|
@ -56,7 +51,7 @@ mkYesod "App" [parseRoutes|
|]
instance Yesod App where
-- redirect_uri must be absolute to avoid callback mismatch error
-- see https://github.com/thoughtbot/yesod-auth-oauth2/issues/87
approot = ApprootStatic "http://localhost:3000"
instance YesodAuth App where
@ -77,16 +72,7 @@ instance YesodAuth App where
return $ Authenticated "1"
authHttpManager = appHttpManager
authPlugins m =
[ oauth2Github
(oauthKeysClientId $ appGithubKeys m)
(oauthKeysClientSecret $ appGithubKeys m)
-- , oauth2Google
-- (oauthKeysClientId $ appGoogleKeys m)
-- (oauthKeysClientSecret $ appGoogleKeys m)
-- , etc...
]
authPlugins = appAuthPlugins
instance RenderMessage App FormMessage where
renderMessage _ _ = defaultFormMessage
@ -109,11 +95,30 @@ mkFoundation = do
loadEnv
appHttpManager <- newManager tlsManagerSettings
appGithubKeys <- loadOAuthKeysEnv "GITHUB"
-- appGoogleKeys <- loadOAuthKeysEnv "GOOGLE"
-- etc...
appAuthPlugins <- sequence
-- When Providers are added, add them here and update .env.example.
-- Nothing else should need changing.
--
-- FIXME: oauth2BattleNet is quite annoying!
--
[ loadPlugin (oauth2BattleNet [whamlet|TODO|] "en") "BATTLE_NET"
, loadPlugin oauth2Bitbucket "BITBUCKET"
, loadPlugin (oauth2Eve Plain) "EVE_ONLINE"
, loadPlugin oauth2Github "GITHUB"
, loadPlugin oauth2Google "GOOGLE"
, loadPlugin oauth2Nylas "NYLAS"
, loadPlugin oauth2Salesforce "SALES_FORCE"
, loadPlugin oauth2Slack "SLACK"
, loadPlugin (oauth2Spotify []) "SPOTIFY"
, loadPlugin oauth2Upcase "UPCASE"
]
return App{..}
where
loadPlugin f prefix = do
clientId <- getEnv $ prefix <> "_CLIENT_ID"
clientSecret <- getEnv $ prefix <> "_CLIENT_SECRET"
pure $ f (T.pack clientId) (T.pack clientSecret)
main :: IO ()
main = runEnv 3000 =<< toWaiApp =<< mkFoundation

View File

@ -34,6 +34,27 @@ library:
- yesod-auth >=1.3 && <1.5
- yesod-core >=1.2 && <1.5
executables:
yesod-auth-oauth2-example:
main: Main.hs
source-dirs: example
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
dependencies:
- yesod-auth-oauth2
- containers
- http-conduit
- load-env
- text
- warp
- yesod
- yesod-auth
when:
- condition: ! '!(flag(example))'
buildable: false
tests:
test:
main: Spec.hs
@ -42,3 +63,9 @@ tests:
- yesod-auth-oauth2
- hspec
- uri-bytestring
flags:
example:
description: Build the example application
manual: false
default: false