Merge branch 'master' into default-main

This commit is contained in:
patrick brisbin 2011-09-11 11:55:46 -04:00
commit 47b0986964
20 changed files with 123 additions and 58 deletions

1
aeson

@ -1 +0,0 @@
Subproject commit 5e7dfc9e217e84d195f2ec9904e0baee84ed18f9

@ -1 +0,0 @@
Subproject commit 084f118ff1617bbc6c132aa1b09d1f29d9e25f0b

@ -1 +0,0 @@
Subproject commit fb6f8f1f440acb4d77f7b5039813573b990e300f

View File

@ -6,9 +6,6 @@ CABAL=${CABAL:-cabal}
# install testing dependencies
$CABAL install HUnit QuickCheck 'hspec >= 0.6.1 && < 0.7' shelltestrunner
# pull submodules
git submodule update --init
pkgs=( yesod-core
yesod-json
yesod-static

View File

@ -3,6 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Yesod.Auth.BrowserId
( authBrowserId
, authBrowserId'
) where
import Yesod.Auth
@ -11,6 +12,8 @@ import Data.Text (Text)
import Yesod.Core
import Text.Hamlet (hamlet)
import Control.Monad.IO.Class (liftIO)
import qualified Data.Text as T
import Data.Maybe (fromMaybe)
#include "qq.h"
@ -46,3 +49,33 @@ authBrowserId audience = AuthPlugin
<img src="https://browserid.org/i/sign_in_green.png">
|]
}
authBrowserId' :: YesodAuth m => AuthPlugin m
authBrowserId' = AuthPlugin
{ apName = pid
, apDispatch = \m ps ->
case (m, ps) of
("GET", [assertion]) -> do
tm <- getRouteToMaster
r <- getUrlRender
let audience = T.takeWhile (/= '/') $ stripScheme $ r $ tm LoginR
memail <- liftIO $ checkAssertion audience assertion
case memail of
Nothing -> error "Invalid assertion"
Just email -> setCreds True Creds
{ credsPlugin = pid
, credsIdent = email
, credsExtra = []
}
(_, []) -> badMethod
_ -> notFound
, apLogin = \toMaster -> do
addScriptRemote browserIdJs
addHamlet [QQ(hamlet)|
<p>
<a href="javascript:navigator.id.getVerifiedEmail(function(a){if(a)document.location='@{toMaster complete}/'+a});">
<img src="https://browserid.org/i/sign_in_green.png">
|]
}
where
stripScheme t = fromMaybe t $ T.stripPrefix "//" $ snd $ T.breakOn "//" t

View File

