yesod/openid2.hs
Michael Snoyman 17b5406fce OpenID v2 support.
All of the heavy lifting was taken directly from the openid package, and
lives in the OpenId2.* module hierarchy. The difference here is that we
don't use associations at all, removing the need for some hefty
dependencies. I've also gutted MonadLib dependencies.
2010-10-05 08:37:04 +02:00

37 lines
912 B
Haskell

{-# LANGUAGE TypeFamilies, QuasiQuotes #-}
import Yesod
import Web.Authenticate.OpenId2
import Data.Object
import Data.Maybe (fromMaybe)
import Network.HTTP.Enumerator
data OID = OID
mkYesod "OID" [$parseRoutes|
/ RootR GET
/forward ForwardR GET
/complete CompleteR GET
|]
instance Yesod OID where approot _ = "http://localhost:3000"
getRootR = defaultLayout [$hamlet|
%form!action=@ForwardR@
OpenId:
%input!type=text!name=openid_identifier!value="http://"
%input!type=submit
|]
getForwardR = do
openid <- runFormGet' $ stringInput "openid_identifier"
render <- getUrlRender
url <- liftIO $ getForwardUrl openid $ render CompleteR
redirectString RedirectTemporary url
return ()
getCompleteR = do
params <- reqGetParams `fmap` getRequest
ident <- liftIO $ authenticate params
return $ RepPlain $ toContent ident
main = withHttpEnumerator $ basicHandler 3000 OID