Merge branch 'master' of github.com:yesodweb/yesod
This commit is contained in:
commit
ab980f34bd
@ -233,10 +233,17 @@ handlePluginR plugin pieces = do
|
||||
ap:_ -> apDispatch ap method pieces
|
||||
|
||||
maybeAuth :: ( YesodAuth m
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, PersistMonadBackend (b (GHandler s m)) ~ PersistEntityBackend val
|
||||
, b ~ YesodPersistBackend m
|
||||
, Key val ~ AuthId m
|
||||
, PersistStore (b (GHandler s m))
|
||||
#else
|
||||
, b ~ YesodPersistBackend m
|
||||
, b ~ PersistEntityBackend val
|
||||
, Key b val ~ AuthId m
|
||||
, PersistStore b (GHandler s m)
|
||||
#endif
|
||||
, PersistEntity val
|
||||
, YesodPersist m
|
||||
) => GHandler s m (Maybe (Entity val))
|
||||
@ -250,9 +257,15 @@ requireAuthId = maybeAuthId >>= maybe redirectLogin return
|
||||
|
||||
requireAuth :: ( YesodAuth m
|
||||
, b ~ YesodPersistBackend m
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, PersistMonadBackend (b (GHandler s m)) ~ PersistEntityBackend val
|
||||
, Key val ~ AuthId m
|
||||
, PersistStore (b (GHandler s m))
|
||||
#else
|
||||
, b ~ PersistEntityBackend val
|
||||
, Key b val ~ AuthId m
|
||||
, PersistStore b (GHandler s m)
|
||||
#endif
|
||||
, PersistEntity val
|
||||
, YesodPersist m
|
||||
) => GHandler s m (Entity val)
|
||||
|
||||
@ -5,6 +5,7 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
-------------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Yesod.Auth.HashDB
|
||||
@ -133,14 +134,24 @@ setPassword pwd u = do salt <- randomSalt
|
||||
-- | Given a user ID and password in plaintext, validate them against
|
||||
-- the database values.
|
||||
validateUser :: ( YesodPersist yesod
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, b ~ YesodPersistBackend yesod
|
||||
, PersistMonadBackend (b (GHandler sub yesod)) ~ PersistEntityBackend user
|
||||
, PersistUnique (b (GHandler sub yesod))
|
||||
#else
|
||||
, b ~ YesodPersistBackend yesod
|
||||
, b ~ PersistEntityBackend user
|
||||
, PersistStore b (GHandler sub yesod)
|
||||
, PersistUnique b (GHandler sub yesod)
|
||||
#endif
|
||||
, PersistEntity user
|
||||
, HashDBUser user
|
||||
) =>
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
Unique user -- ^ User unique identifier
|
||||
#else
|
||||
Unique user b -- ^ User unique identifier
|
||||
#endif
|
||||
-> Text -- ^ Password in plaint-text
|
||||
-> GHandler sub yesod Bool
|
||||
validateUser userID passwd = do
|
||||
@ -160,12 +171,23 @@ login = PluginR "hashdb" ["login"]
|
||||
-- | Handle the login form. First parameter is function which maps
|
||||
-- username (whatever it might be) to unique user ID.
|
||||
postLoginR :: ( YesodAuth y, YesodPersist y
|
||||
, HashDBUser user, PersistEntity user
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, b ~ YesodPersistBackend y
|
||||
, PersistMonadBackend (b (GHandler Auth y)) ~ PersistEntityBackend user
|
||||
, PersistUnique (b (GHandler Auth y))
|
||||
#else
|
||||
, b ~ YesodPersistBackend y
|
||||
, b ~ PersistEntityBackend user
|
||||
, HashDBUser user, PersistEntity user
|
||||
, PersistStore b (GHandler Auth y)
|
||||
, PersistUnique b (GHandler Auth y))
|
||||
=> (Text -> Maybe (Unique user b))
|
||||
, PersistUnique b (GHandler Auth y)
|
||||
#endif
|
||||
)
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
=> (Text -> Maybe (Unique user))
|
||||
#else
|
||||
=> (Text -> Maybe (Unique user b))
|
||||
#endif
|
||||
-> GHandler Auth y ()
|
||||
postLoginR uniq = do
|
||||
(mu,mp) <- runInputPost $ (,)
|
||||
@ -185,13 +207,25 @@ postLoginR uniq = do
|
||||
-- can be used if authHashDB is the only plugin in use.
|
||||
getAuthIdHashDB :: ( YesodAuth master, YesodPersist master
|
||||
, HashDBUser user, PersistEntity user
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, Key user ~ AuthId master
|
||||
, b ~ YesodPersistBackend master
|
||||
, PersistMonadBackend (b (GHandler sub master)) ~ PersistEntityBackend user
|
||||
, PersistUnique (b (GHandler sub master))
|
||||
#else
|
||||
, Key b user ~ AuthId master
|
||||
, b ~ YesodPersistBackend master
|
||||
, b ~ PersistEntityBackend user
|
||||
, PersistUnique b (GHandler sub master)
|
||||
, PersistStore b (GHandler sub master))
|
||||
, PersistStore b (GHandler sub master)
|
||||
#endif
|
||||
)
|
||||
=> (AuthRoute -> Route master) -- ^ your site's Auth Route
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
-> (Text -> Maybe (Unique user)) -- ^ gets user ID
|
||||
#else
|
||||
-> (Text -> Maybe (Unique user b)) -- ^ gets user ID
|
||||
#endif
|
||||
-> Creds master -- ^ the creds argument
|
||||
-> GHandler sub master (Maybe (AuthId master))
|
||||
getAuthIdHashDB authR uniq creds = do
|
||||
@ -215,11 +249,18 @@ getAuthIdHashDB authR uniq creds = do
|
||||
authHashDB :: ( YesodAuth m, YesodPersist m
|
||||
, HashDBUser user
|
||||
, PersistEntity user
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, b ~ YesodPersistBackend m
|
||||
, PersistMonadBackend (b (GHandler Auth m)) ~ PersistEntityBackend user
|
||||
, PersistUnique (b (GHandler Auth m)))
|
||||
=> (Text -> Maybe (Unique user)) -> AuthPlugin m
|
||||
#else
|
||||
, b ~ YesodPersistBackend m
|
||||
, b ~ PersistEntityBackend user
|
||||
, PersistStore b (GHandler Auth m)
|
||||
, PersistUnique b (GHandler Auth m))
|
||||
=> (Text -> Maybe (Unique user b)) -> AuthPlugin m
|
||||
#endif
|
||||
authHashDB uniq = AuthPlugin "hashdb" dispatch $ \tm -> toWidget [hamlet|
|
||||
$newline never
|
||||
<div id="header">
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod-auth
|
||||
version: 1.1.2
|
||||
version: 1.1.2.1
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Michael Snoyman, Patrick Brisbin
|
||||
@ -32,8 +32,8 @@ library
|
||||
, unordered-containers
|
||||
, yesod-form >= 1.1 && < 1.3
|
||||
, transformers >= 0.2.2 && < 0.4
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-template >= 1.0 && < 1.1
|
||||
, persistent >= 1.0 && < 1.2
|
||||
, persistent-template >= 1.0 && < 1.2
|
||||
, SHA >= 1.4.1.3 && < 1.7
|
||||
, http-conduit >= 1.5 && < 1.9
|
||||
, aeson >= 0.5
|
||||
|
||||
@ -71,6 +71,9 @@ import qualified Blaze.ByteString.Builder.Html.Utf8 as B
|
||||
import Blaze.ByteString.Builder (writeByteString, toLazyByteString)
|
||||
import Blaze.ByteString.Builder.Internal.Write (fromWriteList)
|
||||
import Database.Persist.Store (PersistEntityBackend)
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
import Database.Persist.Store (PersistMonadBackend)
|
||||
#endif
|
||||
|
||||
import Text.Blaze.Html.Renderer.String (renderHtml)
|
||||
import qualified Data.ByteString as S
|
||||
@ -492,10 +495,16 @@ optionsEnum :: (Show a, Enum a, Bounded a) => GHandler sub master (OptionList a)
|
||||
optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound]
|
||||
|
||||
optionsPersist :: ( YesodPersist master, PersistEntity a
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
, PersistQuery (YesodPersistBackend master (GHandler sub master))
|
||||
, PathPiece (Key a)
|
||||
, PersistEntityBackend a ~ PersistMonadBackend (YesodPersistBackend master (GHandler sub master))
|
||||
#else
|
||||
, PersistQuery (YesodPersistBackend master) (GHandler sub master)
|
||||
, PathPiece (Key (YesodPersistBackend master) a)
|
||||
, RenderMessage master msg
|
||||
, PersistEntityBackend a ~ YesodPersistBackend master
|
||||
#endif
|
||||
, RenderMessage master msg
|
||||
)
|
||||
=> [Filter a] -> [SelectOpt a] -> (a -> msg) -> GHandler sub master (OptionList (Entity a))
|
||||
optionsPersist filts ords toDisplay = fmap mkOptionList $ do
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod-form
|
||||
version: 1.2.0.1
|
||||
version: 1.2.0.2
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Michael Snoyman <michael@snoyman.com>
|
||||
@ -20,7 +20,7 @@ library
|
||||
, hamlet >= 1.1 && < 1.2
|
||||
, shakespeare-css >= 1.0 && < 1.1
|
||||
, shakespeare-js >= 1.0.2 && < 1.2
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent >= 1.0 && < 1.2
|
||||
, template-haskell
|
||||
, transformers >= 0.2.2 && < 0.4
|
||||
, data-default
|
||||
|
||||
@ -1,5 +1,6 @@
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
module Yesod.Persist
|
||||
( YesodPersist (..)
|
||||
, YesodDB
|
||||
@ -22,6 +23,16 @@ class YesodPersist master where
|
||||
runDB :: YesodDB sub master a -> GHandler sub master a
|
||||
|
||||
-- | Get the given entity by ID, or return a 404 not found if it doesn't exist.
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
get404 :: ( PersistStore (t m)
|
||||
, PersistEntity val
|
||||
, Monad (t m)
|
||||
, m ~ GHandler sub master
|
||||
, MonadTrans t
|
||||
, PersistMonadBackend (t m) ~ PersistEntityBackend val
|
||||
)
|
||||
=> Key val -> t m val
|
||||
#else
|
||||
get404 :: ( PersistStore b m
|
||||
, PersistEntity val
|
||||
, Monad (b m)
|
||||
@ -29,6 +40,7 @@ get404 :: ( PersistStore b m
|
||||
, MonadTrans b
|
||||
)
|
||||
=> Key b val -> b m val
|
||||
#endif
|
||||
get404 key = do
|
||||
mres <- get key
|
||||
case mres of
|
||||
@ -37,6 +49,16 @@ get404 key = do
|
||||
|
||||
-- | Get the given entity by unique key, or return a 404 not found if it doesn't
|
||||
-- exist.
|
||||
#if MIN_VERSION_persistent(1, 1, 0)
|
||||
getBy404 :: ( PersistUnique (t m)
|
||||
, PersistEntity val
|
||||
, m ~ GHandler sub master
|
||||
, Monad (t m)
|
||||
, MonadTrans t
|
||||
, PersistEntityBackend val ~ PersistMonadBackend (t m)
|
||||
)
|
||||
=> Unique val -> t m (Entity val)
|
||||
#else
|
||||
getBy404 :: ( PersistUnique b m
|
||||
, PersistEntity val
|
||||
, m ~ GHandler sub master
|
||||
@ -45,6 +67,7 @@ getBy404 :: ( PersistUnique b m
|
||||
, PersistEntityBackend val ~ b
|
||||
)
|
||||
=> Unique val b -> b m (Entity val)
|
||||
#endif
|
||||
getBy404 key = do
|
||||
mres <- getBy key
|
||||
case mres of
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod-persistent
|
||||
version: 1.1.0
|
||||
version: 1.1.0.1
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Michael Snoyman <michael@snoyman.com>
|
||||
@ -15,8 +15,8 @@ description: Some helpers for using Persistent from Yesod.
|
||||
library
|
||||
build-depends: base >= 4 && < 5
|
||||
, yesod-core >= 1.1 && < 1.2
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-template >= 1.0 && < 1.1
|
||||
, persistent >= 1.0 && < 1.2
|
||||
, persistent-template >= 1.0 && < 1.2
|
||||
, transformers >= 0.2.2 && < 0.4
|
||||
exposed-modules: Yesod.Persist
|
||||
ghc-options: -Wall
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod-test
|
||||
version: 0.3.1.1
|
||||
version: 0.3.2
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Nubis <nubis@woobiz.com.ar>
|
||||
@ -16,7 +16,7 @@ extra-source-files: README.md, LICENSE, test/main.hs
|
||||
library
|
||||
build-depends: base >= 4.3 && < 5
|
||||
, attoparsec >= 0.10 && < 0.11
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent >= 1.0 && < 1.2
|
||||
, transformers >= 0.2.2 && < 0.4
|
||||
, wai >= 1.3 && < 1.4
|
||||
, wai-test >= 1.3 && < 1.4
|
||||
|
||||
@ -30,6 +30,7 @@ module Yesod
|
||||
, julius
|
||||
, JavascriptUrl
|
||||
, renderJavascriptUrl
|
||||
, toJSON
|
||||
-- ** Cassius/Lucius
|
||||
, cassius
|
||||
, lucius
|
||||
@ -55,6 +56,7 @@ import Network.Wai.Handler.Warp (run)
|
||||
import System.IO (stderr, hPutStrLn)
|
||||
import Text.Blaze.Html (toHtml)
|
||||
import System.Environment (getEnv)
|
||||
import Data.Aeson (toJSON)
|
||||
|
||||
showIntegral :: Integral a => a -> String
|
||||
showIntegral x = show (fromIntegral x :: Integer)
|
||||
|
||||
@ -313,7 +313,7 @@ import Language.Haskell.TH.Syntax
|
||||
-- You can find more information on persistent and how to declare entities
|
||||
-- at:
|
||||
-- http://www.yesodweb.com/book/persistent/
|
||||
share [mkPersist MkPersistSettings { mpsBackend = ConT ''Action }, mkMigrate "migrateAll"]
|
||||
share [mkPersist MkPersistSettings { mpsBackend = ConT ''MongoBackend }, mkMigrate "migrateAll"]
|
||||
$(persistFileWith lowerCaseSettings "config/models")
|
||||
|
||||
{-# START_FILE PROJECTNAME.cabal #-}
|
||||
@ -370,8 +370,8 @@ library
|
||||
, clientsession >= 0.8 && < 0.9
|
||||
, bytestring >= 0.9 && < 0.11
|
||||
, text >= 0.11 && < 0.12
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-mongoDB >= 1.0 && < 1.1
|
||||
, persistent >= 1.1 && < 1.2
|
||||
, persistent-mongoDB >= 1.1 && < 1.2
|
||||
, template-haskell
|
||||
, hamlet >= 1.1 && < 1.2
|
||||
, shakespeare-css >= 1.0 && < 1.1
|
||||
|
||||
@ -371,8 +371,8 @@ library
|
||||
, clientsession >= 0.8 && < 0.9
|
||||
, bytestring >= 0.9 && < 0.11
|
||||
, text >= 0.11 && < 0.12
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-mysql >= 1.0 && < 1.1
|
||||
, persistent >= 1.1 && < 1.2
|
||||
, persistent-mysql >= 1.1 && < 1.2
|
||||
, template-haskell
|
||||
, hamlet >= 1.1 && < 1.2
|
||||
, shakespeare-css >= 1.0 && < 1.1
|
||||
|
||||
@ -371,8 +371,8 @@ library
|
||||
, clientsession >= 0.8 && < 0.9
|
||||
, bytestring >= 0.9 && < 0.11
|
||||
, text >= 0.11 && < 0.12
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-postgresql >= 1.0 && < 1.1
|
||||
, persistent >= 1.1 && < 1.2
|
||||
, persistent-postgresql >= 1.1 && < 1.2
|
||||
, template-haskell
|
||||
, hamlet >= 1.1 && < 1.2
|
||||
, shakespeare-css >= 1.0 && < 1.1
|
||||
|
||||
@ -371,8 +371,8 @@ library
|
||||
, clientsession >= 0.8 && < 0.9
|
||||
, bytestring >= 0.9 && < 0.11
|
||||
, text >= 0.11 && < 0.12
|
||||
, persistent >= 1.0 && < 1.1
|
||||
, persistent-sqlite >= 1.0 && < 1.1
|
||||
, persistent >= 1.1 && < 1.2
|
||||
, persistent-sqlite >= 1.1 && < 1.2
|
||||
, template-haskell
|
||||
, hamlet >= 1.1 && < 1.2
|
||||
, shakespeare-css >= 1.0 && < 1.1
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod
|
||||
version: 1.1.4.1
|
||||
version: 1.1.5
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Michael Snoyman <michael@snoyman.com>
|
||||
@ -43,6 +43,7 @@ library
|
||||
, warp >= 1.3 && < 1.4
|
||||
, blaze-html >= 0.5 && < 0.6
|
||||
, blaze-markup >= 0.5.1 && < 0.6
|
||||
, aeson
|
||||
|
||||
exposed-modules: Yesod
|
||||
ghc-options: -Wall
|
||||
|
||||
Loading…
Reference in New Issue
Block a user