@ -13,7 +13,6 @@ import Yesod.Form
import Network.Wai.Handler.Warp (run)
data BID = BID
type Handler = GHandler BID BID
mkYesod "BID" [parseRoutes|
/ RootR GET
@ -39,7 +38,7 @@ instance YesodAuth BID where
loginDest _ = AfterLoginR
logoutDest _ = AuthR LoginR
getAuthId = return . Just . credsIdent
authPlugins = [authBrowserId "localhost:3000"]
authPlugins = [authBrowserId']
instance RenderMessage BID FormMessage where
renderMessage _ _ = defaultFormMessage

View File

@ -1,5 +1,5 @@
name: yesod-auth
version: 0.7.1.1
version: 0.7.3
license: BSD3
license-file: LICENSE
author: Michael Snoyman, Patrick Brisbin

View File

@ -1,5 +1,5 @@
name: yesod-core
version: 0.9.1.1
version: 0.9.2
license: BSD3
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>

View File

@ -9,6 +9,6 @@ module Yesod.Form
import Yesod.Form.Types
import Yesod.Form.Functions
import Yesod.Form.Fields
import Yesod.Form.Fields hiding (FormMessage (..))
import Yesod.Form.Class
import Yesod.Form.Input

View File

@ -34,6 +34,7 @@ module Yesod.Form.Fields
) where
import Yesod.Form.Types
import Yesod.Form.I18n.English
import Yesod.Widget
import Yesod.Message (RenderMessage (renderMessage), SomeMessage (..))
import Text.Hamlet
@ -58,7 +59,6 @@ import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import Data.Text (Text, unpack, pack)
import qualified Data.Text.Read
import Data.Monoid (mappend)
import Control.Monad.IO.Class (liftIO)
import Control.Applicative ((<$>))
@ -80,44 +80,9 @@ import Yesod.Request (FileInfo)
#define HTML $html
#endif
data FormMessage = MsgInvalidInteger Text
| MsgInvalidNumber Text
| MsgInvalidEntry Text
| MsgInvalidUrl Text
| MsgInvalidEmail Text
| MsgInvalidTimeFormat
| MsgInvalidHour Text
| MsgInvalidMinute Text
| MsgInvalidSecond Text
| MsgInvalidDay
| MsgCsrfWarning
| MsgValueRequired
| MsgInputNotFound Text
| MsgSelectNone
| MsgInvalidBool Text
| MsgBoolYes
| MsgBoolNo
| MsgDelete
defaultFormMessage :: FormMessage -> Text
defaultFormMessage (MsgInvalidInteger t) = "Invalid integer: " `mappend` t
defaultFormMessage (MsgInvalidNumber t) = "Invalid number: " `mappend` t
defaultFormMessage (MsgInvalidEntry t) = "Invalid entry: " `mappend` t
defaultFormMessage MsgInvalidTimeFormat = "Invalid time, must be in HH:MM[:SS] format"
defaultFormMessage MsgInvalidDay = "Invalid day, must be in YYYY-MM-DD format"
defaultFormMessage (MsgInvalidUrl t) = "Invalid URL: " `mappend` t
defaultFormMessage (MsgInvalidEmail t) = "Invalid e-mail address: " `mappend` t
defaultFormMessage (MsgInvalidHour t) = "Invalid hour: " `mappend` t
defaultFormMessage (MsgInvalidMinute t) = "Invalid minute: " `mappend` t
defaultFormMessage (MsgInvalidSecond t) = "Invalid second: " `mappend` t
defaultFormMessage MsgCsrfWarning = "As a protection against cross-site request forgery attacks, please confirm your form submission."
defaultFormMessage MsgValueRequired = "Value is required"
defaultFormMessage (MsgInputNotFound t) = "Input not found: " `mappend` t
defaultFormMessage MsgSelectNone = "<None>"
defaultFormMessage (MsgInvalidBool t) = "Invalid boolean: " `mappend` t
defaultFormMessage MsgBoolYes = "Yes"
defaultFormMessage MsgBoolNo = "No"
defaultFormMessage MsgDelete = "Delete?"
defaultFormMessage = englishFormMessage
blank :: (Monad m, RenderMessage master FormMessage)
=> (Text -> Either FormMessage a) -> [Text] -> m (Either (SomeMessage master) (Maybe a))

View File

@ -34,7 +34,6 @@ module Yesod.Form.Functions
) where
import Yesod.Form.Types
import Yesod.Form.Fields (FormMessage (MsgCsrfWarning, MsgValueRequired))
import Data.Text (Text, pack)
import Control.Monad.Trans.RWS (ask, get, put, runRWST, tell, evalRWST)
import Control.Monad.Trans.Class (lift)

View File

@ -0,0 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}
module Yesod.Form.I18n.English where
import Yesod.Form.Types (FormMessage (..))
import Data.Monoid (mappend)
import Data.Text (Text)
englishFormMessage :: FormMessage -> Text
englishFormMessage (MsgInvalidInteger t) = "Invalid integer: " `mappend` t
englishFormMessage (MsgInvalidNumber t) = "Invalid number: " `mappend` t
englishFormMessage (MsgInvalidEntry t) = "Invalid entry: " `mappend` t
englishFormMessage MsgInvalidTimeFormat = "Invalid time, must be in HH:MM[:SS] format"
englishFormMessage MsgInvalidDay = "Invalid day, must be in YYYY-MM-DD format"
englishFormMessage (MsgInvalidUrl t) = "Invalid URL: " `mappend` t
englishFormMessage (MsgInvalidEmail t) = "Invalid e-mail address: " `mappend` t
englishFormMessage (MsgInvalidHour t) = "Invalid hour: " `mappend` t
englishFormMessage (MsgInvalidMinute t) = "Invalid minute: " `mappend` t
englishFormMessage (MsgInvalidSecond t) = "Invalid second: " `mappend` t
englishFormMessage MsgCsrfWarning = "As a protection against cross-site request forgery attacks, please confirm your form submission."
englishFormMessage MsgValueRequired = "Value is required"
englishFormMessage (MsgInputNotFound t) = "Input not found: " `mappend` t
englishFormMessage MsgSelectNone = "<None>"
englishFormMessage (MsgInvalidBool t) = "Invalid boolean: " `mappend` t
englishFormMessage MsgBoolYes = "Yes"
englishFormMessage MsgBoolNo = "No"
englishFormMessage MsgDelete = "Delete?"

View File

