{-# LANGUAGE ExistentialQuantification #-}
module Database.Persist
( module Database.Persist.Class
, module Database.Persist.Types
, (=.), (+=.), (-=.), (*=.), (/=.)
, (==.), (!=.), (<.), (>.), (<=.), (>=.), (<-.), (/<-.), (||.)
, listToJSON
, mapToJSON
, toJsonText
, getPersistMap
, limitOffsetOrder
) where
import Data.Aeson (toJSON, ToJSON)
import Data.Aeson.Text (encodeToTextBuilder)
import qualified Data.Text as T
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (toLazyText)
import Database.Persist.Types
import Database.Persist.Class
import Database.Persist.Class.PersistField (getPersistMap)
infixr 3 =., +=., -=., *=., /=.
(=.), (+=.), (-=.), (*=.), (/=.) ::
forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
f :: EntityField v typ
f =. :: EntityField v typ -> typ -> Update v
=. a :: typ
a = EntityField v typ -> typ -> PersistUpdate -> Update v
forall record typ.
PersistField typ =>
EntityField record typ -> typ -> PersistUpdate -> Update record
Update EntityField v typ
f typ
a PersistUpdate
Assign
f :: EntityField v typ
f +=. :: EntityField v typ -> typ -> Update v
+=. a :: typ
a = EntityField v typ -> typ -> PersistUpdate -> Update v
forall record typ.
PersistField typ =>
EntityField record typ -> typ -> PersistUpdate -> Update record
Update EntityField v typ
f typ
a PersistUpdate
Add
f :: EntityField v typ
f -=. :: EntityField v typ -> typ -> Update v
-=. a :: typ
a = EntityField v typ -> typ -> PersistUpdate -> Update v
forall record typ.
PersistField typ =>
EntityField record typ -> typ -> PersistUpdate -> Update record
Update EntityField v typ
f typ
a PersistUpdate
Subtract
f :: EntityField v typ
f *=. :: EntityField v typ -> typ -> Update v
*=. a :: typ
a = EntityField v typ -> typ -> PersistUpdate -> Update v
forall record typ.
PersistField typ =>
EntityField record typ -> typ -> PersistUpdate -> Update record
Update EntityField v typ
f typ
a PersistUpdate
Multiply
f :: EntityField v typ
f /=. :: EntityField v typ -> typ -> Update v
/=. a :: typ
a = EntityField v typ -> typ -> PersistUpdate -> Update v
forall record typ.
PersistField typ =>
EntityField record typ -> typ -> PersistUpdate -> Update record
Update EntityField v typ
f typ
a PersistUpdate
Divide
infix 4 ==., <., <=., >., >=., !=.
(==.), (!=.), (<.), (<=.), (>.), (>=.) ::
forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
f :: EntityField v typ
f ==. :: EntityField v typ -> typ -> Filter v
==. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Eq
f :: EntityField v typ
f !=. :: EntityField v typ -> typ -> Filter v
!=. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Ne
f :: EntityField v typ
f <. :: EntityField v typ -> typ -> Filter v
<. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Lt
f :: EntityField v typ
f <=. :: EntityField v typ -> typ -> Filter v
<=. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Le
f :: EntityField v typ
f >. :: EntityField v typ -> typ -> Filter v
>. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Gt
f :: EntityField v typ
f >=. :: EntityField v typ -> typ -> Filter v
>=. a :: typ
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f (typ -> FilterValue typ
forall typ. typ -> FilterValue typ
FilterValue typ
a) PersistFilter
Ge
infix 4 <-., /<-.
(<-.), (/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v
f :: EntityField v typ
f <-. :: EntityField v typ -> [typ] -> Filter v
<-. a :: [typ]
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f ([typ] -> FilterValue typ
forall typ. [typ] -> FilterValue typ
FilterValues [typ]
a) PersistFilter
In
f :: EntityField v typ
f /<-. :: EntityField v typ -> [typ] -> Filter v
/<-. a :: [typ]
a = EntityField v typ -> FilterValue typ -> PersistFilter -> Filter v
forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter EntityField v typ
f ([typ] -> FilterValue typ
forall typ. [typ] -> FilterValue typ
FilterValues [typ]
a) PersistFilter
NotIn
infixl 3 ||.
(||.) :: forall v. [Filter v] -> [Filter v] -> [Filter v]
a :: [Filter v]
a ||. :: [Filter v] -> [Filter v] -> [Filter v]
||. b :: [Filter v]
b = [[Filter v] -> Filter v
forall record. [Filter record] -> Filter record
FilterOr [[Filter v] -> Filter v
forall record. [Filter record] -> Filter record
FilterAnd [Filter v]
a, [Filter v] -> Filter v
forall record. [Filter record] -> Filter record
FilterAnd [Filter v]
b]]
listToJSON :: [PersistValue] -> T.Text
listToJSON :: [PersistValue] -> Text
listToJSON = [PersistValue] -> Text
forall j. ToJSON j => j -> Text
toJsonText
mapToJSON :: [(T.Text, PersistValue)] -> T.Text
mapToJSON :: [(Text, PersistValue)] -> Text
mapToJSON = [(Text, PersistValue)] -> Text
forall j. ToJSON j => j -> Text
toJsonText
toJsonText :: ToJSON j => j -> T.Text
toJsonText :: j -> Text
toJsonText = Text -> Text
toStrict (Text -> Text) -> (j -> Text) -> j -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
toLazyText (Builder -> Text) -> (j -> Builder) -> j -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Builder
forall a. ToJSON a => a -> Builder
encodeToTextBuilder (Value -> Builder) -> (j -> Value) -> j -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Value
forall a. ToJSON a => a -> Value
toJSON
limitOffsetOrder :: PersistEntity val
=> [SelectOpt val]
-> (Int, Int, [SelectOpt val])
limitOffsetOrder :: [SelectOpt val] -> (Int, Int, [SelectOpt val])
limitOffsetOrder opts :: [SelectOpt val]
opts =
(SelectOpt val
-> (Int, Int, [SelectOpt val]) -> (Int, Int, [SelectOpt val]))
-> (Int, Int, [SelectOpt val])
-> [SelectOpt val]
-> (Int, Int, [SelectOpt val])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr SelectOpt val
-> (Int, Int, [SelectOpt val]) -> (Int, Int, [SelectOpt val])
forall record.
SelectOpt record
-> (Int, Int, [SelectOpt record]) -> (Int, Int, [SelectOpt record])
go (0, 0, []) [SelectOpt val]
opts
where
go :: SelectOpt record
-> (Int, Int, [SelectOpt record]) -> (Int, Int, [SelectOpt record])
go (LimitTo l :: Int
l) (_, b :: Int
b, c :: [SelectOpt record]
c) = (Int
l, Int
b ,[SelectOpt record]
c)
go (OffsetBy o :: Int
o) (a :: Int
a, _, c :: [SelectOpt record]
c) = (Int
a, Int
o, [SelectOpt record]
c)
go x :: SelectOpt record
x (a :: Int
a, b :: Int
b, c :: [SelectOpt record]
c) = (Int
a, Int
b, SelectOpt record
x SelectOpt record -> [SelectOpt record] -> [SelectOpt record]
forall a. a -> [a] -> [a]
: [SelectOpt record]
c)