{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} module Database.Persist.Query.Internal ( -- re-exported as public PersistQuery (..) , selectList -- just Internal , SelectOpt (..) , limitOffsetOrder , Filter (..) , PersistUpdate (..) , Update (..) , updateFieldDef , deleteCascadeWhere ) where import Database.Persist.Store import Database.Persist.EntityDef import Control.Monad.Trans.Class (lift) import qualified Data.Conduit as C import qualified Data.Conduit.List as CL class PersistStore b m => PersistQuery b m where -- | Update individual fields on a specific record. update :: PersistEntity val => Key b val -> [Update val] -> b m () -- | Update individual fields on any record matching the given criterion. updateWhere :: PersistEntity val => [Filter val] -> [Update val] -> b m () -- | Delete all records matching the given criterion. deleteWhere :: PersistEntity val => [Filter val] -> b m () -- | Get all records matching the given criterion in the specified order. -- Returns also the identifiers. selectSource :: (PersistEntity val, PersistEntityBackend val ~ b) => [Filter val] -> [SelectOpt val] -> C.Source (C.ResourceT (b m)) (Entity val) -- | get just the first record for the criterion selectFirst :: (PersistEntity val, PersistEntityBackend val ~ b) => [Filter val] -> [SelectOpt val] -> b m (Maybe (Entity val)) selectFirst filts opts = C.runResourceT $ selectSource filts ((LimitTo 1):opts) C.$$ CL.head -- | Get the 'Key's of all records matching the given criterion. selectKeys :: PersistEntity val => [Filter val] -> C.Source (C.ResourceT (b m)) (Key b val) -- | The total number of records fulfilling the given criterion. count :: PersistEntity val => [Filter val] -> b m Int -- | Filters which are available for 'select', 'updateWhere' and -- 'deleteWhere'. Each filter constructor specifies the field being -- filtered on, the type of comparison applied (equals, not equals, etc) -- and the argument for the comparison. data Filter v = forall typ. PersistField typ => Filter { filterField :: EntityField v typ , filterValue :: Either typ [typ] -- FIXME , filterFilter :: PersistFilter -- FIXME } | FilterAnd [Filter v] -- ^ convenient for internal use, not needed for the API | FilterOr [Filter v] data SelectOpt v = forall typ. Asc (EntityField v typ) | forall typ. Desc (EntityField v typ) | OffsetBy Int | LimitTo Int -- | Call 'select' but return the result as a list. selectList :: (PersistEntity val, PersistQuery b m, PersistEntityBackend val ~ b) => [Filter val] -> [SelectOpt val] -> b m [Entity val] selectList a b = C.runResourceT $ selectSource a b C.$$ CL.consume data PersistUpdate = Assign | Add | Subtract | Multiply | Divide -- FIXME need something else here deriving (Read, Show, Enum, Bounded) data Update v = forall typ. PersistField typ => Update { updateField :: EntityField v typ , updateValue :: typ , updateUpdate :: PersistUpdate -- FIXME Replace with expr down the road } limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val]) limitOffsetOrder opts = foldr go (0, 0, []) opts where go (LimitTo l) (_, b, c) = (l, b ,c) go (OffsetBy o) (a, _, c) = (a, o, c) go x (a, b, c) = (a, b, x : c) updateFieldDef :: PersistEntity v => Update v -> FieldDef updateFieldDef (Update f _ _) = persistFieldDef f deleteCascadeWhere :: (DeleteCascade a b m, PersistQuery b m) => [Filter a] -> b m () deleteCascadeWhere filts = do C.runResourceT $ selectKeys filts C.$$ CL.mapM_ (lift . deleteCascade)