@ -0,0 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}
module Yesod.Form.I18n.Swedish where
import Yesod.Form.Types (FormMessage (..))
import Data.Monoid (mappend)
import Data.Text (Text)
swedishFormMessage :: FormMessage -> Text
swedishFormMessage (MsgInvalidInteger t) = "Ogiltigt antal: " `mappend` t
swedishFormMessage (MsgInvalidNumber t) = "Ogiltigt nummer: " `mappend` t
swedishFormMessage (MsgInvalidEntry t) = "Invalid entry: " `mappend` t
swedishFormMessage MsgInvalidTimeFormat = "Ogiltigt klockslag, måste vara på formatet HH:MM[:SS]"
swedishFormMessage MsgInvalidDay = "Ogiltigt datum, måste vara på formatet ÅÅÅÅ-MM-DD"
swedishFormMessage (MsgInvalidUrl t) = "Ogiltig URL: " `mappend` t
swedishFormMessage (MsgInvalidEmail t) = "Ogiltig epostadress: " `mappend` t
swedishFormMessage (MsgInvalidHour t) = "Ogiltig timme: " `mappend` t
swedishFormMessage (MsgInvalidMinute t) = "Ogiltig minut: " `mappend` t
swedishFormMessage (MsgInvalidSecond t) = "Ogiltig sekund: " `mappend` t
swedishFormMessage MsgValueRequired = "Fältet är obligatoriskt"
swedishFormMessage (MsgInputNotFound t) = "Fältet hittades ej: " `mappend` t
swedishFormMessage MsgSelectNone = "<Ingenting>"
swedishFormMessage (MsgInvalidBool t) = "Ogiltig boolesk: " `mappend` t
swedishFormMessage MsgBoolYes = "Ja"
swedishFormMessage MsgBoolNo = "Nej"
swedishFormMessage MsgDelete = "Radera?"
swedishFormMessage MsgCsrfWarning = "Som skydd mot \"cross-site request forgery\" attacker, vänligen bekräfta skickandet av formuläret."

View File

@ -9,7 +9,6 @@ module Yesod.Form.Input
) where
import Yesod.Form.Types
import Yesod.Form.Fields (FormMessage (MsgInputNotFound))
import Data.Text (Text)
import Control.Applicative (Applicative (..))
import Yesod.Handler (GHandler, GGHandler, invalidArgs, runRequestBody, getRequest, getYesod, liftIOHandler)

View File

@ -11,7 +11,7 @@ module Yesod.Form.MassInput
import Yesod.Form.Types
import Yesod.Form.Functions
import Yesod.Form.Fields (boolField, FormMessage (MsgDelete))
import Yesod.Form.Fields (boolField)
import Yesod.Widget (GWidget, whamlet)
import Yesod.Message (RenderMessage)
import Yesod.Handler (newIdent, GGHandler)

View File

@ -5,6 +5,7 @@ module Yesod.Form.Types
( -- * Helpers
Enctype (..)
, FormResult (..)
, FormMessage (..)
, Env
, FileEnv
, Ints (..)
@ -121,3 +122,22 @@ data Field sub master a = Field
-> Bool
-> GWidget sub master ()
}
data FormMessage = MsgInvalidInteger Text
| MsgInvalidNumber Text
| MsgInvalidEntry Text
| MsgInvalidUrl Text
| MsgInvalidEmail Text
| MsgInvalidTimeFormat
| MsgInvalidHour Text
| MsgInvalidMinute Text
| MsgInvalidSecond Text
| MsgInvalidDay
| MsgCsrfWarning
| MsgValueRequired
| MsgInputNotFound Text
| MsgSelectNone
| MsgInvalidBool Text
| MsgBoolYes
| MsgBoolNo
| MsgDelete

View File

@ -42,6 +42,8 @@ library
Yesod.Form.Jquery
Yesod.Form.Nic
Yesod.Form.MassInput
Yesod.Form.I18n.English
Yesod.Form.I18n.Swedish
-- FIXME Yesod.Helpers.Crud
ghc-options: -Wall

View File

@ -1,7 +1,9 @@
Yesod uses Persistent for its (you guessed it) persistence layer.
This tool will build in either SQLite or PostgreSQL support for you.
This tool will build in either SQLite or PostgreSQL or MongoDB support for you.
We recommend starting with SQLite: it has no dependencies.
We have another option: a tiny project with minimal dependencies. In particular: no database and no authentication.
We have another option: a tiny project with minimal dependencies.
Mostly this means no database and no authentication.
So, what'll it be? s for sqlite, p for postgresql, t for tiny:
So, what'll it be?
s for sqlite, p for postgresql, m for mongodb, or t for tiny:

View File

@ -1,10 +1,10 @@
User
ident Text
password Text Maybe Update
password Text Maybe
UniqueUser ident
Email
email Text
user UserId Maybe Update
verkey Text Maybe Update
user UserId Maybe
verkey Text Maybe
UniqueEmail email

View File

@ -1,5 +1,5 @@
name: yesod
version: 0.9.1.1
version: 0.9.2.1
license: BSD3
license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com>