seakale-0.2.1.0: Pure SQL layer on top of other libraries

Safe HaskellNone
LanguageHaskell2010

Database.Seakale.Store

Contents

Description

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.

Synopsis

Documentation

data Entity a Source #

A value together with its identifier.

Constructors

Entity 

Fields

Instances

(ToRow backend k (EntityID a), ToRow backend l a, (~) Nat ((:+) k l) i) => ToRow backend i (Entity a) Source # 

Methods

toRow :: backend -> Entity a -> QueryData i Source #

(FromRow backend k (EntityID a), FromRow backend l a, (~) Nat ((:+) k l) i) => FromRow backend i (Entity a) Source # 

Methods

fromRow :: RowParser backend i (Entity a) Source #

(Eq (EntityID a), Eq a) => Eq (Entity a) Source # 

Methods

(==) :: Entity a -> Entity a -> Bool #

(/=) :: Entity a -> Entity a -> Bool #

(Show (EntityID a), Show a) => Show (Entity a) Source # 

Methods

showsPrec :: Int -> Entity a -> ShowS #

show :: Entity a -> String #

showList :: [Entity a] -> ShowS #

class MonadSeakaleBase backend m => MonadSelect backend m Source #

Minimal complete definition

select, count

Instances

(MonadSelect backend m, MonadTrans t, MonadSeakaleBase backend (t m)) => MonadSelect backend (t m) Source # 

Methods

select :: (Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Relation backend k l a -> Condition backend a -> SelectClauses backend a -> t m [Entity a] Source #

count :: Storable backend k l a => Relation backend k l a -> Condition backend a -> t m Integer Source #

Monad m => MonadSelect backend (RequestT backend m) Source # 

Methods

select :: (Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Relation backend k l a -> Condition backend a -> SelectClauses backend a -> RequestT backend m [Entity a] Source #

count :: Storable backend k l a => Relation backend k l a -> Condition backend a -> RequestT backend m Integer Source #

Monad m => MonadSelect backend (FreeT (SelectF backend) m) Source # 

Methods

select :: (Storable backend k l a, FromRow backend (k :+ l) (Entity a)) => Relation backend k l a -> Condition backend a -> SelectClauses backend a -> FreeT (SelectF backend) m [Entity a] Source #

count :: Storable backend k l a => Relation backend k l a -> Condition backend a -> FreeT (SelectF backend) m Integer Source #

class MonadSelect backend m => MonadStore backend m Source #

Minimal complete definition

insert, update, delete

Instances

(MonadStore backend m, MonadTrans t, MonadSeakaleBase backend (t m)) => MonadStore backend (t m) Source # 

Methods

insert :: (Storable backend k l b, ToRow backend l b, FromRow backend k (EntityID b)) => [b] -> t m [EntityID b] Source #

update :: Storable backend k l a => UpdateSetter backend a -> Condition backend a -> t m Integer Source #

delete :: Storable backend k l a => Condition backend a -> t m Integer Source #

Monad m => MonadStore backend (RequestT backend m) Source # 

Methods

insert :: (Storable backend k l b, ToRow backend l b, FromRow backend k (EntityID b)) => [b] -> RequestT backend m [EntityID b] Source #

update :: Storable backend k l a => UpdateSetter backend a -> Condition backend a -> RequestT backend m Integer Source #

delete :: Storable backend k l a => Condition backend a -> RequestT backend m Integer Source #

MonadSelect backend m => MonadStore backend (FreeT (StoreF backend) m) Source # 

Methods

insert :: (Storable backend k l b, ToRow backend l b, FromRow backend k (EntityID b)) => [b] -> FreeT (StoreF backend) m [EntityID b] Source #

update :: Storable backend k l a => UpdateSetter backend a -> Condition backend a -> FreeT (StoreF backend) m Integer Source #

delete :: Storable backend k l a => Condition backend a -> FreeT (StoreF backend) m Integer 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.

save :: forall backend m k l a. (MonadStore backend m, Storable backend k l a, ToRow backend k (EntityID a), ToRow backend l a) => EntityID a -> a -> m () Source #

data UpdateSetter backend a Source #

Instances

Monoid (UpdateSetter backend a) Source # 

Methods

mempty :: UpdateSetter backend a #

mappend :: UpdateSetter backend a -> UpdateSetter backend a -> UpdateSetter backend a #

mconcat :: [UpdateSetter backend a] -> UpdateSetter backend a #

(=.) :: (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 #

Minimal complete definition

relation

Associated Types

data EntityID a :: * Source #

Methods

relation :: backend -> Relation backend k l a Source #

Instances

(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 # 

Associated Types

data EntityID (FullJoin a b) :: * Source #

Methods

relation :: backend -> Relation 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 # 

Associated Types

data EntityID (InnerJoin a b) :: * Source #

Methods

relation :: backend -> Relation 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 # 

Associated Types

data EntityID (RightJoin a b) :: * Source #

Methods

relation :: backend -> Relation 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 # 

Associated Types

data EntityID (LeftJoin a b) :: * Source #

Methods

relation :: backend -> Relation backend g h (LeftJoin a b) Source #

newtype Column Source #

Constructors

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 Conditions 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

Minimal complete definition

toColumns

Methods

toColumns :: backend -> f backend n b -> Vector n Column Source #

Instances

Property backend a (EntityIDProperty a) Source # 

Methods

toColumns :: backend -> EntityIDProperty a backend n b -> Vector n Column Source #

Property backend b f => Property backend (j a b) (JoinRightProperty j f a) Source # 

Methods

toColumns :: backend -> JoinRightProperty j f a backend n b -> Vector n Column Source #

Property backend a f => Property backend (j a b) (JoinLeftProperty j f b) Source # 

Methods

toColumns :: backend -> JoinLeftProperty j f b backend n b -> Vector n Column 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 Conditions on any type such as EntityID ==. UserID 42.

Constructors

EntityID :: forall backend k l a. Storable backend k l a => EntityIDProperty a backend k (EntityID a) 

Instances

Property backend a (EntityIDProperty a) Source # 

Methods

toColumns :: backend -> EntityIDProperty a backend n b -> Vector n Column Source #

SELECT clauses

data SelectClauses backend a Source #

Instances

Monoid (SelectClauses backend a) Source # 

Methods

mempty :: SelectClauses backend a #

mappend :: SelectClauses backend a -> SelectClauses backend a -> SelectClauses backend a #

mconcat :: [SelectClauses backend a] -> SelectClauses backend a #

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

data Condition backend a Source #

Instances

Monoid (Condition backend a) Source # 

Methods

mempty :: Condition backend a #

mappend :: Condition backend a -> Condition backend a -> Condition backend a #

mconcat :: [Condition backend a] -> Condition backend a #

(==.) :: (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 #

(&&.) :: Condition backend a -> Condition backend a -> Condition backend a infixr 2 Source #

(||.) :: Condition backend a -> Condition backend a -> Condition backend a infixr 2 Source #

isNull :: Property backend a f => f backend n b -> Condition backend a Source #

isNotNull :: Property backend a f => f backend n b -> Condition backend a Source #

inList :: (Property backend a f, ToRow backend n b) => f backend n b -> [b] -> Condition backend a Source #

notInList :: (Property backend a f, ToRow backend n b) => f backend n b -> [b] -> Condition backend a Source #