Integrate Contrib

This commit is contained in:
Michael Snoyman 2010-06-09 10:11:13 +03:00
parent f99852fd0f
commit f76d5a6442
4 changed files with 20 additions and 9 deletions

View File

@ -10,6 +10,7 @@ module Yesod
, module Yesod.Form
, module Yesod.Hamlet
, module Yesod.Json
, module Yesod.Contrib
, Application
, liftIO
, Routes
@ -26,10 +27,11 @@ import Yesod.Dispatch
#endif
import Yesod.Request
import Yesod.Form
import Yesod.Form hiding (Form)
import Yesod.Yesod
import Yesod.Handler hiding (runHandler)
import Network.Wai (Application)
import Yesod.Hamlet
import "transformers" Control.Monad.IO.Class (liftIO)
import Web.Routes.Quasi (Routes)
import Yesod.Contrib

View File

@ -3,7 +3,14 @@
{-# LANGUAGE Rank2Types #-}
module Yesod.Contrib.Crud where
import Yesod hiding (Form)
import Yesod.Yesod
import Yesod.Dispatch
import Yesod.Content
import Yesod.Handler
import Yesod.Request
import Text.Hamlet
import Control.Monad.IO.Class (liftIO)
import Web.Routes.Quasi
import Database.Persist
import Control.Applicative.Error
import Yesod.Contrib.Formable hiding (runForm)

View File

@ -1,7 +1,12 @@
{-# LANGUAGE TypeFamilies #-}
module Yesod.Contrib.Persist where
module Yesod.Contrib.Persist
( YesodPersist (..)
, Persist (..)
) where
import Yesod
import Yesod.Handler
import Yesod.Yesod
import Database.Persist
class YesodPersist y where
type YesodDB y :: (* -> *) -> * -> *

View File

@ -301,7 +301,7 @@ getEmailRegisterR = do
postEmailRegisterR :: YesodAuth master => GHandler Auth master RepHtml
postEmailRegisterR = do
ae <- getAuthEmailSettings
email <- runFormPost $ checkEmail $ required $ input "email"
email <- runFormPost $ notEmpty $ required $ input "email" -- FIXME checkEmail
y <- getYesod
mecreds <- liftIO $ getEmailCreds ae email
(lid, verKey) <-
@ -319,9 +319,6 @@ postEmailRegisterR = do
%p A confirmation e-mail has been sent to $string.email$.
|]
checkEmail :: Form ParamValue -> Form ParamValue
checkEmail = notEmpty -- FIXME consider including e-mail validation
getEmailVerifyR :: YesodAuth master
=> Integer -> String -> GHandler Auth master RepHtml
getEmailVerifyR lid key = do
@ -368,7 +365,7 @@ postEmailLoginR :: YesodAuth master => GHandler Auth master ()
postEmailLoginR = do
ae <- getAuthEmailSettings
(email, pass) <- runFormPost $ (,)
<$> checkEmail (required $ input "email")
<$> notEmpty (required $ input "email") -- FIXME valid e-mail?
<*> required (input "password")
y <- getYesod
mecreds <- liftIO $ getEmailCreds ae email