Use PersistRecordBackend constraint synonym
This commit is contained in:
parent
bf3a9c9dd4
commit
8e71f766b5
@ -501,10 +501,9 @@ class (YesodAuth master, YesodPersist master) => YesodAuthPersist master where
|
||||
|
||||
default getAuthEntity
|
||||
:: ( YesodPersistBackend master ~ backend
|
||||
, BaseBackend backend ~ PersistEntityBackend (AuthEntity master)
|
||||
, PersistRecordBackend (AuthEntity master) backend
|
||||
, Key (AuthEntity master) ~ AuthId master
|
||||
, PersistStore backend
|
||||
, PersistEntity (AuthEntity master)
|
||||
)
|
||||
=> AuthId master -> HandlerT master IO (Maybe (AuthEntity master))
|
||||
getAuthEntity = runDB . get
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
@ -74,7 +75,7 @@ import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
|
||||
import Data.Text.Encoding.Error (lenientDecode)
|
||||
import Network.URI (parseURI)
|
||||
import Database.Persist.Sql (PersistField, PersistFieldSql (..))
|
||||
import Database.Persist (Entity (..), SqlType (SqlString), BaseBackend, PersistQueryRead)
|
||||
import Database.Persist (Entity (..), SqlType (SqlString), PersistRecordBackend, PersistQueryRead)
|
||||
import Text.HTML.SanitizeXSS (sanitizeBalance)
|
||||
import Control.Monad (when, unless)
|
||||
import Data.Either (partitionEithers)
|
||||
@ -646,12 +647,11 @@ optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound]
|
||||
-- > where
|
||||
-- > countries = optionsPersist [] [Asc CountryName] countryName
|
||||
optionsPersist :: ( YesodPersist site
|
||||
, PersistEntity a
|
||||
, PersistQueryRead backend
|
||||
, PathPiece (Key a)
|
||||
, RenderMessage site msg
|
||||
, YesodPersistBackend site ~ backend
|
||||
, BaseBackend backend ~ PersistEntityBackend a
|
||||
, PersistRecordBackend a backend
|
||||
)
|
||||
=> [Filter a]
|
||||
-> [SelectOpt a]
|
||||
@ -672,12 +672,11 @@ optionsPersist filts ords toDisplay = fmap mkOptionList $ do
|
||||
-- Since 1.3.2
|
||||
optionsPersistKey
|
||||
:: (YesodPersist site
|
||||
, PersistEntity a
|
||||
, PersistQueryRead backend
|
||||
, PathPiece (Key a)
|
||||
, RenderMessage site msg
|
||||
, backend ~ YesodPersistBackend site
|
||||
, BaseBackend backend ~ PersistEntityBackend a
|
||||
, PersistRecordBackend a backend
|
||||
)
|
||||
=> [Filter a]
|
||||
-> [SelectOpt a]
|
||||
|
||||
@ -125,7 +125,7 @@ respondSourceDB :: YesodPersistRunner site
|
||||
respondSourceDB ctype = respondSource ctype . runDBSource
|
||||
|
||||
-- | Get the given entity by ID, or return a 404 not found if it doesn't exist.
|
||||
get404 :: (MonadIO m, PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, PersistEntity val)
|
||||
get404 :: (MonadIO m, PersistStore backend, PersistRecordBackend val backend)
|
||||
=> Key val
|
||||
-> ReaderT backend m val
|
||||
get404 key = do
|
||||
@ -136,7 +136,7 @@ get404 key = do
|
||||
|
||||
-- | Get the given entity by unique key, or return a 404 not found if it doesn't
|
||||
-- exist.
|
||||
getBy404 :: (PersistUnique backend, BaseBackend backend ~ PersistEntityBackend val, PersistEntity val, MonadIO m)
|
||||
getBy404 :: (PersistUnique backend, PersistRecordBackend val backend, MonadIO m)
|
||||
=> Unique val
|
||||
-> ReaderT backend m (Entity val)
|
||||
getBy404 key = do
|
||||
|
||||
Loading…
Reference in New Issue
Block a user