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

Safe HaskellNone
LanguageHaskell2010

Database.Seakale.Store.Join

Description

This module allows to make SELECT queries on several tables with LEFT JOIN, RIGHT JOIN, INNER JOIN and FULL JOIN. Note that they can be nested.

To be able to create Conditons and SelectClauses, JLeft and JRight are provided to lift properties of a storable value into properties of a join.

Synopsis

Documentation

data JoinLeftProperty j f b backend n c Source #

Constructors

JLeft (f backend n c) 

Instances

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 JoinRightProperty j f a backend n c Source #

Constructors

JRight (f backend n c) 

Instances

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 #

data LeftJoin a b Source #

Constructors

LeftJoin a (Maybe b) 

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 (LeftJoin a b) Source # 

Associated Types

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

Methods

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

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

Methods

fromRow :: RowParser backend i (EntityID (LeftJoin a b)) Source #

(FromRow backend k a, FromRow backend l (Maybe b), (~) Nat ((:+) k l) i) => FromRow backend i (LeftJoin a b) Source # 

Methods

fromRow :: RowParser backend i (LeftJoin a b) Source #

(Eq (EntityID a), Eq (EntityID b)) => Eq (EntityID (LeftJoin a b)) Source # 

Methods

(==) :: EntityID (LeftJoin a b) -> EntityID (LeftJoin a b) -> Bool #

(/=) :: EntityID (LeftJoin a b) -> EntityID (LeftJoin a b) -> Bool #

(Show (EntityID a), Show (EntityID b)) => Show (EntityID (LeftJoin a b)) Source # 

Methods

showsPrec :: Int -> EntityID (LeftJoin a b) -> ShowS #

show :: EntityID (LeftJoin a b) -> String #

showList :: [EntityID (LeftJoin a b)] -> ShowS #

(Eq b, Eq a) => Eq (LeftJoin a b) Source # 

Methods

(==) :: LeftJoin a b -> LeftJoin a b -> Bool #

(/=) :: LeftJoin a b -> LeftJoin a b -> Bool #

(Show b, Show a) => Show (LeftJoin a b) Source # 

Methods

showsPrec :: Int -> LeftJoin a b -> ShowS #

show :: LeftJoin a b -> String #

showList :: [LeftJoin a b] -> ShowS #

Generic (LeftJoin a b) Source # 

Associated Types

type Rep (LeftJoin a b) :: * -> * #

Methods

from :: LeftJoin a b -> Rep (LeftJoin a b) x #

to :: Rep (LeftJoin a b) x -> LeftJoin a b #

type Rep (LeftJoin a b) Source # 
type Rep (LeftJoin a b) = D1 (MetaData "LeftJoin" "Database.Seakale.Store.Join" "seakale-0.2.1.0-18LBlBG1B0l7ZTrekNptHO" False) (C1 (MetaCons "LeftJoin" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe b)))))
data EntityID (LeftJoin a b) Source # 

data RightJoin a b Source #

Constructors

RightJoin (Maybe a) b 

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 (RightJoin a b) Source # 

Associated Types

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

Methods

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

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

Methods

fromRow :: RowParser backend i (EntityID (RightJoin a b)) Source #

(FromRow backend k (Maybe a), FromRow backend l b, (~) Nat ((:+) k l) i) => FromRow backend i (RightJoin a b) Source # 

Methods

fromRow :: RowParser backend i (RightJoin a b) Source #

(Eq (EntityID a), Eq (EntityID b)) => Eq (EntityID (RightJoin a b)) Source # 

Methods

(==) :: EntityID (RightJoin a b) -> EntityID (RightJoin a b) -> Bool #

(/=) :: EntityID (RightJoin a b) -> EntityID (RightJoin a b) -> Bool #

(Show (EntityID a), Show (EntityID b)) => Show (EntityID (RightJoin a b)) Source # 
(Eq b, Eq a) => Eq (RightJoin a b) Source # 

Methods

(==) :: RightJoin a b -> RightJoin a b -> Bool #

(/=) :: RightJoin a b -> RightJoin a b -> Bool #

(Show b, Show a) => Show (RightJoin a b) Source # 

Methods

showsPrec :: Int -> RightJoin a b -> ShowS #

show :: RightJoin a b -> String #

showList :: [RightJoin a b] -> ShowS #

data EntityID (RightJoin a b) Source # 

data InnerJoin a b Source #

Constructors

InnerJoin a b 

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 (InnerJoin a b) Source # 

Associated Types

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

Methods

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

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

Methods

fromRow :: RowParser backend i (EntityID (InnerJoin a b)) Source #

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

Methods

