Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides functions and types to work on values instantiating
Storable
. Such values have an associated type for their ID and an
associated relation (table name, columns for the ID and columns for the
value.)
The type classes MonadSelect
and MonadStore
and provided so that code can
be written with types such as MonadSelect m => Int -> m String
ensuring
that the function is read-only. In MonadStore
, all four operations
(SELECT
, INSERT
, UPDATE
and @DELETE#) can be done.
In order to be able to use a type with these functions, it should be made an
instance of Storable
as well as possibly an instance of 'FromRow'/'ToRow'
depending on what functions are called. It is also a good idea to define a
type specifying the properties (fields) on which we can define conditions.
See the demo for an example.
- data Entity a = Entity {}
- class MonadSeakaleBase backend m => MonadSelect backend m
- class MonadSelect backend m => MonadStore backend m
- select :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Condition backend a -> SelectClauses backend a -> m [Entity a]
- select_ :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Condition backend a -> m [Entity a]
- count :: (MonadSelect backend m, Storable backend k l a) => Condition backend a -> m Integer
- getMany :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => [EntityID a] -> m [Entity a]
- getMaybe :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => EntityID a -> m (Maybe a)
- get :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => EntityID a -> m a
- insertMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a, ToRow backend l a, FromRow backend k (EntityID a)) => [a] -> m [EntityID a]
- insert :: (MonadStore backend m, Storable backend k l a, ToRow backend l a, FromRow backend k (EntityID a)) => a -> m (EntityID a)
- updateMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a) => UpdateSetter backend a -> Condition backend a -> m Integer
- update :: (MonadStore backend m, Storable backend k l a, ToRow backend k (EntityID a)) => EntityID a -> UpdateSetter backend a -> m ()
- data UpdateSetter backend a
- (=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> UpdateSetter backend a
- deleteMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a) => Condition backend a -> m Integer
- delete :: (MonadStore backend m, Storable backend k l a, ToRow backend k (EntityID a)) => EntityID a -> m ()
- class (Typeable backend, Typeable k, Typeable l, Typeable a) => Storable backend k l a | a -> k, a -> l where
- data Relation backend k l a = Relation {}
- newtype RelationName = RelationName {}
- newtype Column = Column {
- unColumn :: ByteString -> ByteString
- class Property backend a f | f -> a where
- data EntityIDProperty a backend :: Nat -> * -> * where
- EntityID :: forall backend k l a. Storable backend k l a => EntityIDProperty a backend k (EntityID a)
- data SelectClauses backend a
- groupBy :: Property backend a f => f backend n b -> SelectClauses backend a
- asc :: Property backend a f => f backend n b -> SelectClauses backend a
- desc :: Property backend a f => f backend n b -> SelectClauses backend a
- limit :: Int -> SelectClauses backend a
- offset :: Int -> SelectClauses backend a
- data Condition backend a
- (==.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (/=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (<=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (<.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (>=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (>.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a
- (==#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (/=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (<=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (<#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (>=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (>#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a
- (==~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (/=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (<=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (<~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (>=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (>~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a
- (&&.) :: Condition backend a -> Condition backend a -> Condition backend a
- (||.) :: Condition backend a -> Condition backend a -> Condition backend a
- isNull :: Property backend a f => f backend n b -> Condition backend a
- isNotNull :: Property backend a f => f backend n b -> Condition backend a
- inList :: (Property backend a f, ToRow backend n b) => f backend n b -> [b] -> Condition backend a
- notInList :: (Property backend a f, ToRow backend n b) => f backend n b -> [b] -> Condition backend a
Documentation
A value together with its identifier.
(ToRow backend k (EntityID a), ToRow backend l a, (~) Nat ((:+) k l) i) => ToRow backend i (Entity a) Source # | |
(FromRow backend k (EntityID a), FromRow backend l a, (~) Nat ((:+) k l) i) => FromRow backend i (Entity a) Source # | |
(Eq (EntityID a), Eq a) => Eq (Entity a) Source # | |
(Show (EntityID a), Show a) => Show (Entity a) Source # | |
class MonadSeakaleBase backend m => MonadSelect backend m Source #
(MonadSelect backend m, MonadTrans t, MonadSeakaleBase backend (t m)) => MonadSelect backend (t m) Source # | |
Monad m => MonadSelect backend (RequestT backend m) Source # | |
Monad m => MonadSelect backend (FreeT (SelectF backend) m) Source # | |
class MonadSelect backend m => MonadStore backend m Source #
(MonadStore backend m, MonadTrans t, MonadSeakaleBase backend (t m)) => MonadStore backend (t m) Source # | |
Monad m => MonadStore backend (RequestT backend m) Source # | |
MonadSelect backend m => MonadStore backend (FreeT (StoreF backend) m) Source # | |
Operations
select :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Condition backend a -> SelectClauses backend a -> m [Entity a] Source #
Select all entities for the corresponding relation.
select_ :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Condition backend a -> m [Entity a] Source #
Like select
but without any other clauses than WHERE
.
count :: (MonadSelect backend m, Storable backend k l a) => Condition backend a -> m Integer Source #
Count the number of rows matching the conditions.
getMany :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => [EntityID a] -> m [Entity a] Source #
Select all entities with the given IDs.
getMaybe :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => EntityID a -> m (Maybe a) Source #
Return the value corresponding to the given ID if it exists, otherwise
return Nothing
.
get :: (MonadSelect backend m, Storable backend k l a, FromRow backend (k :+ l) (Entity a), ToRow backend k (EntityID a)) => EntityID a -> m a Source #
Return the value corresponding to the given ID if it exists, otherwise
throw EntityNotFoundError
.
insertMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a, ToRow backend l a, FromRow backend k (EntityID a)) => [a] -> m [EntityID a] Source #
Insert the given values and return their ID in the same order.
insert :: (MonadStore backend m, Storable backend k l a, ToRow backend l a, FromRow backend k (EntityID a)) => a -> m (EntityID a) Source #
Like insertMany
but for only one value.
updateMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a) => UpdateSetter backend a -> Condition backend a -> m Integer Source #
Update columns on rows matching the given conditions and return the number of rows affected.
update :: (MonadStore backend m, Storable backend k l a, ToRow backend k (EntityID a)) => EntityID a -> UpdateSetter backend a -> m () Source #
Update columns on the row with the given ID.
data UpdateSetter backend a Source #
Monoid (UpdateSetter backend a) Source # | |
(=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> UpdateSetter backend a Source #
deleteMany :: forall backend m k l a. (MonadStore backend m, Storable backend k l a) => Condition backend a -> m Integer Source #
Delete rows matching the given conditions.
delete :: (MonadStore backend m, Storable backend k l a, ToRow backend k (EntityID a)) => EntityID a -> m () Source #
Delete the row with the given ID.
Setup
class (Typeable backend, Typeable k, Typeable l, Typeable a) => Storable backend k l a | a -> k, a -> l where Source #
(Storable backend k l a, Storable backend i j b, (~) Nat ((:+) k i) g, (~) Nat ((:+) l j) h, Typeable Nat g, Typeable Nat h) => Storable backend g h (FullJoin a b) Source # | |
(Storable backend k l a, Storable backend i j b, (~) Nat ((:+) k i) g, (~) Nat ((:+) l j) h, Typeable Nat g, Typeable Nat h) => Storable backend g h (InnerJoin a b) Source # | |
(Storable backend k l a, Storable backend i j b, (~) Nat ((:+) k i) g, (~) Nat ((:+) l j) h, Typeable Nat g, Typeable Nat h) => Storable backend g h (RightJoin a b) Source # | |
(Storable backend k l a, Storable backend i j b, (~) Nat ((:+) k i) g, (~) Nat ((:+) l j) h, Typeable Nat g, Typeable Nat h) => Storable backend g h (LeftJoin a b) Source # | |
newtype RelationName Source #
Column | |
|
Properties
class Property backend a f | f -> a where Source #
Specify that the type f
specify properties of a
. These values of type
f
can then be used to create Condition
s on type a
. The type parameters
n
and b
in the class definition are, respectively, the number of rows
taken by this property and the associated type.
See the following example:
data User = User { userFirstName :: String , userLastName :: String } data UserProperty b n a where UserFirstName :: UserProperty b One String UserLastName :: UserProperty b One String UserFirstName ==. "Marie" &&. UserLastName ==. "Curie" :: Condition backend User
Property backend a (EntityIDProperty a) Source # | |
Property backend b f => Property backend (j a b) (JoinRightProperty j f a) Source # | |
Property backend a f => Property backend (j a b) (JoinLeftProperty j f b) Source # | |
data EntityIDProperty a backend :: Nat -> * -> * where Source #
Property of any value instantiating Storable
and selecting its ID.
This can be used to easily create Condition
s on any type such as
EntityID ==. UserID 42
.
EntityID :: forall backend k l a. Storable backend k l a => EntityIDProperty a backend k (EntityID a) |
Property backend a (EntityIDProperty a) Source # | |
SELECT clauses
data SelectClauses backend a Source #
Monoid (SelectClauses backend a) Source # | |
groupBy :: Property backend a f => f backend n b -> SelectClauses backend a Source #
asc :: Property backend a f => f backend n b -> SelectClauses backend a Source #
desc :: Property backend a f => f backend n b -> SelectClauses backend a Source #
limit :: Int -> SelectClauses backend a Source #
offset :: Int -> SelectClauses backend a Source #
Conditions
(==.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(/=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(<=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(<.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(>=.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(>.) :: (Property backend a f, ToRow backend n b) => f backend n b -> b -> Condition backend a infix 4 Source #
(==#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(/=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(<=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(<#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(>=#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(>#) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n b -> Condition backend a infix 4 Source #
(==~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #
(/=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #
(<=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #
(<~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #
(>=~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #
(>~) :: (Property backend a f, Property backend a g) => f backend n b -> g backend n c -> Condition backend a infix 4 Source #