{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes, TypeFamilies, UndecidableInstances #-} {-# OPTIONS_GHC -F -pgmFtrhsx #-} module Happstack.Auth.HSP.Login where import Control.Applicative (Alternative, (<*>), (<$>), (<*), (*>), optional) import Control.Monad (replicateM, mplus) import Control.Monad.Trans (MonadIO(liftIO)) import Data.Acid (AcidState, query', update') import Data.Maybe (mapMaybe) import Data.Set (Set) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as Text import Data.Time.Clock (getCurrentTime) import Happstack.Auth.Core.Auth import Happstack.Auth.Core.AuthParts import Happstack.Auth.Core.AuthURL import Happstack.Auth.Core.ProfileURL import Happstack.Auth.Core.Profile import Happstack.Auth.Core.ProfileParts import Happstack.Server -- (CookieLife(Session), Response, ServerMonad(..), FilterMonad(..), Input(..), Happstack, ServerPartT, addCookie, escape, internalServerError, lookCookieValue, lookPairs, mkCookie, seeOther, toResponse, unauthorized) import Happstack.Server.HSP.HTML (XML) import HSP (Attr(..), EmbedAsAttr(..), EmbedAsChild(..), XMLGenT(..), XMLGenerator, genElement, genEElement, unXMLGenT) import HSP.ServerPartT() import qualified HSX.XMLGenerator as HSX import Happstack.Auth.HSP.FormPart import Text.Digestive import Text.Digestive.Forms.Happstack () import Text.Digestive.HSP.Html4 import Web.Authenticate.OpenId (Identifier, authenticate, getForwardUrl) import Web.Authenticate.OpenId.Providers (google, yahoo, livejournal, myspace) import Web.Authenticate.Facebook (Facebook) import Web.Routes (RouteT, ShowURL, showURL, showURLParams, nestURL, URL) import Web.Routes.XMLGenT -- * AuthURL stuff logoutPage :: (XMLGenerator m, Alternative m, Happstack m, EmbedAsAttr m (Attr String AuthURL)) => AcidState AuthState -> XMLGenT m (HSX.XML m) logoutPage authStateH = do deleteAuthCookie authStateH

You are now logged out. Click here to log in again.

loginPage :: (XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => Maybe Facebook -> XMLGenT m (HSX.XML m) loginPage mFacebook =
  1. Login with your Google Account
  2. Login with your Yahoo Account
  3. Login with your Live Journal Account
  4. Login with your Myspace Account
  5. Login with your OpenId Account
  6. Login with a username and password
  7. <% case mFacebook of Nothing -> [] (Just facebook) -> [
  8. Login with your Facebook Account
  9. ] %>
addAuthPage :: (XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => Maybe Facebook -> XMLGenT m (HSX.XML m) addAuthPage mFacebook =
  1. Add your Google
  2. Add your Yahoo Account
  3. Add your Live Journal Account
  4. Add your Myspace Account
  5. Add your OpenId Account
  6. <% case mFacebook of Nothing -> [] (Just facebook) -> [
  7. Add your Facebook Account
  8. ] %>
authPicker :: (XMLGenerator m, EmbedAsAttr m (Attr String ProfileURL)) => Set AuthId -> XMLGenT m (HSX.XML m) authPicker authIds =
where auth authId =
  • <% show authId %>
  • -- FIXME: give a more informative view. personalityPicker :: (XMLGenerator m, EmbedAsChild m Text, EmbedAsAttr m (Attr String ProfileURL)) => Set Profile -> XMLGenT m (HSX.XML m) personalityPicker profiles =
    where personality profile =
  • <% nickName profile %>
  • type PageTemplate x = String -> () -> (XMLGenT x (HSX.XML x)) -> XMLGenT x Response type PageTemplate' x = String -> () -> (XMLGenT x (HSX.XML x)) -> x Response {- providerPage :: (Happstack m, XMLGenerator m) => (forall body. (EmbedAsChild (RouteT AuthURL m) body) => (String -> () -> body -> XMLGenT (RouteT AuthURL m) Response)) -> OpenIdProvider -> AuthURL -> AuthMode -> RouteT AuthURL m Response -} providerPage appTemplate provider = case provider of Google -> googlePage Yahoo -> yahooPage LiveJournal -> liveJournalPage appTemplate -- FIXME googlePage :: (Happstack m, ShowURL m, URL m ~ AuthURL) => AuthURL -> AuthMode -> m Response googlePage _here authMode = do u <- showURLParams (A_OpenId (O_Connect authMode)) [("url", google)] seeOther u (toResponse ()) yahooPage :: (Happstack m, ShowURL m, URL m ~ AuthURL) => AuthURL -> AuthMode -> m Response yahooPage _here authMode = do u <- showURLParams (A_OpenId (O_Connect authMode)) [("url", yahoo)] seeOther u (toResponse ()) {- liveJournalPage :: (Happstack m, XMLGenerator m, ToMessage (HSX.XML m), EmbedAsChild m (), Alternative m, ShowURL m, URL m ~ (OpenIdURL p)) => PageTemplate m -> OpenIdURL p -> AuthMode -> m Response -} liveJournalPage appTemplate here authMode = do actionURL <- showURL here appTemplate "Login" () $

    Login using your Live Journal account

    Enter your livejournal account name to connect. You may be prompted to log into your livejournal account and to confirm the login.

    <% formPart "p" actionURL handleSuccess (handleFailure appTemplate) liveJournalForm %>
    where -- handleSuccess :: String -> XMLGenT (RouteT (OpenIdURL p) (ServerPartT IO)) Response handleSuccess username = do u <- showURLParams (A_OpenId (O_Connect authMode)) [("url", livejournal username)] seeOther u (toResponse ()) {- handleFailure :: (XMLGenerator m, Happstack m, EmbedAsChild m (), ToMessage (HSX.XML m)) => PageTemplate m -> [(FormRange, String)] -> [XMLGenT m (HSX.XML m)] -> XMLGenT m Response -} handleFailure appTemplate errs formXML = XMLGenT $ appTemplate "Login" ()

    Errors

    -- <% errorList (map snd errs) %> <% formXML %>
    liveJournalForm :: (Functor v, Monad v, XMLGenerator m) => Form v [Input] String [XMLGenT m (HSX.XML m)] String liveJournalForm = label "http://" ++> inputString Nothing <++ label ".livejournal.com/" <* submit "Connect" handleAuth :: (Happstack m, Alternative m) => AcidState AuthState -> (String -> () -> XMLGenT (RouteT AuthURL m) XML -> RouteT AuthURL m Response) -> Maybe Facebook -> Maybe String -> String -> AuthURL -> RouteT AuthURL m Response handleAuth authStateH appTemplate mFacebook realm onAuthURL url = case url of A_Login -> appTemplate "Login" () (loginPage mFacebook) A_AddAuth -> appTemplate "Add Auth" () (addAuthPage mFacebook) A_Logout -> appTemplate "Logout" () (logoutPage authStateH) A_Local -> localLoginPage authStateH appTemplate url onAuthURL A_CreateAccount -> createAccountPage authStateH appTemplate onAuthURL url A_ChangePassword -> changePasswordPage authStateH appTemplate url (A_OpenId oidURL) -> nestURL A_OpenId $ handleOpenId authStateH realm onAuthURL oidURL (A_OpenIdProvider authMode provider) -> providerPage appTemplate provider url authMode (A_Facebook authMode) -> case mFacebook of Nothing -> internalServerError $ toResponse "Facebook authentication not configured." (Just facebook) -> facebookPage facebook authMode (A_FacebookRedirect authMode) -> case mFacebook of Nothing -> internalServerError $ toResponse "Facebook authentication not configured." (Just facebook) -> facebookRedirectPage authStateH facebook onAuthURL authMode handleProfile :: (Happstack m, Alternative m) => AcidState AuthState -> AcidState ProfileState -> (String -> () -> XMLGenT (RouteT ProfileURL m) XML -> RouteT ProfileURL m Response) -> String -> ProfileURL -> RouteT ProfileURL m Response handleProfile authStateH profileStateH appTemplate postPickedURL url = case url of P_PickProfile -> do r <- pickProfile authStateH profileStateH case r of (Picked {}) -> seeOther postPickedURL (toResponse postPickedURL) (PickPersonality profiles) -> appTemplate "Pick Personality" () (personalityPicker profiles) (PickAuthId authIds) -> appTemplate "Pick Auth" () (authPicker authIds) (P_SetAuthId authId) -> do b <- setAuthIdPage authStateH authId if b then seeOther "/" (toResponse "") -- FIXME: don't hardcode destination else unauthorized =<< appTemplate "unauthorized" ()

    Attempted to set AuthId to <% show $ unAuthId authId %>, but failed because the Identifier is not associated with that AuthId.

    {- localLoginPage :: (Happstack m, Alternative m) => (forall header body. ( EmbedAsChild (RouteT AuthURL m) XML , EmbedAsChild (RouteT AuthURL m) header , EmbedAsChild (RouteT AuthURL m) body) => (String -> header -> body -> RouteT AuthURL m Response)) -> AuthURL -> String -> RouteT AuthURL m Response -} localLoginPage authStateH appTemplate here onAuthURL = do actionURL <- showURL here appTemplate "Login" () $

    Login with a username and password

    <% formPart "p" actionURL (XMLGenT . handleLogin) (handleFailure appTemplate) loginForm %>
    where handleLogin :: (Happstack m) => UserPassId -> RouteT AuthURL m Response handleLogin userPassId = do authId <- do authIds <- query' authStateH (UserPassIdAuthIds userPassId) case Set.size authIds of 1 -> return (Just $ head $ Set.toList $ authIds) n -> return Nothing addAuthCookie authStateH authId (AuthUserPassId userPassId) seeOther onAuthURL (toResponse ()) loginForm :: (Functor v, MonadIO v, XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => Form v [Input] String [XMLGenT m (HSX.XML m)] UserPassId loginForm = (errors ++> (fieldset $ ol (((,) <$> (li $ label "username: " ++> inputText Nothing) <*> (li $ label "password: " ++> inputPassword) <* login) `transform` checkAuth))) <* create create :: (Functor v, Monad v, XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => Form v [Input] String [XMLGenT m (HSX.XML m)] () create = view [

    or create a new account

    ] login :: (Functor v, Monad v, XMLGenerator m) => Form v [Input] String [XMLGenT m (HSX.XML m)] String login = li $ (submit "Login") `setAttrs` [("class" := "submit")] checkAuth :: (MonadIO m) => Transformer m String (Text, String) UserPassId checkAuth = transformEitherM $ \(username, password) -> do r <- query' authStateH (CheckUserPass username (Text.pack password)) case r of (Left e) -> return (Left $ userPassErrorString e) (Right userPassId) -> return (Right userPassId) -- createAccountPage :: StoryPromptsURL -> StoryPrompts Response createAccountPage authStateH appTemplate onAuthURL here = do actionURL <- showURL here ok =<< appTemplate "Create User Account" ()

    Create an account

    <% formPart "p" actionURL handleSuccess (handleFailure appTemplate) (newAccountForm authStateH) %>
    where handleSuccess (authId, userPassId) = do addAuthCookie authStateH (Just authId) (AuthUserPassId userPassId) seeOther onAuthURL (toResponse ()) newAccountForm :: (Functor v, MonadIO v, XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => AcidState AuthState -> Form v [Input] String [XMLGenT m (HSX.XML m)] (AuthId, UserPassId) newAccountForm authStateH = fieldset (errors ++> (ol $ ((,) <$> username <*> password <* submitButton) `transform` createAccount)) where br :: (XMLGenerator m, Monad v) => Form v [Input] String [XMLGenT m (HSX.XML m)] () br = view [
    ] submitButton = li $ (submit "Create Account" `setAttrs` [("class" := "submit")]) username = li $ ((label "username: " ++> inputText Nothing <++ errors) `validate` notEmpty) password1 = li $ label "password: " ++> inputPassword <++ errors password2 = li $ label "confirm password: " ++> inputPassword <++ errors -- password :: StoryForm String password = (minLengthString 6 $ (((,) <$> password1 <*> password2) `transform` samePassword)) samePassword = transformEither $ \(p1, p2) -> if p1 /= p2 then (Left "Passwords do not match.") else (Right p1) -- createAccount :: (MonadIO m) => Transformer m String (Text, String) UserId createAccount = transformEitherM $ \(username, password) -> do passHash <- liftIO $ mkHashedPass (Text.pack password) r <- update' authStateH $ CreateUserPass (UserName username) passHash -- fixme: race condition case r of (Left e) -> return (Left (userPassErrorString e)) (Right userPass) -> do authId <- update' authStateH (NewAuthMethod (AuthUserPassId (upId userPass))) return (Right (authId, upId userPass)) fieldset, li, ol :: (XMLGenerator m, Functor v, Monad v) => Form v [Input] String [XMLGenT m (HSX.XML m)] a -> Form v [Input] String [XMLGenT m (HSX.XML m)] a fieldset = mapView (\x -> [
    <% x %>
    ]) li = mapView (\x -> [
  • <% x %>
  • ]) ol = mapView (\x -> [
      <% x %>
    ]) notEmpty :: (Monad m) => Validator m String Text notEmpty = (check "field can not be empty") (not . Text.null) minLengthString 0 f = f minLengthString 1 f = errors ++> (f `validate` (check "This field can not be empty." (not . null))) minLengthString n f = errors ++> (f `validate` (check ("This field must be at least " ++ show n ++ " characters.") (\t -> length t >= n))) -- changePasswordPage :: StoryPromptsURL -> StoryPrompts Response changePasswordPage authStateH appTemplate here = do actionURL <- showURL here mAuthToken <- getAuthToken authStateH case mAuthToken of Nothing -> seeOtherURL A_Login (Just authToken) -> case tokenAuthMethod authToken of (AuthUserPassId userPassId) -> do mUserPass <- query' authStateH (AskUserPass userPassId) case mUserPass of Nothing -> internalServerError =<< appTemplate "Invalid UserPassId" ()

    Invalid UserPassId <% show $ unUserPassId userPassId %>

    (Just userPass) -> ok =<< appTemplate "Change Password" ()

    Change Password for <% unUserName $ upName userPass %>

    <% formPart "p" actionURL (XMLGenT . handleSuccess (upId userPass)) (handleFailure appTemplate) (changePasswordForm authStateH userPass) %>
    _ -> ok =<< appTemplate "Change Password Failure" ()

    This account does not use a username and password.

    where handleSuccess userPassId passwd = do hashedPass <- liftIO $ mkHashedPass (Text.pack passwd) r <- update' authStateH (SetPassword userPassId hashedPass) case r of (Just e) -> internalServerError =<< appTemplate "Internal Server Error" ()

    <% userPassErrorString e %>

    Nothing -> ok =<< appTemplate "Password Updated" ()

    Your password has updated.

    changePasswordForm :: (Functor v, MonadIO v, XMLGenerator m, EmbedAsAttr m (Attr String AuthURL)) => AcidState AuthState -> UserPass -> Form v [Input] String [XMLGenT m (HSX.XML m)] String changePasswordForm authStateH userPass = fieldset $ ol $ oldPassword *> newPassword <* changeBtn where -- form elements oldPassword = errors ++> (li $ label "old password: " ++> inputPassword `transform` checkAuth) checkAuth = transformEitherM $ \password -> do r <- query' authStateH (CheckUserPass (unUserName $ upName userPass) (Text.pack password)) case r of (Left e) -> return (Left (userPassErrorString e)) (Right _) -> return (Right password) password1 = li $ label "new password: " ++> inputPassword password2 = li $ label "new confirm password: " ++> inputPassword -- newPassword :: StoryForm String newPassword = errors ++> (minLengthString 6 $ ((((,) <$> password1 <*> password2)) `transform` samePassword)) samePassword = transformEither $ \(p1, p2) -> if p1 /= p2 then (Left "Passwords do not match.") else (Right p1) changeBtn = li $ submit "change"