mirror of
https://github.com/freckle/yesod-auth-oauth2.git
synced 2026-01-11 19:58:28 +01:00
Add potential, currently non-functioning tests
Approach so far: The SpecHelper sets up an example App type which should (theoretically) be enough to get some fake requests and responses going, as in any yesod-test-based suite. The spec then tries to build an example plugin and make assertions on how it dispatches. This is currently falling down on subsite-related type errors (see commented attempts). Another potential direction is to define the YesodAuth instance for App to specify authPlugins built using the library. With that, we might be able to create specs using yesod-test that exercise aspects of the plugins in an indirect way, but enough to make useful assertions.
This commit is contained in:
parent
c2794f4040
commit
9b028535bd
43
test/SpecHelper.hs
Normal file
43
test/SpecHelper.hs
Normal file
@ -0,0 +1,43 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
module SpecHelper
|
||||
( App(..)
|
||||
, Widget
|
||||
, resourcesApp
|
||||
, module Test.Hspec
|
||||
, module Yesod
|
||||
, module Yesod.Auth
|
||||
, module Yesod.Auth.OAuth2
|
||||
) where
|
||||
|
||||
import Test.Hspec
|
||||
|
||||
import Data.Text (Text)
|
||||
|
||||
import Yesod
|
||||
import Yesod.Auth
|
||||
import Yesod.Auth.OAuth2
|
||||
|
||||
data App = App
|
||||
|
||||
mkYesod "App" [parseRoutes| / R GET |]
|
||||
|
||||
instance Yesod App
|
||||
instance YesodAuth App where
|
||||
type AuthId App = Text
|
||||
|
||||
authHttpManager = undefined
|
||||
authPlugins = undefined
|
||||
authenticate = undefined
|
||||
loginDest = undefined
|
||||
logoutDest = undefined
|
||||
maybeAuthId = undefined
|
||||
|
||||
instance RenderMessage App FormMessage where
|
||||
renderMessage _ _ = defaultFormMessage
|
||||
|
||||
getR :: Handler ()
|
||||
getR = return ()
|
||||
@ -3,13 +3,38 @@ module Yesod.Auth.OAuth2Spec
|
||||
, spec
|
||||
) where
|
||||
|
||||
import Test.Hspec
|
||||
import Yesod.Auth.OAuth2
|
||||
import SpecHelper
|
||||
|
||||
main :: IO ()
|
||||
main = hspec spec
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "authOAuth2" $
|
||||
it "works" $
|
||||
it "works" $ do
|
||||
-- If I could somehow get this dispatch to execute, I could assert on the
|
||||
-- response; at least enough to verify the state parameter that prompted
|
||||
-- this track of work...
|
||||
--
|
||||
-- Currently, the blocker is that apDispatch is:
|
||||
--
|
||||
-- > HandlerT Auth (HandlerT App IO) TypedContent
|
||||
--
|
||||
-- but I really need a:
|
||||
--
|
||||
-- > HandlerT App IO TypedContent
|
||||
--
|
||||
-- to be able to use runFakeHandler, as is sort of shown below:
|
||||
--
|
||||
-- > let app = App
|
||||
-- > plugin = authOAuth2 "example" undefined undefined
|
||||
-- >
|
||||
-- > x <- runFakeHandler
|
||||
-- > M.empty undefined (getAuth app) $
|
||||
-- > apDispatch plugin "GET" ["callback"]
|
||||
-- >
|
||||
-- > liftIO $ print (x :: TypedContent)
|
||||
--
|
||||
-- I basically need to peel one layer off the transformer stack, but I can't
|
||||
-- find the right run-handler anywhere.
|
||||
|
||||
True `shouldBe` True
|
||||
|
||||
@ -58,6 +58,9 @@ test-suite test
|
||||
build-depends: base
|
||||
, yesod-auth-oauth2
|
||||
, hspec
|
||||
, text
|
||||
, yesod
|
||||
, yesod-auth
|
||||
|
||||
source-repository head
|
||||
type: git
|
||||
|
||||
Loading…
Reference in New Issue
Block a user