fromRow :: RowParser backend i (InnerJoin a b) Source #

(Eq (EntityID a), Eq (EntityID b)) => Eq (EntityID (InnerJoin a b)) Source # 

Methods

(==) :: EntityID (InnerJoin a b) -> EntityID (InnerJoin a b) -> Bool #

(/=) :: EntityID (InnerJoin a b) -> EntityID (InnerJoin a b) -> Bool #

(Show (EntityID a), Show (EntityID b)) => Show (EntityID (InnerJoin a b)) Source # 
(Eq b, Eq a) => Eq (InnerJoin a b) Source # 

Methods

(==) :: InnerJoin a b -> InnerJoin a b -> Bool #

(/=) :: InnerJoin a b -> InnerJoin a b -> Bool #

(Show b, Show a) => Show (InnerJoin a b) Source # 

Methods

showsPrec :: Int -> InnerJoin a b -> ShowS #

show :: InnerJoin a b -> String #

showList :: [InnerJoin a b] -> ShowS #

data EntityID (InnerJoin a b) Source # 

data FullJoin a b Source #

Constructors

FullJoin (Maybe a) (Maybe b) 

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 #

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

Methods

fromRow :: RowParser backend i (EntityID (FullJoin a b)) Source #

(FromRow backend k (Maybe a), FromRow backend l (Maybe b), (~) Nat ((:+) k l) i) => FromRow backend i (FullJoin a b) Source # 

Methods

fromRow :: RowParser backend i (FullJoin a b) Source #

(Eq (EntityID a), Eq (EntityID b)) => Eq (EntityID (FullJoin a b)) Source # 

Methods

(==) :: EntityID (FullJoin a b) -> EntityID (FullJoin a b) -> Bool #

(/=) :: EntityID (FullJoin a b) -> EntityID (FullJoin a b) -> Bool #

(Show (EntityID a), Show (EntityID b)) => Show (EntityID (FullJoin a b)) Source # 

Methods

showsPrec :: Int -> EntityID (FullJoin a b) -> ShowS #

show :: EntityID (FullJoin a b) -> String #

showList :: [EntityID (FullJoin a b)] -> ShowS #

(Eq b, Eq a) => Eq (FullJoin a b) Source # 

Methods

(==) :: FullJoin a b -> FullJoin a b -> Bool #

(/=) :: FullJoin a b -> FullJoin a b -> Bool #

(Show b, Show a) => Show (FullJoin a b) Source # 

Methods

showsPrec :: Int -> FullJoin a b -> ShowS #

show :: FullJoin a b -> String #

showList :: [FullJoin a b] -> ShowS #

data EntityID (FullJoin a b) Source # 

type JoinRelation backend k l a = backend -> Relation backend k l a Source #

selectJoin :: (MonadSelect backend m, Storable backend k l (f a b), FromRow backend (k :+ l) (Entity (f a b))) => JoinRelation backend k l (f a b) -> Condition backend (f a b) -> SelectClauses backend (f a b) -> m [Entity (f a b)] Source #

Send a SELECT query on a JOIN.

selectJoin_ :: (MonadSelect backend m, Storable backend k l (f a b), FromRow backend (k :+ l) (Entity (f a b))) => JoinRelation backend k l (f a b) -> Condition backend (f a b) -> m [Entity (f a b)] Source #

countJoin :: (MonadSelect backend m, Storable backend k l (f a b)) => JoinRelation backend k l (f a b) -> Condition backend (f a b) -> m Integer Source #

leftJoin :: JoinRelation backend k l a -> JoinRelation backend i j b -> Condition backend (LeftJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (LeftJoin a b) Source #

leftJoin_ :: (Storable backend k l a, Storable backend i j b) => Condition backend (LeftJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (LeftJoin a b) Source #

rightJoin :: JoinRelation backend k l a -> JoinRelation backend i j b -> Condition backend (RightJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (RightJoin a b) Source #

rightJoin_ :: (Storable backend k l a, Storable backend i j b) => Condition backend (RightJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (RightJoin a b) Source #

innerJoin :: JoinRelation backend k l a -> JoinRelation backend i j b -> Condition backend (InnerJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (InnerJoin a b) Source #

innerJoin_ :: (Storable backend k l a, Storable backend i j b) => Condition backend (InnerJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (InnerJoin a b) Source #

fullJoin :: JoinRelation backend k l a -> JoinRelation backend i j b -> Condition backend (FullJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (FullJoin a b) Source #

fullJoin_ :: (Storable backend k l a, Storable backend i j b) => Condition backend (FullJoin a b) -> JoinRelation backend (k :+ i) (l :+ j) (FullJoin a b) Source #