{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} -- | 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.Auth.Dummy ( authDummy ) where import Yesod.Auth import Yesod.Form (runInputPost, textField, ireq) import Yesod.Core authDummy :: YesodAuth m => AuthPlugin m authDummy = AuthPlugin "dummy" dispatch login where dispatch "POST" [] = do ident <- runInputPost $ ireq textField "ident" setCredsRedirect $ Creds "dummy" ident [] dispatch _ _ = notFound url = PluginR "dummy" [] login authToMaster = do request <- getRequest toWidget [hamlet| $newline never
$maybe t <- reqToken request Your new identifier is: # |]