yesod/yesod-auth/browserid.hs
Michael Snoyman cd5ee0fb12 Add 'yesod-auth/' from commit 'fe498e3dac01bfc999cad33b90a2b1b397785178'
git-subtree-dir: yesod-auth
git-subtree-mainline: a7df7531dc
git-subtree-split: fe498e3dac
2011-07-22 08:59:54 +03:00

49 lines
1.1 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import Yesod.Core
import Yesod.Auth
import Yesod.Auth.BrowserId
import Data.Text (Text)
import Text.Hamlet (hamlet)
import Control.Monad.IO.Class (liftIO)
import Yesod.Form
import Network.Wai.Handler.Warp (run)
data BID = BID
type Handler = GHandler BID BID
mkYesod "BID" [parseRoutes|
/ RootR GET
/after AfterLoginR GET
/auth AuthR Auth getAuth
|]
getRootR :: Handler ()
getRootR = redirect RedirectTemporary $ AuthR LoginR
getAfterLoginR :: Handler RepHtml
getAfterLoginR = do
mauth <- maybeAuthId
defaultLayout $ addHamlet [hamlet|
<p>Auth: #{show mauth}
|]
instance Yesod BID where
approot _ = "http://localhost:3000"
instance YesodAuth BID where
type AuthId BID = Text
loginDest _ = AfterLoginR
logoutDest _ = AuthR LoginR
getAuthId = return . Just . credsIdent
authPlugins = [authBrowserId "localhost:3000"]
instance RenderMessage BID FormMessage where
renderMessage _ _ = defaultFormMessage
main :: IO ()
main = toWaiApp BID >>= run 3000