Moved authDummy to a separate module

This commit is contained in:
Michael Snoyman 2010-10-20 22:50:48 +02:00
parent 20b0790c25
commit 46d8398d7a
3 changed files with 34 additions and 20 deletions

View File

@ -4,18 +4,20 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
module Yesod.Helpers.Auth
( Auth
( -- * Subsite
Auth
, AuthPlugin (..)
, AuthRoute (..)
, getAuth
, Creds (..)
, YesodAuth (..)
-- * Plugin interface
, Creds (..)
, setCreds
-- * User functions
, maybeAuthId
, maybeAuth
, requireAuthId
, requireAuth
, authDummy
) where
import Yesod
@ -81,6 +83,7 @@ mkYesodSub "Auth"
credsKey :: String
credsKey = "_ID"
-- | FIXME: won't show up till redirect
setCreds :: YesodAuth m => Bool -> Creds m -> GHandler s m ()
setCreds doRedirects creds = do
y <- getYesod
@ -189,20 +192,3 @@ redirectLogin = do
case authRoute y of
Just z -> redirect RedirectTemporary z
Nothing -> permissionDenied "Please configure authRoute"
authDummy :: YesodAuth m => AuthPlugin m
authDummy =
AuthPlugin "dummy" dispatch login
where
dispatch "POST" [] = do
ident <- runFormPost' $ stringInput "ident"
setCreds True $ Creds "dummy" ident []
dispatch _ _ = notFound
url = PluginR "dummy" []
login authToMaster = do
addBody [$hamlet|
%form!method=post!action=@authToMaster.url@
Your new identifier is: $
%input!type=text!name=ident
%input!type=submit!value="Dummy Login"
|]

View File

@ -0,0 +1,27 @@
{-# LANGUAGE QuasiQuotes #-}
-- | Provides a dummy authentication module that simply lets a user specify
-- his/her identifier. This is not intended for real world use, just for
-- testing.
module Yesod.Helpers.Auth.Dummy
( authDummy
) where
import Yesod
import Yesod.Helpers.Auth
authDummy :: YesodAuth m => AuthPlugin m
authDummy =
AuthPlugin "dummy" dispatch login
where
dispatch "POST" [] = do
ident <- runFormPost' $ stringInput "ident"
setCreds True $ Creds "dummy" ident []
dispatch _ _ = notFound
url = PluginR "dummy" []
login authToMaster = do
addBody [$hamlet|
%form!method=post!action=@authToMaster.url@
Your new identifier is: $
%input!type=text!name=ident
%input!type=submit!value="Dummy Login"
|]

View File

@ -26,6 +26,7 @@ library
, blaze-builder >= 0.1 && < 0.2
, mime-mail >= 0.0 && < 0.1
exposed-modules: Yesod.Helpers.Auth
Yesod.Helpers.Auth.Dummy
Yesod.Helpers.Auth.Email
Yesod.Helpers.Auth.Facebook
Yesod.Helpers.Auth.OpenId