{-# LANGUAGE QuasiQuotes, TypeFamilies #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE Rank2Types #-} -- | A Yesod plugin for Authentication via e-mail -- -- This plugin works out of the box by only setting a few methods on the type class -- that tell the plugin how to interoprate with your user data storage (your database). -- However, almost everything is customizeable by setting more methods on the type class. -- In addition, you can send all the form submissions via JSON and completely control the user's flow. -- This is a standard registration e-mail flow -- -- 1) A user registers a new e-mail address, and an e-mail is sent there -- 2) The user clicks on the registration link in the e-mail -- Note that at this point they are actually logged in (without a password) -- That means that when they log out they will need to reset their password -- 3) The user sets their password and is redirected to the site. -- 4) The user can now -- * logout and sign in -- * reset their password module Yesod.Auth.Email ( -- * Plugin authEmail , YesodAuthEmail (..) , EmailCreds (..) , saltPass -- * Routes , loginR , registerR , forgotPasswordR , setpassR , isValidPass -- * Types , Email , VerKey , VerUrl , SaltedPass , VerStatus , Identifier -- * Misc , loginLinkKey , setLoginLinkKey -- * Default handlers , defaultRegisterHandler , defaultForgotPasswordHandler , defaultSetPasswordHandler ) where import Network.Mail.Mime (randomString) import Yesod.Auth import System.Random import qualified Data.Text as TS import qualified Data.Text as T import qualified Data.Text.Encoding as TE import qualified Crypto.Hash.MD5 as H import Data.ByteString.Base16 as B16 import Data.Text.Encoding (encodeUtf8, decodeUtf8With) import Data.Text.Encoding.Error (lenientDecode) import Data.Text (Text) import Yesod.Core import qualified Yesod.PasswordStore as PS import qualified Text.Email.Validate import qualified Yesod.Auth.Message as Msg import Control.Applicative ((<$>), (<*>)) import Control.Monad (void) import Yesod.Form import Data.Time (getCurrentTime, addUTCTime) import Safe (readMay) loginR, registerR, forgotPasswordR, setpassR :: AuthRoute loginR = PluginR "email" ["login"] registerR = PluginR "email" ["register"] forgotPasswordR = PluginR "email" ["forgot-password"] setpassR = PluginR "email" ["set-password"] verify :: Text -> Text -> AuthRoute -- FIXME verify eid verkey = PluginR "email" ["verify", eid, verkey] type Email = Text type VerKey = Text type VerUrl = Text type SaltedPass = Text type VerStatus = Bool -- | An Identifier generalizes an email address to allow users to log in with -- some other form of credentials (e.g., username). -- -- Note that any of these other identifiers must not be valid email addresses. -- -- Since 1.2.0 type Identifier = Text -- | Data stored in a database for each e-mail address. data EmailCreds site = EmailCreds { emailCredsId :: AuthEmailId site , emailCredsAuthId :: Maybe (AuthId site) , emailCredsStatus :: VerStatus , emailCredsVerkey :: Maybe VerKey , emailCredsEmail :: Email } class ( YesodAuth site , PathPiece (AuthEmailId site) , (RenderMessage site Msg.AuthMessage) ) => YesodAuthEmail site where type AuthEmailId site -- | Add a new email address to the database, but indicate that the address -- has not yet been verified. -- -- Since 1.1.0 addUnverified :: Email -> VerKey -> HandlerT site IO (AuthEmailId site) -- | Send an email to the given address to verify ownership. -- -- Since 1.1.0 sendVerifyEmail :: Email -> VerKey -> VerUrl -> HandlerT site IO () -- | Get the verification key for the given email ID. -- -- Since 1.1.0 getVerifyKey :: AuthEmailId site -> HandlerT site IO (Maybe VerKey) -- | Set the verification key for the given email ID. -- -- Since 1.1.0 setVerifyKey :: AuthEmailId site -> VerKey -> HandlerT site IO () -- | Verify the email address on the given account. -- -- Since 1.1.0 verifyAccount :: AuthEmailId site -> HandlerT site IO (Maybe (AuthId site)) -- | Get the salted password for the given account. -- -- Since 1.1.0 getPassword :: AuthId site -> HandlerT site IO (Maybe SaltedPass) -- | Set the salted password for the given account. -- -- Since 1.1.0 setPassword :: AuthId site -> SaltedPass -> HandlerT site IO () -- | Get the credentials for the given @Identifier@, which may be either an -- email address or some other identification (e.g., username). -- -- Since 1.2.0 getEmailCreds :: Identifier -> HandlerT site IO (Maybe (EmailCreds site)) -- | Get the email address for the given email ID. -- -- Since 1.1.0 getEmail :: AuthEmailId site -> HandlerT site IO (Maybe Email) -- | Generate a random alphanumeric string. -- -- Since 1.1.0 randomKey :: site -> IO Text randomKey _ = do stdgen <- newStdGen return $ TS.pack $ fst $ randomString 10 stdgen -- | Route to send user to after password has been set correctly. -- -- Since 1.2.0 afterPasswordRoute :: site -> Route site -- | Does the user need to provide the current password in order to set a -- new password? -- -- Default: if the user logged in via an email link do not require a password. -- -- Since 1.2.1 needOldPassword :: AuthId site -> HandlerT site IO Bool needOldPassword aid' = do mkey <- lookupSession loginLinkKey case mkey >>= readMay . TS.unpack of Just (aidT, time) | Just aid <- fromPathPiece aidT, toPathPiece (aid `asTypeOf` aid') == toPathPiece aid' -> do now <- liftIO getCurrentTime return $ addUTCTime (60 * 30) time <= now _ -> return True -- | Check that the given plain-text password meets minimum security standards. -- -- Default: password is at least three characters. checkPasswordSecurity :: AuthId site -> Text -> HandlerT site IO (Either Text ()) checkPasswordSecurity _ x | TS.length x >= 3 = return $ Right () | otherwise = return $ Left "Password must be at least three characters" -- | Response after sending a confirmation email. -- -- Since 1.2.2 confirmationEmailSentResponse :: Text -> HandlerT site IO TypedContent confirmationEmailSentResponse identifier = do mr <- getMessageRender selectRep $ do provideJsonMessage (mr msg) provideRep $ authLayout $ do setTitleI Msg.ConfirmationEmailSentTitle [whamlet|

_{msg}|] where msg = Msg.ConfirmationEmailSent identifier -- | Additional normalization of email addresses, besides standard canonicalization. -- -- Default: Lower case the email address. -- -- Since 1.2.3 normalizeEmailAddress :: site -> Text -> Text normalizeEmailAddress _ = TS.toLower -- | Handler called to render the registration page. The -- default works fine, but you may want to override it in -- order to have a different DOM. -- -- Default: 'defaultRegisterHandler'. -- -- Since: 1.2.6. registerHandler :: AuthHandler site Html registerHandler = defaultRegisterHandler -- | Handler called to render the \"forgot password\" page. -- The default works fine, but you may want to override it in -- order to have a different DOM. -- -- Default: 'defaultForgotPasswordHandler'. -- -- Since: 1.2.6. forgotPasswordHandler :: AuthHandler site Html forgotPasswordHandler = defaultForgotPasswordHandler -- | Handler called to render the \"set password\" page. The -- default works fine, but you may want to override it in -- order to have a different DOM. -- -- Default: 'defaultSetPasswordHandler'. -- -- Since: 1.2.6. setPasswordHandler :: Bool -- ^ Whether the old password is needed. If @True@, a -- field for the old password should be presented. -- Otherwise, just two fields for the new password are -- needed. -> AuthHandler site TypedContent setPasswordHandler = defaultSetPasswordHandler authEmail :: YesodAuthEmail m => AuthPlugin m authEmail = AuthPlugin "email" dispatch $ \tm -> [whamlet| $newline never

_{Msg.Email}
_{Msg.Password}