relational-query-0.12.0.1: Typeful, Modular, Relational, algebraic query engine

Copyright2015-2018 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Database.Relational.Arrow

Contents

Description

This module defines arrow version combinators which improves type-safty on building queries. Referencing the local projected records may cause to break the result query. It is possible to controls injection of previous local projected records by restricting domain type of arrow. This idea is imported from Opaleye:

Importing this module instead of Database.Relational.Query enables to build query using arrow combinators.

Synopsis

Documentation

data Unique #

Constraint type. Unique key.

data NotNull #

Constraint type. Not-null key.

Instances
HasColumnConstraint NotNull a => HasColumnConstraint NotNull (a, b)

Inference rule of ColumnConstraint NotNull for tuple (,) type.

Instance details

Defined in Database.Record.KeyConstraint

data Primary #

Constraint type. Primary key.

data Config Source #

Configuration type.

Instances
Show Config Source # 
Instance details

Defined in Database.Relational.Internal.Config

data IdentifierQuotation Source #

Configuration for quotation of identifiers of SQL.

Constructors

NoQuotation 
Quotation Char 

data SchemaNameMode Source #

Schema name qualify mode in SQL string.

Constructors

SchemaQualified

Schema qualified table name in SQL string

SchemaNotQualified

Not qualified table name in SQL string

data ProductUnitSupport Source #

Unit of product is supported or not.

data NameConfig Source #

NameConfig type to customize names of expanded templates.

defaultNameConfig :: NameConfig Source #

Default implementation of NameConfig type.

defaultConfig :: Config Source #

Default configuration of Config. To change some behaviour of relational-query, use record update syntax:

  defaultConfig
    { productUnitSupport            =  PUSupported
    , chunksInsertSize              =  256
    , schemaNameMode                =  SchemaQualified
    , normalizedTableName           =  True
    , verboseAsCompilerWarning      =  False
    , disableOverloadedProjection   =  False
    , disableSpecializedProjection  =  False
    , identifierQuotation           =  NoQuotation
    , nameConfig                    =
       defaultNameConfig
       { recordConfig     =  defaultNameConfig
       , relationVarName  =  \schema table -> varCamelcaseName $ table ++ "_" ++ scheme
       -- ^ append the table name after the schema name. e.g. "schemaTable"
       }
    }

data Power Source #

Type tag for aggregatings power set

data SetList Source #

Type tag for aggregatings GROUPING SETS

data OverWindow Source #

Type tag for window function building

Instances
AggregatedContext OverWindow Source #

OverWindow context is aggregated context

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext OverWindow Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

data Exists Source #

Type tag for exists predicate

data Aggregated Source #

Type tag for aggregated query

Instances
AggregatedContext Aggregated Source #

Aggregated context is aggregated context

Instance details

Defined in Database.Relational.Projectable.Instances

OperatorContext Aggregated Source #

full SQL expression is availabe in Aggregated context

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Aggregated Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

MonadRestrict Flat q => MonadRestrict Flat (Restrictings Aggregated q) Source #

Restricted MonadRestrict instance.

Instance details

Defined in Database.Relational.Monad.Aggregate

data Flat Source #

Type tag for flat (not-aggregated) query

Instances
OperatorContext Flat Source #

full SQL expression is availabe in Flat context

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Flat Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

MonadRestrict Flat q => MonadRestrict Flat (Restrictings Aggregated q) Source #

Restricted MonadRestrict instance.

Instance details

Defined in Database.Relational.Monad.Aggregate

type StringSQL = Keyword Source #

String wrap type for SQL strings.

data Pi r0 r1 Source #

Projection path from type r0 into type r1. This type also indicate key object which type is r1 for record type r0.

Instances
HasProjection l a b => IsLabel l (Pi a b) #

Derive IsLabel instance from HasProjection.

Instance details

Defined in Database.Relational.OverloadedProjection

Methods

fromLabel :: Pi a b #

ProductIsoFunctor (Pi a) Source #

Map projection path Pi which has record result type.

Instance details

Defined in Database.Relational.Pi.Unsafe

Methods

(|$|) :: ProductConstructor (a0 -> b) => (a0 -> b) -> Pi a a0 -> Pi a b #

ProductIsoApplicative (Pi a) Source #

Compose projection path Pi which has record result type using applicative style.

Instance details

Defined in Database.Relational.Pi.Unsafe

Methods

pureP :: ProductConstructor a0 => a0 -> Pi a a0 #

(|*|) :: Pi a (a0 -> b) -> Pi a a0 -> Pi a b #

Category Pi Source # 
Instance details

Defined in Database.Relational.Pi.Unsafe

Methods

id :: Pi a a #

(.) :: Pi b c -> Pi a b -> Pi a c #

ProductIsoEmpty (Pi a) () Source # 
Instance details

Defined in Database.Relational.Pi.Unsafe

Methods

pureE :: Pi a () #

peRight :: Pi a (a0, ()) -> Pi a a0 #

peLeft :: Pi a ((), a0) -> Pi a a0 #

PersistableWidth r0 => Show (Pi r0 r1) Source # 
Instance details

Defined in Database.Relational.Pi.Unsafe

Methods

showsPrec :: Int -> Pi r0 r1 -> ShowS #

show :: Pi r0 r1 -> String #

showList :: [Pi r0 r1] -> ShowS #

(<.>) :: Pi a b -> Pi b c -> Pi a c infixl 8 Source #

Compose projection path.

(<?.>) :: Pi a (Maybe b) -> Pi b c -> Pi a (Maybe c) infixl 8 Source #

Compose projection path. Maybe phantom functor is map-ed.

(<?.?>) :: Pi a (Maybe b) -> Pi b (Maybe c) -> Pi a (Maybe c) infixl 8 Source #

Compose projection path. Maybe phantom functors are join-ed like >=>.

id' :: Pi a a Source #

Identity projection path.

class PersistableWidth ct => HasConstraintKey c r ct where Source #

Constraint Key inference interface.

Minimal complete definition

constraintKey

Methods

constraintKey :: Key c r ct Source #

Infer constraint key.

data Key c r ct Source #

Constraint Key proof object. Constraint type c, record type r and columns type ct.

tableConstraint :: Key c r ct -> KeyConstraint c r Source #

Get table constraint KeyConstraint proof object from constraint Key.

projectionKey :: Key c r ct -> Pi r ct Source #

Get projection path proof object from constraint Key.

uniqueKey :: PersistableWidth ct => Key Primary r ct -> Key Unique r ct Source #

Derive Unique constraint Key from Primary constraint Key

derivedUniqueKey :: HasConstraintKey Primary r ct => Key Unique r ct Source #

Inferred Unique constraint Key. Record type r has unique key which type is ct derived from primay key.

type ShowConstantTermsSQL = LiteralSQL Source #

Deprecated: Use LiteralSQL instead of this.

Deprecated.

class LiteralSQL a where Source #

LiteralSQL a is implicit rule to derive function to convert from haskell record type a into SQL literal row-value.

Generic programming (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#generic-programming) with default signature is available for LiteralSQL class, so you can make instance like below:

  {-# LANGUAGE DeriveGeneric #-}
  import GHC.Generics (Generic)
  --
  data Foo = Foo { ... } deriving Generic
  instance LiteralSQL Foo

Methods

showLiteral' :: a -> DList StringSQL Source #

showLiteral' :: (Generic a, GLiteralSQL (Rep a)) => a -> DList StringSQL Source #

Instances
LiteralSQL Bool Source #

Constant SQL terms of Bool.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Char Source #

Constant SQL terms of Char.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Double Source #

Constant SQL terms of Double. Caution for floating-point error rate.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Float Source #

Constant SQL terms of Float. Caution for floating-point error rate.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int Source #

Constant SQL terms of Int. Use this carefully, because this is architecture dependent size of integer type.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int8 Source #

Constant SQL terms of Int8.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int16 Source #

Constant SQL terms of Int16.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int32 Source #

Constant SQL terms of Int32.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int64 Source #

Constant SQL terms of Int64.

Instance details

Defined in Database.Relational.Pure

LiteralSQL () Source #

Constant SQL terms of '()'.

Instance details

Defined in Database.Relational.Pure

LiteralSQL String Source #

Constant SQL terms of String.

Instance details

Defined in Database.Relational.Pure

LiteralSQL ByteString Source #

Constant SQL terms of ByteString.

Instance details

Defined in Database.Relational.Pure

LiteralSQL ByteString Source #

Constant SQL terms of ByteString.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Text Source #

Constant SQL terms of Text.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Text Source #

Constant SQL terms of Text.

Instance details

Defined in Database.Relational.Pure

LiteralSQL ZonedTime Source #

Constant SQL terms of ZonedTime. This generates ***NOT STANDARD*** SQL of TIMESTAMPTZ literal.

Instance details

Defined in Database.Relational.Pure

LiteralSQL LocalTime Source #

Constant SQL terms of LocalTime.

Instance details

Defined in Database.Relational.Pure

LiteralSQL TimeOfDay Source #

Constant SQL terms of TimeOfDay.

Instance details

Defined in Database.Relational.Pure

LiteralSQL UTCTime Source #

Constant SQL terms of UTCTime. This generates ***NOT STANDARD*** SQL of TIMESTAMPTZ literal with UTC timezone.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Day Source #

Constant SQL terms of Day.

Instance details

Defined in Database.Relational.Pure

(PersistableWidth a, LiteralSQL a) => LiteralSQL (Maybe a) Source #

Constant SQL terms of Maybe type. Width inference is required.

Instance details

Defined in Database.Relational.Pure

(LiteralSQL a1, LiteralSQL a2) => LiteralSQL (a1, a2) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3) => LiteralSQL (a1, a2, a3) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4) => LiteralSQL (a1, a2, a3, a4) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5) => LiteralSQL (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5, LiteralSQL a6) => LiteralSQL (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5, a6) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5, LiteralSQL a6, LiteralSQL a7) => LiteralSQL (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5, a6, a7) -> DList StringSQL Source #

showLiteral :: LiteralSQL a => a -> [StringSQL] Source #

Convert from haskell record to SQL literal row-value.

showConstantTermsSQL' :: ShowConstantTermsSQL a => a -> DList StringSQL Source #

Deprecated: Use showLiteral' instead of this.

showConstantTermsSQL :: ShowConstantTermsSQL a => a -> [StringSQL] Source #

Deprecated: Use showLiteral instead of this.

Deprecated.

class PersistableWidth ct => ScalarDegree ct Source #

Constraint which represents scalar degree.

Instances
ScalarDegree ct => ScalarDegree (Maybe ct) Source # 
Instance details

Defined in Database.Relational.Scalar

type PI c a b = Record c a -> Record c b Source #

Type for projection function.

type Predicate c = Record c (Maybe Bool) Source #

Type for predicate to restrict of query result.

data Record c t Source #

Phantom typed record. Projected into Haskell record type t.

Instances
(PersistableWidth a, HasProjection l a b) => IsLabel l (PI c a b) #

Derive PI label.

Instance details

Defined in Database.Relational.OverloadedProjection

Methods

fromLabel :: PI c a b #

ProductIsoFunctor (Record c) #

Map Record which result type is record.

Instance details

Defined in Database.Relational.Record

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> Record c a -> Record c b #

ProductIsoApplicative (Record c) #

Compose Record using applicative style.

Instance details

Defined in Database.Relational.Record

Methods

pureP :: ProductConstructor a => a -> Record c a #

(|*|) :: Record c (a -> b) -> Record c a -> Record c b #

ProjectableMaybe (Record c) Source #

Control phantom Maybe type in record type Record.

Instance details

Defined in Database.Relational.Projectable

Methods

just :: Record c a -> Record c (Maybe a) Source #

flattenMaybe :: Record c (Maybe (Maybe a)) -> Record c (Maybe a) Source #

ProductIsoEmpty (Record c) () # 
Instance details

Defined in Database.Relational.Record

Methods

pureE :: Record c () #

peRight :: Record c (a, ()) -> Record c a #

peLeft :: Record c ((), a) -> Record c a #

Show (Record c t) Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Record c t -> ShowS #

show :: Record c t -> String #

showList :: [Record c t] -> ShowS #

data SubQuery Source #

Sub-query type

Instances
Show SubQuery Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data AggregateKey a Source #

Typeful aggregate element.

data Nulls Source #

Order of null.

Constructors

NullsFirst 
NullsLast 
Instances
Show Nulls Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Nulls -> ShowS #

show :: Nulls -> String #

showList :: [Nulls] -> ShowS #

data Order Source #

Order direction. Ascendant or Descendant.

Constructors

Asc 
Desc 
Instances
Show Order Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

unitSQL :: SubQuery -> String Source #

SQL string for nested-qeury.

data PlaceHolders p Source #

Placeholder parameter type which has real parameter type arguemnt p.

Instances
ProductIsoFunctor PlaceHolders #

Compose seed of record type PlaceHolders.

Instance details

Defined in Database.Relational.Projectable.Instances

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> PlaceHolders a -> PlaceHolders b #

ProductIsoApplicative PlaceHolders #

Compose record type PlaceHolders using applicative style.

Instance details

Defined in Database.Relational.Projectable.Instances

ProjectableMaybe PlaceHolders Source #

Control phantom Maybe type in placeholder parameters.

Instance details

Defined in Database.Relational.Projectable

ProductIsoEmpty PlaceHolders () #

Zipping except for identity element laws against placeholder parameter type.

Instance details

Defined in Database.Relational.Projectable.Instances

class SqlContext c where Source #

Interface to project SQL terms unsafely.

Minimal complete definition

unsafeProjectSqlTerms

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Record c t Source #

Unsafely project from SQL expression terms.

Instances
SqlContext OverWindow Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Aggregated Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Flat Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

data Relation p r Source #

Relation type with place-holder parameter p and query result type r.

Instances
Show (Relation p r) Source # 
Instance details

Defined in Database.Relational.Monad.BaseType

Methods

showsPrec :: Int -> Relation p r -> ShowS #

show :: Relation p r -> String #

showList :: [Relation p r] -> ShowS #

type ConfigureQuery = Qualify (QueryConfig Identity) Source #

Thin monad type for untyped structure.

configureQuery :: ConfigureQuery q -> Config -> q Source #

Run ConfigureQuery monad with initial state to get only result.

qualifyQuery :: a -> ConfigureQuery (Qualified a) Source #

Get qualifyed table form query.

askConfig :: ConfigureQuery Config Source #

Read configuration.

unsafeTypeRelation :: ConfigureQuery SubQuery -> Relation p r Source #

Unsafely type qualified subquery into record typed relation type.

untypeRelation :: Relation p r -> ConfigureQuery SubQuery Source #

Sub-query Qualify monad from relation.

rightPh :: Relation ((), p) r -> Relation p r Source #

Simplify placeholder type applying left identity element.

leftPh :: Relation (p, ()) r -> Relation p r Source #

Simplify placeholder type applying right identity element.

sqlFromRelationWith :: Relation p r -> Config -> StringSQL Source #

Generate SQL string from Relation with configuration.

dump :: Relation p r -> String Source #

Dump internal structure tree.

class PersistableWidth r => TableDerivable r where Source #

Inference rule of Table existence.

Minimal complete definition

derivedTable

data Table r Source #

Phantom typed table type

data RecordList p t Source #

Projected record list type for row list.

list :: [p t] -> RecordList p t Source #

Make projected record list from Record list.

type QuerySuffix = [Keyword] Source #

Type for query suffix words

updateOtherThanKeySQL Source #

Arguments

:: Table r

Table metadata

-> Pi r p

Key columns

-> String

Result SQL

Generate update SQL specified by single key.

tuplePi2_0' :: forall a1 a2. (PersistableWidth a1, PersistableWidth a2) => Pi (a1, a2) a1 Source #

tuplePi2_1' :: forall a1 a2. (PersistableWidth a1, PersistableWidth a2) => Pi (a1, a2) a2 Source #

tuplePi3_0' :: forall a1 a2 a3. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3) => Pi (a1, a2, a3) a1 Source #

tuplePi3_1' :: forall a1 a2 a3. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3) => Pi (a1, a2, a3) a2 Source #

tuplePi3_2' :: forall a1 a2 a3. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3) => Pi (a1, a2, a3) a3 Source #

tuplePi4_0' :: forall a1 a2 a3 a4. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4) => Pi (a1, a2, a3, a4) a1 Source #

tuplePi4_1' :: forall a1 a2 a3 a4. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4) => Pi (a1, a2, a3, a4) a2 Source #

tuplePi4_2' :: forall a1 a2 a3 a4. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4) => Pi (a1, a2, a3, a4) a3 Source #

tuplePi4_3' :: forall a1 a2 a3 a4. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4) => Pi (a1, a2, a3, a4) a4 Source #

tuplePi5_0' :: forall a1 a2 a3 a4 a5. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5) => Pi (a1, a2, a3, a4, a5) a1 Source #

tuplePi5_1' :: forall a1 a2 a3 a4 a5. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5) => Pi (a1, a2, a3, a4, a5) a2 Source #

tuplePi5_2' :: forall a1 a2 a3 a4 a5. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5) => Pi (a1, a2, a3, a4, a5) a3 Source #

tuplePi5_3' :: forall a1 a2 a3 a4 a5. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5) => Pi (a1, a2, a3, a4, a5) a4 Source #

tuplePi5_4' :: forall a1 a2 a3 a4 a5. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5) => Pi (a1, a2, a3, a4, a5) a5 Source #

tuplePi6_0' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a1 Source #

tuplePi6_1' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a2 Source #

tuplePi6_2' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a3 Source #

tuplePi6_3' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a4 Source #

tuplePi6_4' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a5 Source #

tuplePi6_5' :: forall a1 a2 a3 a4 a5 a6. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6) => Pi (a1, a2, a3, a4, a5, a6) a6 Source #

tuplePi7_0' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a1 Source #

tuplePi7_1' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a2 Source #

tuplePi7_2' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a3 Source #

tuplePi7_3' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a4 Source #

tuplePi7_4' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a5 Source #

tuplePi7_5' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a6 Source #

tuplePi7_6' :: forall a1 a2 a3 a4 a5 a6 a7. (PersistableWidth a1, PersistableWidth a2, PersistableWidth a3, PersistableWidth a4, PersistableWidth a5, PersistableWidth a6, PersistableWidth a7) => Pi (a1, a2, a3, a4, a5, a6, a7) a7 Source #

fst' :: (PersistableWidth a, PersistableWidth b) => Pi (a, b) a Source #

Projection path for fst of tuple.

snd' :: (PersistableWidth a, PersistableWidth b) => Pi (a, b) b Source #

Projection path for snd of tuple.

class ProjectableFlattenMaybe a b where Source #

Interface to compose phantom Maybe nested type.

Minimal complete definition

flatten

Methods

flatten :: ProjectableMaybe p => p a -> p b Source #

Instances
ProjectableFlattenMaybe (Maybe a) b => ProjectableFlattenMaybe (Maybe (Maybe a)) b Source #

Compose Maybe type in record phantom type.

Instance details

Defined in Database.Relational.Projectable

Methods

flatten :: ProjectableMaybe p => p (Maybe (Maybe a)) -> p b Source #

ProjectableFlattenMaybe (Maybe a) (Maybe a) Source #

Not Maybe type is not processed.

Instance details

Defined in Database.Relational.Projectable

Methods

flatten :: ProjectableMaybe p => p (Maybe a) -> p (Maybe a) Source #

class ProjectableMaybe p where Source #

Interface to control Maybe of phantom type in records.

Minimal complete definition

just, flattenMaybe

Methods

just :: p a -> p (Maybe a) Source #

Cast record phantom type into Maybe.

flattenMaybe :: p (Maybe (Maybe a)) -> p (Maybe a) Source #

Compose nested Maybe phantom type on record.

Instances
ProjectableMaybe PlaceHolders Source #

Control phantom Maybe type in placeholder parameters.

Instance details

Defined in Database.Relational.Projectable

ProjectableMaybe (Record c) Source #

Control phantom Maybe type in record type Record.

Instance details

Defined in Database.Relational.Projectable

Methods

just :: Record c a -> Record c (Maybe a) Source #

flattenMaybe :: Record c (Maybe (Maybe a)) -> Record c (Maybe a) Source #

type SqlBinOp = Keyword -> Keyword -> Keyword Source #

Binary operator type for SQL String.

unsafeProjectSql' :: SqlContext c => StringSQL -> Record c t Source #

Unsafely Project single SQL term.

unsafeProjectSql :: SqlContext c => String -> Record c t Source #

Unsafely Project single SQL string. String interface of unsafeProjectSql''.

nothing :: (OperatorContext c, SqlContext c, PersistableWidth a) => Record c (Maybe a) Source #

Record with polymorphic phantom type of SQL null value. Semantics of comparing is unsafe.

value :: (LiteralSQL t, OperatorContext c) => t -> Record c t Source #

Generate record with polymorphic type of SQL constant values from Haskell value.

valueTrue :: OperatorContext c => Record c (Maybe Bool) Source #

Record with polymorphic type of SQL true value.

valueFalse :: OperatorContext c => Record c (Maybe Bool) Source #

Record with polymorphic type of SQL false value.

values :: (LiteralSQL t, OperatorContext c) => [t] -> RecordList (Record c) t Source #

RecordList with polymorphic type of SQL set value from Haskell list.

unsafeShowSql' :: Record c a -> StringSQL Source #

Unsafely generate SQL expression term from record object.

unsafeShowSql Source #

Arguments

:: Record c a

Source record object

-> String

Result SQL expression string.

Unsafely generate SQL expression string from record object. String interface of unsafeShowSql'.

unsafeUniOp :: SqlContext c2 => (Keyword -> Keyword) -> Record c1 a -> Record c2 b Source #

Unsafely make unary operator for records from SQL keyword.

unsafeBinOp :: SqlContext k => SqlBinOp -> Record k a -> Record k b -> Record k c Source #

Unsafely make binary operator for records from string binary operator.

(.=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL = .

(.<.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL < .

(.<=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <= .

(.>.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL > .

(.>=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL >= .

(.<>.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <> .

and' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) -> Record c (Maybe Bool) infixr 3 Source #

Logical operator corresponding SQL AND .

or' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) -> Record c (Maybe Bool) infixr 2 Source #

Logical operator corresponding SQL OR .

not' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) Source #

Logical operator corresponding SQL NOT .

exists :: OperatorContext c => RecordList (Record Exists) r -> Record c (Maybe Bool) Source #

Logical operator corresponding SQL EXISTS .

(.||.) :: OperatorContext c => Record c a -> Record c a -> Record c a infixl 5 Source #

Concatinate operator corresponding SQL || .

(?||?) :: (OperatorContext c, IsString a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 5 Source #

Concatinate operator corresponding SQL || . Maybe type version.

like' :: (OperatorContext c, IsString a) => Record c a -> Record c a -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe' :: (OperatorContext c, IsString a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

like :: (OperatorContext c, IsString a, LiteralSQL a) => Record c a -> a -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe :: (OperatorContext c, IsString a, LiteralSQL a) => Record c (Maybe a) -> a -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE . Maybe type version.

(.+.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 6 Source #

Number operator corresponding SQL + .

(.-.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 6 Source #

Number operator corresponding SQL - .

(./.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 7 Source #

Number operator corresponding SQL /// .

(.*.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 7 Source #

Number operator corresponding SQL * .

negate' :: (OperatorContext c, Num a) => Record c a -> Record c a Source #

Number negate uni-operator corresponding SQL -.

fromIntegral' :: (SqlContext c, Integral a, Num b) => Record c a -> Record c b Source #

Number fromIntegral uni-operator.

showNum :: (SqlContext c, Num a, IsString b) => Record c a -> Record c b Source #

Unsafely show number into string-like type in records.

(?+?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 6 Source #

Number operator corresponding SQL + .

(?-?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 6 Source #

Number operator corresponding SQL - .

(?/?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 7 Source #

Number operator corresponding SQL /// .

(?*?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 7 Source #

Number operator corresponding SQL * .

negateMaybe :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) Source #

Number negate uni-operator corresponding SQL -.

fromIntegralMaybe :: (SqlContext c, Integral a, Num b) => Record c (Maybe a) -> Record c (Maybe b) Source #

Number fromIntegral uni-operator.

showNumMaybe :: (SqlContext c, Num a, IsString b) => Record c (Maybe a) -> Record c (Maybe b) Source #

Unsafely show number into string-like type in records.

caseSearch Source #

Arguments

:: OperatorContext c 
=> [(Predicate c, Record c a)]

Each when clauses

-> Record c a

Else result record

-> Record c a

Result record

Search case operator correnponding SQL search CASE. Like, CASE WHEN p0 THEN a WHEN p1 THEN b ... ELSE c END

casesOrElse Source #

Arguments

:: OperatorContext c 
=> [(Predicate c, Record c a)]

Each when clauses

-> Record c a

Else result record

-> Record c a

Result record

Same as caseSearch, but you can write like list casesOrElse clause.

caseSearchMaybe Source #

Arguments

:: (OperatorContext c, PersistableWidth a) 
=> [(Predicate c, Record c (Maybe a))]

Each when clauses

-> Record c (Maybe a)

Result record

Null default version of caseSearch.

case' Source #

Arguments

:: OperatorContext c 
=> Record c a

Record value to match

-> [(Record c a, Record c b)]

Each when clauses

-> Record c b

Else result record

-> Record c b

Result record

Simple case operator correnponding SQL simple CASE. Like, CASE x WHEN v THEN a WHEN w THEN b ... ELSE c END

casesOrElse' Source #

Arguments

:: OperatorContext c 
=> (Record c a, [(Record c a, Record c b)])

Record value to match and each when clauses list

-> Record c b

Else result record

-> Record c b

Result record

Uncurry version of case', and you can write like ... casesOrElse' clause.

caseMaybe Source #

Arguments

:: (OperatorContext c, PersistableWidth b) 
=> Record c a

Record value to match

-> [(Record c a, Record c (Maybe b))]

Each when clauses

-> Record c (Maybe b)

Result record

Null default version of case'.

in' :: OperatorContext c => Record c t -> RecordList (Record c) t -> Record c (Maybe Bool) infix 4 Source #

Binary operator corresponding SQL IN .

isNothing :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c (Maybe r) -> Predicate c Source #

Operator corresponding SQL IS NULL , and extended against record types.

isJust :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c (Maybe r) -> Predicate c Source #

Operator corresponding SQL NOT (... IS NULL) , and extended against record type.

fromMaybe :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c r -> Record c (Maybe r) -> Record c r Source #

Operator from maybe type using record extended isNull.

rank :: Integral a => Record OverWindow a Source #

RANK() term.

denseRank :: Integral a => Record OverWindow a Source #

DENSE_RANK() term.

rowNumber :: Integral a => Record OverWindow a Source #

ROW_NUMBER() term.

percentRank :: Record OverWindow Double Source #

PERCENT_RANK() term.

cumeDist :: Record OverWindow Double Source #

CUME_DIST() term.

unsafeAddPlaceHolders :: Functor f => f a -> f (PlaceHolders p, a) Source #

Unsafely add placeholder parameter to queries.

unsafePlaceHolders :: PlaceHolders p Source #

Unsafely get placeholder parameter

unitPlaceHolder :: PlaceHolders () Source #

No placeholder semantics

unitPH :: PlaceHolders () Source #

No placeholder semantics. Same as unitPlaceHolder

pwPlaceholder :: SqlContext c => PersistableRecordWidth a -> (Record c a -> b) -> (PlaceHolders a, b) Source #

Provide scoped placeholder from width and return its parameter object.

placeholder' :: (PersistableWidth t, SqlContext c) => (Record c t -> a) -> (PlaceHolders t, a) Source #

Provide scoped placeholder and return its parameter object.

projectZip :: ProductIsoApplicative p => p a -> p b -> p (a, b) Source #

Zipping projections.

(><) :: ProductIsoApplicative p => p a -> p b -> p (a, b) infixl 1 Source #

Binary operator the same as projectZip.

unsafeAggregateOp :: (AggregatedContext ac, SqlContext ac) => Keyword -> Record Flat a -> Record ac b Source #

Unsafely make aggregation uni-operator from SQL keyword.

count :: (Integral b, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac b Source #

Aggregation function COUNT.

sumMaybe :: (Num a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function SUM.

sum' :: (Num a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function SUM.

avgMaybe :: (Num a, Fractional b, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe b) Source #

Aggregation function AVG.

avg :: (Num a, Fractional b, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe b) Source #

Aggregation function AVG.

maxMaybe :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function MAX.

max' :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function MAX.

minMaybe :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function MIN.

min' :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function MIN.

every :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function EVERY.

any' :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function ANY.

some' :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function SOME.

(!) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c a

Source Record

-> Pi a b

Record path

-> Record c b

Narrower projected object

Get narrower record along with projection path.

(?!) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe type

-> Pi a b

Record path

-> Record c (Maybe b)

Narrower projected object. Maybe type result

Get narrower record along with projection path Maybe phantom functor is map-ed.

(?!?) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe phantom type

-> Pi a (Maybe b)

Record path. Maybe type leaf

-> Record c (Maybe b)

Narrower projected object. Maybe phantom type result

Get narrower record along with projection path and project into result record type. Source record Maybe phantom functor and projection path leaf Maybe functor are join-ed.

flattenPiMaybe Source #

Arguments

:: (PersistableWidth a, ProjectableFlattenMaybe (Maybe b) c) 
=> Record cont (Maybe a)

Source Record. Maybe phantom type

-> Pi a b

Projection path

-> Record cont c

Narrower Record. Flatten Maybe phantom type

Get narrower record with flatten leaf phantom Maybe types along with projection path.

(!??) infixl 8 Source #

Arguments

:: (PersistableWidth a, ProjectableFlattenMaybe (Maybe b) c) 
=> Record cont (Maybe a)

Source Record. Maybe phantom type

-> Pi a b

Projection path

-> Record cont c

Narrower flatten and projected object.

Get narrower record with flatten leaf phantom Maybe types along with projection path.

(?) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe type

-> Pi a b

Record path

-> Record c (Maybe b)

Narrower projected object. Maybe type result

Same as '(?!)'. Use this operator like '(? #foo) mayX'.

(??) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe phantom type

-> Pi a (Maybe b)

Record path. Maybe type leaf

-> Record c (Maybe b)

Narrower projected object. Maybe phantom type result

Same as '(?!?)'. Use this operator like '(?? #foo) mayX'.

class Monad m => MonadPartition c m Source #

Window specification building interface.

Minimal complete definition

partitionBy

Instances
MonadPartition c m => MonadPartition c (Orderings c m) Source #

MonadPartition with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

partitionBy :: Record c r -> Orderings c m () Source #

Monad m => MonadPartition c (PartitioningSetT c m) Source #

Partition clause instance

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

Methods

partitionBy :: Record c r -> PartitioningSetT c m () Source #

class (Functor q, Monad q, Functor m, Monad m) => MonadQualify q m Source #

Lift interface from base qualify monad.

Minimal complete definition

liftQualify

Instances
(Functor q, Monad q) => MonadQualify q q Source # 
Instance details

Defined in Database.Relational.Monad.Class

Methods

liftQualify :: q a -> q a Source #

MonadQualify ConfigureQuery QueryUnique Source # 
Instance details

Defined in Database.Relational.Monad.Unique

MonadQualify q m => MonadQualify q (QueryJoin m) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Join

Methods

liftQualify :: q a -> QueryJoin m a Source #

MonadQualify q m => MonadQualify q (AggregatingSetT m) Source #

Aggregated MonadQualify.

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

Methods

liftQualify :: q a -> AggregatingSetT m a Source #

MonadQualify q m => MonadQualify q (Restrictings c m) Source #

Restricted MonadQualify instance.

Instance details

Defined in Database.Relational.Monad.Trans.Restricting

Methods

liftQualify :: q a -> Restrictings c m a Source #

MonadQualify q m => MonadQualify q (Orderings c m) Source #

MonadQualify with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

liftQualify :: q a -> Orderings c m a Source #

MonadQualify q m => MonadQualify q (Assignings r m) Source #

MonadQualify with assigning.

Instance details

Defined in Database.Relational.Monad.Trans.Assigning

Methods

liftQualify :: q a -> Assignings r m a Source #

class (Functor m, Monad m, MonadQualify ConfigureQuery m) => MonadQuery m Source #

Query building interface.

Minimal complete definition

setDuplication, restrictJoin, query', queryMaybe'

Instances
MonadQuery QueryUnique Source # 
Instance details

Defined in Database.Relational.Monad.Unique

MonadQuery (QueryJoin ConfigureQuery) Source #

Joinable query instance.

Instance details

Defined in Database.Relational.Monad.Trans.Join

MonadQuery m => MonadQuery (AggregatingSetT m) Source #

Aggregated MonadQuery.

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

MonadQuery q => MonadQuery (Restrictings c q) Source #

Restricted MonadQuery instance.

Instance details

Defined in Database.Relational.Monad.Trans.Restricting

MonadQuery m => MonadQuery (Orderings c m) Source #

MonadQuery with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

class (Functor m, Monad m) => MonadRestrict c m where Source #

Restrict context interface

Minimal complete definition

restrict

Methods

restrict Source #

Arguments

:: Predicate c

Record which represent restriction

-> m ()

Restricted query context

Add restriction to this context.

type Restrict = Restrictings Flat ConfigureQuery Source #

Restrict only monad type used from update statement and delete statement.

type OrderedQuery c m p r = Orderings c m (PlaceHolders p, Record c r) Source #

OrderedQuery monad type with placeholder type p. Record must be the same as Orderings context type parameter c.

type QueryCore = Restrictings Flat (QueryJoin ConfigureQuery) Source #

Core query monad type used from flat(not-aggregated) query and aggregated query.

type SimpleQuery p r = OrderedQuery Flat QueryCore p r Source #

Simple (not-aggregated) query type. SimpleQuery' p r == QuerySimple (PlaceHolders p, Record r).

assignTo :: Monad m => Record Flat v -> AssignTarget r v -> Assignings r m () Source #

Add an assignment.

(<-#) :: Monad m => AssignTarget r v -> Record Flat v -> Assignings r m () infix 4 Source #

Add and assginment.

type Assign r = Assignings r Restrict Source #

Target update monad type used from update statement and merge statement.

data UniqueRelation p c r Source #

Unique relation type to compose scalar queries.

table :: Table r -> Relation () r Source #

Simple Relation from Table.

tableOf :: TableDerivable r => Relation () r -> Table r Source #

Interface to derive Table type object.

unsafeUnique :: Relation p r -> UniqueRelation p c r Source #

Unsafely specify unique relation.

unUnique :: UniqueRelation p c r -> Relation p r Source #

Discard unique attribute.

type JoinRestriction a b = Record Flat a -> Record Flat b -> Predicate Flat Source #

Restriction predicate function type for direct style join operator, used on predicates of direct join style as follows.

  do xy <- query $
           relX inner relY on' [ x y -> ... ] -- this lambda form has JoinRestriction type
     ...

inner' infixl 8 Source #

Arguments

:: Relation pa a

Left query to join

-> Relation pb b

Right query to join

-> [JoinRestriction a b]

Join restrictions

-> Relation (pa, pb) (a, b)

Result joined relation

Direct inner join with place-holder parameters.

left' infixl 8 Source #

Arguments

:: Relation pa a

Left query to join

-> Relation pb b

Right query to join

-> [JoinRestriction a (Maybe b)]

Join restrictions

-> Relation (pa, pb) (a, Maybe b)

Result joined relation

Direct left outer join with place-holder parameters.

right' infixl 8 Source #

Arguments

:: Relation pa a

Left query to join

-> Relation pb b

Right query to join

-> [JoinRestriction (Maybe a) b]

Join restrictions

-> Relation (pa, pb) (Maybe a, b)

Result joined relation

Direct right outer join with place-holder parameters.

full' infixl 8 Source #

Arguments

:: Relation pa a

Left query to join

-> Relation pb b

Right query to join

-> [JoinRestriction (Maybe a) (Maybe b)]

Join restrictions

-> Relation (pa, pb) (Maybe a, Maybe b)

Result joined relation

Direct full outer join with place-holder parameters.

inner infixl 8 Source #

Arguments

:: Relation () a

Left query to join

-> Relation () b

Right query to join

-> [JoinRestriction a b]

Join restrictions

-> Relation () (a, b)

Result joined relation

Direct inner join.

left infixl 8 Source #

Arguments

:: Relation () a

Left query to join

-> Relation () b

Right query to join

-> [JoinRestriction a (Maybe b)]

Join restrictions

-> Relation () (a, Maybe b)

Result joined relation

Direct left outer join.

right infixl 8 Source #

Arguments

:: Relation () a

Left query to join

-> Relation () b

Right query to join

-> [JoinRestriction (Maybe a) b]

Join restrictions

-> Relation () (Maybe a, b)

Result joined relation

Direct right outer join.

full infixl 8 Source #

Arguments

:: Relation () a

Left query to join

-> Relation () b

Right query to join

-> [JoinRestriction (Maybe a) (Maybe b)]

Join restrictions

-> Relation () (Maybe a, Maybe b)

Result joined relation

Direct full outer join.

on' :: ([JoinRestriction a b] -> Relation pc (a, b)) -> [JoinRestriction a b] -> Relation pc (a, b) infixl 8 Source #

Apply restriction for direct join style.

union :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Union of two relations.

unionAll :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Union of two relations. Not distinct.

except :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Subtraction of two relations.

exceptAll :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Subtraction of two relations. Not distinct.

intersect :: Relation () a -> Relation () a -> Relation () a infixl 8 Source #

Intersection of two relations.

intersectAll :: Relation () a -> Relation () a -> Relation () a infixl 8 Source #

Intersection of two relations. Not distinct.

union' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source #

Union of two relations with place-holder parameters.

unionAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source #

Union of two relations with place-holder parameters. Not distinct.

except' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source #

Subtraction of two relations with place-holder parameters.

exceptAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source #

Subtraction of two relations with place-holder parameters. Not distinct.

intersect' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 8 Source #

Intersection of two relations with place-holder parameters.

intersectAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 8 Source #

Intersection of two relations with place-holder parameters. Not distinct.

data InsertTarget p r Source #

InsertTarget type with place-holder parameter p and projected record type r.

data UpdateTarget p r Source #

UpdateTarget type with place-holder parameter p and projected record type r.

Instances
TableDerivable r => Show (UpdateTarget p r) Source # 
Instance details

Defined in Database.Relational.Effect

data Restriction p r Source #

Restriction type with place-holder parameter p and projected record type r.

Instances
TableDerivable r => Show (Restriction p r) Source #

Show where clause.

Instance details

Defined in Database.Relational.Effect

Methods

showsPrec :: Int -> Restriction p r -> ShowS #

show :: Restriction p r -> String #

showList :: [Restriction p r] -> ShowS #

restriction :: RestrictedStatement r () -> Restriction () r Source #

Finalize Restrict monad and generate Restriction.

restriction' :: RestrictedStatement r (PlaceHolders p) -> Restriction p r Source #

Finalize Restrict monad and generate Restriction with place-holder parameter p

sqlWhereFromRestriction :: Config -> Table r -> Restriction p r -> StringSQL Source #

SQL WHERE clause StringSQL string from Restriction.

updateTarget :: AssignStatement r () -> UpdateTarget () r Source #

Finalize Target monad and generate UpdateTarget.

updateTarget' :: AssignStatement r (PlaceHolders p) -> UpdateTarget p r Source #

Finalize Target monad and generate UpdateTarget with place-holder parameter p.

liftTargetAllColumn :: PersistableWidth r => Restriction () r -> UpdateTarget r r Source #

Lift Restriction to UpdateTarget. Update target columns are all.

liftTargetAllColumn' :: PersistableWidth r => Restriction p r -> UpdateTarget (r, p) r Source #

Lift Restriction to UpdateTarget. Update target columns are all. With placefolder type p.

updateTargetAllColumn :: PersistableWidth r => RestrictedStatement r () -> UpdateTarget r r Source #

Finalize Restrict monad and generate UpdateTarget. Update target columns are all.

updateTargetAllColumn' :: PersistableWidth r => RestrictedStatement r (PlaceHolders p) -> UpdateTarget (r, p) r Source #

Finalize Restrict monad and generate UpdateTarget. Update target columns are all. With placefolder type p.

sqlFromUpdateTarget :: Config -> Table r -> UpdateTarget p r -> StringSQL Source #

SQL SET clause and WHERE clause StringSQL string from UpdateTarget

insertTarget :: Register r () -> InsertTarget () r Source #

Finalize Register monad and generate InsertTarget.

insertTarget' :: Register r (PlaceHolders p) -> InsertTarget p r Source #

Finalize Target monad and generate UpdateTarget with place-holder parameter p.

piRegister :: PersistableWidth r => Pi r r' -> Register r (PlaceHolders r') Source #

parametalized Register monad from Pi

sqlChunkFromInsertTarget :: Config -> Table r -> InsertTarget p r -> (StringSQL, Int) Source #

Make StringSQL string of SQL INSERT record chunk statement from InsertTarget

sqlFromInsertTarget :: Config -> Table r -> InsertTarget p r -> StringSQL Source #

Make StringSQL string of SQL INSERT statement from InsertTarget

sqlChunksFromRecordList :: LiteralSQL r' => Config -> Table r -> Pi r r' -> [r'] -> [StringSQL] Source #

Make StringSQL strings of SQL INSERT strings from records list

class UntypeableNoFetch s where Source #

Untype interface for typed no-result type statments with single type parameter which represents place-holder parameter p.

Minimal complete definition

untypeNoFetch

Methods

untypeNoFetch :: s p -> String Source #

newtype Delete p Source #

Delete type with place-holder parameter p.

Constructors

Delete 

Fields

Instances
UntypeableNoFetch Delete Source # 
Instance details

Defined in Database.Relational.Type

Show (Delete p) Source #

Show delete SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Delete p -> ShowS #

show :: Delete p -> String #

showList :: [Delete p] -> ShowS #

newtype InsertQuery p Source #

InsertQuery type.

Constructors

InsertQuery 
Instances
UntypeableNoFetch InsertQuery Source # 
Instance details

Defined in Database.Relational.Type

Show (InsertQuery p) Source #

Show insert SQL string.

Instance details

Defined in Database.Relational.Type

data Insert a Source #

Insert type to insert record type a.

Constructors

Insert 
Instances
UntypeableNoFetch Insert Source # 
Instance details

Defined in Database.Relational.Type

Show (Insert a) Source #

Show insert SQL string.

Instance details

Defined in Database.Relational.Type

Methods

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

show :: Insert a -> String #

showList :: [Insert a] -> ShowS #

newtype Update p Source #

Update type with place-holder parameter p.

Constructors

Update 

Fields

Instances
UntypeableNoFetch Update Source # 
Instance details

Defined in Database.Relational.Type

Show (Update p) Source #

Show update SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Update p -> ShowS #

show :: Update p -> String #

showList :: [Update p] -> ShowS #

data KeyUpdate p a Source #

Update type with key type p and update record type a. Columns to update are record columns other than key columns, So place-holder parameter type is the same as record type a.

Constructors

KeyUpdate 

Fields

Instances
Show (KeyUpdate p a) Source #

Show update SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> KeyUpdate p a -> ShowS #

show :: KeyUpdate p a -> String #

showList :: [KeyUpdate p a] -> ShowS #

newtype Query p a Source #

Query type with place-holder parameter p and query result type a.

Constructors

Query 

Fields

Instances
Show (Query p a) Source #

Show query SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Query p a -> ShowS #

show :: Query p a -> String #

showList :: [Query p a] -> ShowS #

unsafeTypedQuery Source #

Arguments

:: String

Query SQL to type

-> Query p a

Typed result

Unsafely make typed Query from SQL string.

relationalQuerySQL :: Config -> Relation p r -> QuerySuffix -> String Source #

From Relation into untyped SQL query string.

relationalQuery' :: Relation p r -> QuerySuffix -> Query p r Source #

From Relation into typed Query with suffix SQL words.

relationalQuery :: Relation p r -> Query p r Source #

From Relation into typed Query.

typedKeyUpdate :: Table a -> Pi a p -> KeyUpdate p a Source #

Make typed KeyUpdate from Table and key columns selector Pi.

typedKeyUpdateTable :: TableDerivable r => Relation () r -> Pi r p -> KeyUpdate p r Source #

Make typed KeyUpdate object using derived info specified by Relation type.

keyUpdate :: TableDerivable r => Pi r p -> KeyUpdate p r Source #

Make typed KeyUpdate from derived table and key columns selector Pi.

derivedKeyUpdate :: TableDerivable r => Pi r p -> KeyUpdate p r Source #

Deprecated: use keyUpdate instead of this.

Make typed KeyUpdate from derived table and key columns selector Pi.

unsafeTypedUpdate :: String -> Update p Source #

Unsafely make typed Update from SQL string.

updateSQL :: Config -> Table r -> UpdateTarget p r -> String Source #

Make untyped update SQL string from Table and UpdateTarget.

typedUpdate :: Table r -> UpdateTarget p r -> Update p Source #

Deprecated: use typedUpdate defaultConfig` instead of this.

Make typed Update using defaultConfig, Table and UpdateTarget.

typedUpdateAllColumn :: PersistableWidth r => Table r -> Restriction p r -> Update (r, p) Source #

Make typed Update from Table and Restriction. Update target is all column.

derivedUpdateAllColumn' :: (PersistableWidth r, TableDerivable r) => Config -> RestrictedStatement r (PlaceHolders p) -> Update (r, p) Source #

Deprecated: use updateAllColumn' instead of this.

Make typed Update from Config, derived table and AssignStatement. Update target is all column.

derivedUpdateAllColumn :: (PersistableWidth r, TableDerivable r) => RestrictedStatement r (PlaceHolders p) -> Update (r, p) Source #

Deprecated: use updateAllColumn instead of this.

Make typed Update from defaultConfig, derived table and AssignStatement. Update target is all column.

untypeChunkInsert :: Insert a -> String Source #

Statement to use chunked insert

chunkSizeOfInsert :: Insert a -> Int Source #

Size to use chunked insert

unsafeTypedInsert' :: String -> String -> Int -> Insert a Source #

Unsafely make typed Insert from single insert and chunked insert SQL.

typedInsert' :: PersistableWidth r => Config -> Table r -> Pi r r' -> Insert r' Source #

Make typed Insert from Table and columns selector Pi with configuration parameter.

typedInsert :: PersistableWidth r => Table r -> Pi r r' -> Insert r' Source #

Deprecated: use typedInsert defaultConfig` instead of this.

Make typed Insert from Table and columns selector Pi.

insert :: (PersistableWidth r, TableDerivable r) => Pi r r' -> Insert r' Source #

Table type inferred Insert.

derivedInsert :: (PersistableWidth r, TableDerivable r) => Pi r r' -> Insert r' Source #

Deprecated: use insert instead of this.

Table type inferred Insert.

typedInsertValue' :: Config -> Table r -> InsertTarget p r -> Insert p Source #

Make typed Insert from Config, Table and monadic builded InsertTarget object.

typedInsertValue :: Table r -> InsertTarget p r -> Insert p Source #

Deprecated: use typedInsertValue defaultConfig` instead of this.

Make typed Insert from Table and monadic builded InsertTarget object.

insertValueList' :: (TableDerivable r, LiteralSQL r') => Config -> Pi r r' -> [r'] -> [Insert ()] Source #

Make typed Insert list from Config and records list.

insertValueList :: (TableDerivable r, LiteralSQL r') => Pi r r' -> [r'] -> [Insert ()] Source #

Make typed Insert list from records list.

insertQuerySQL :: Config -> Table r -> Pi r r' -> Relation p r' -> String Source #

Make untyped insert select SQL string from Table, Pi and Relation.

typedInsertQuery' :: Config -> Table r -> Pi r r' -> Relation p r' -> InsertQuery p Source #

Make typed InsertQuery from columns selector Table, Pi and Relation with configuration parameter.

typedInsertQuery :: Table r -> Pi r r' -> Relation p r' -> InsertQuery p Source #

Deprecated: use typedInsertQuery defaultConfig` instead of this.

Make typed InsertQuery from columns selector Table, Pi and Relation.

insertQuery :: TableDerivable r => Pi r r' -> Relation p r' -> InsertQuery p Source #

Table type inferred InsertQuery.

derivedInsertQuery :: TableDerivable r => Pi r r' -> Relation p r' -> InsertQuery p Source #

Deprecated: use insertQuery instead of this.

Table type inferred InsertQuery.

deleteSQL :: Config -> Table r -> Restriction p r -> String Source #

Make untyped delete SQL string from Table and Restriction.

typedDelete' :: Config -> Table r -> Restriction p r -> Delete p Source #

Make typed Delete from Config, Table and Restriction.

typedDelete :: Table r -> Restriction p r -> Delete p Source #

Deprecated: use typedDelete defaultConfig` instead of this.

Make typed Delete from Table and Restriction.

data Number r i Source #

Sequence number type for record type r

Instances
Eq i => Eq (Number r i) Source # 
Instance details

Defined in Database.Relational.Sequence

Methods

(==) :: Number r i -> Number r i -> Bool #

(/=) :: Number r i -> Number r i -> Bool #

Ord i => Ord (Number r i) Source # 
Instance details

Defined in Database.Relational.Sequence

Methods

compare :: Number r i -> Number r i -> Ordering #

(<) :: Number r i -> Number r i -> Bool #

(<=) :: Number r i -> Number r i -> Bool #

(>) :: Number r i -> Number r i -> Bool #

(>=) :: Number r i -> Number r i -> Bool #

max :: Number r i -> Number r i -> Number r i #

min :: Number r i -> Number r i -> Number r i #

Show i => Show (Number r i) Source # 
Instance details

Defined in Database.Relational.Sequence

Methods

showsPrec :: Int -> Number r i -> ShowS #

show :: Number r i -> String #

showList :: [Number r i] -> ShowS #

class (TableDerivable r, SequenceDerivable s i) => Binding r s i | r -> s where Source #

Derivation rule for binding between Table and Sequence

data SeqBinding r s i Source #

Record to express binding between normal-table and sequence-table.

class TableDerivable s => SequenceDerivable s i | s -> i where Source #

Sequence derivation rule

Minimal complete definition

derivedSequence

data Sequence s i Source #

Basic record to express sequence-table. actual sequence-table is a table which has only one column of integer type.

unsafeSpecifySequence :: TableDerivable s => (s -> i) -> Pi s i -> Sequence s i Source #

Unsafely specify sequence table.

seqRelation :: TableDerivable s => Sequence s i -> Relation () s Source #

Infer Relation of sequence table

unsafeSpecifyBinding :: (TableDerivable r, SequenceDerivable s i) => Pi r i -> SeqBinding r s i Source #

Unsafely specify binding between normal-table and sequence-table.

primaryBinding :: (TableDerivable r, SequenceDerivable s i, HasConstraintKey Primary r i) => SeqBinding r s i Source #

Derive binding using primary key.

fromRelation :: Binding r s i => Relation () r -> Sequence s i Source #

Derive Sequence from corresponding Relation

unsafeSpecifyNumber :: Binding r s i => i -> Number r i Source #

Unsafely specify sequence number.

extractNumber :: Number r i -> i Source #

Get untyped sequence number.

($$!) Source #

Arguments

:: (i -> r)

sequence number should be passed to proper field of record

-> Number r i 
-> r 

Unsafely apply sequence number.

($$) Source #

Arguments

:: Binding r s i 
=> (i -> r)

sequence number should be passed to proper field of record

-> Number r i 
-> r 

Unsafely apply sequence number. Only safe to build corresponding record type.

updateNumber' Source #

Arguments

:: (PersistableWidth s, Integral i, LiteralSQL i) 
=> Config 
-> i

sequence number to set. expect not SQL injectable.

-> Sequence s i

sequence table

-> Update () 

Update statement for sequence table

updateNumber Source #

Arguments

:: (PersistableWidth s, Integral i, LiteralSQL i) 
=> i

sequence number to set. expect not SQL injectable.

-> Sequence s i

sequence table

-> Update () 

Update statement for sequence table

specifiedKey Source #

Arguments

:: PersistableWidth p 
=> Pi a p

Projection path

-> Relation () a

Relation to add restriction.

-> Relation p a

Result restricted Relation

Query restricted with specified key.

uniqueSelect Source #

Arguments

:: PersistableWidth p 
=> Key Unique a p

Unique key proof object which record type is a and key type is p.

-> Relation () a

Relation to add restriction.

-> Relation p a

Result restricted Relation

Query restricted with specified unique key.

unique :: PersistableWidth p => Key Unique a p -> Relation () a -> Relation p a Source #

Deprecated: use uniqueSelect instead of this.

Deprecated.

primary' Source #

Arguments

:: PersistableWidth p 
=> Key Primary a p

Primary key proof object which record type is a and key type is p.

-> Relation () a

Relation to add restriction.

-> Relation p a

Result restricted Relation

Deprecated: use primarySelect instead of this.

Deprecated.

primarySelect Source #

Arguments

:: HasConstraintKey Primary a p 
=> Relation () a

Relation to add restriction.

-> Relation p a

Result restricted Relation

Query restricted with inferred primary key.

primary :: HasConstraintKey Primary a p => Relation () a -> Relation p a Source #

Deprecated: use primarySelect instead of this.

Deprecated.

updateValuesWithKey :: ToSql q r => Pi r p -> r -> [q] Source #

Convert from Haskell type r into SQL value q list expected by update form like

UPDATE table SET c0 = ?, c1 = ?, ..., cn = ? WHERE key0 = ? AND key1 = ? AND key2 = ? ...

using derived RecordToSql proof object.

updateByConstraintKey Source #

Arguments

:: Table r

Table to update

-> Key c r p

Key with constraint c, record type r and columns type p

-> KeyUpdate p r

Result typed Update

Typed KeyUpdate using specified constraint key.

primaryUpdate Source #

Arguments

:: HasConstraintKey Primary r p 
=> Table r

Table to update

-> KeyUpdate p r

Result typed Update

Typed KeyUpdate using inferred primary key.

derivedUniqueRelation Source #

Arguments

:: TableDerivable r 
=> Key Unique r k

Unique key proof object which record type is a and key type is p.

-> Record c k

Unique key value to specify.

-> UniqueRelation () c r

Result restricted Relation

UniqueRelation inferred from table.

all' :: MonadQuery m => QueryA m () () Source #

Same as all'. Arrow version.

distinct :: MonadQuery m => QueryA m () () Source #

Same as distinct. Arrow version.

query :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Record Flat r) Source #

Same as query. Arrow version. The result arrow is not injected by local projected records.

queryMaybe :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Record Flat (Maybe r)) Source #

Same as queryMaybe. Arrow version. The result arrow is not injected by any local projected records.

query' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Record Flat r) Source #

Same as query'. Arrow version. The result arrow is not injected by any local projected records.

queryMaybe' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Record Flat (Maybe r)) Source #

Same as queryMaybe'. Arrow version. The result arrow is not injected by any local projected records.

queryList :: MonadQualify ConfigureQuery m => (Record c a -> Relation () r) -> QueryA m (Record c a) (RecordList (Record c) r) Source #

Same as queryList. Arrow version. The result arrow is designed to be injected by local projected records.

queryList' :: MonadQualify ConfigureQuery m => (Record c a -> Relation p r) -> QueryA m (Record c a) (PlaceHolders p, RecordList (Record c) r) Source #

Same as queryList'. Arrow version. The result arrow is designed to be injected by local projected records.

queryExists :: MonadQualify ConfigureQuery m => (Record c a -> Relation () r) -> QueryA m (Record c a) (RecordList (Record Exists) r) Source #

Same as queryList to pass this result to exists operator. Arrow version. The result arrow is designed to be injected by local projected records.

queryExists' :: MonadQualify ConfigureQuery m => (Record c a -> Relation p r) -> QueryA m (Record c a) (PlaceHolders p, RecordList (Record Exists) r) Source #

Same as queryList' to pass this result to exists operator. Arrow version. The result arrow is designed to be injected by local projected records.

queryListU :: MonadQualify ConfigureQuery m => Relation () r -> QueryA m () (RecordList (Record c) r) Source #

Same as queryList. Arrow version. Useful for no reference cases to local projected records.

queryListU' :: MonadQualify ConfigureQuery m => Relation p r -> QueryA m () (PlaceHolders p, RecordList (Record c) r) Source #

Same as queryList'. Arrow version. Useful for no reference cases to local projected records.

queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Record c a -> UniqueRelation () c r) -> QueryA m (Record c a) (Record c (Maybe r)) Source #

Same as queryScalar. Arrow version. The result arrow is designed to be injected by any local projected record.

queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Record c a -> UniqueRelation p c r) -> QueryA m (Record c a) (PlaceHolders p, Record c (Maybe r)) Source #

Same as queryScalar'. Arrow version. The result arrow is designed to be injected by any local projected record.

queryScalarU :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> QueryA m () (Record c (Maybe r)) Source #

Same as queryScalar. Arrow version. Useful for no reference cases to local projected records.

queryScalarU' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> QueryA m () (PlaceHolders p, Record c (Maybe r)) Source #

Same as queryScalar'. Arrow version. Useful for no reference cases to local projected records.

uniqueQuery' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Record c r) Source #

Same as uniqueQuery'. Arrow version. The result arrow is not injected by local projected records.

uniqueQueryMaybe' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Record c (Maybe r)) Source #

Same as uniqueQueryMaybe'. Arrow version. The result arrow is not injected by local projected records.

on :: MonadQuery m => QueryA m (Predicate Flat) () Source #

Same as on. Arrow version. The result arrow is designed to be injected by local conditional flat-records.

wheres :: MonadRestrict Flat m => QueryA m (Predicate Flat) () Source #

Same as wheres. Arrow version. The result arrow is designed to be injected by local conditional flat-records.

having :: MonadRestrict Aggregated m => QueryA m (Predicate Aggregated) () Source #

Same as having. Arrow version. The result arrow is designed to be injected by local conditional aggregated-records.

groupBy :: MonadAggregate m => QueryA m (Record Flat r) (Record Aggregated r) Source #

Same as groupBy. Arrow version. The result arrow is designed to be injected by local flat-records.

placeholder :: (PersistableWidth t, SqlContext c, Monad m) => QueryA m (QueryA m (Record c t) a) (PlaceHolders t, a) Source #

Same as placeholder. Arrow version. The result arrow is designed to be injected by locally built arrow using placeholders.

relation :: QuerySimple () (Record Flat r) -> Relation () r Source #

Same as relation. Finalize query-building arrow instead of query-building monad.

relation' :: QuerySimple () (PlaceHolders p, Record Flat r) -> Relation p r Source #

Same as relation'. Finalize query-building arrow instead of query-building monad.

aggregateRelation :: QueryAggregate () (Record Aggregated r) -> Relation () r Source #

Same as aggregateRelation. Finalize query-building arrow instead of query-building monad.

aggregateRelation' :: QueryAggregate () (PlaceHolders p, Record Aggregated r) -> Relation p r Source #

Same as aggregateRelation'. Finalize query-building arrow instead of query-building monad.

uniqueRelation' :: QueryUnique () (PlaceHolders p, Record c r) -> UniqueRelation p c r Source #

Same as uniqueRelation'. Finalize query-building arrow instead of query-building monad.

groupBy' :: MonadAggregate m => QueryA m (AggregateKey (Record Aggregated r)) (Record Aggregated r) Source #

Same as groupBy'. This arrow is designed to be injected by local AggregateKey.

key :: AggregatingSet (Record Flat r) (Record Aggregated (Maybe r)) Source #

Same as key. This arrow is designed to be injected by local flat-records.

key' :: AggregatingSet (AggregateKey a) a Source #

Same as key'. This arrow is designed to be injected by local AggregteKey.

set :: AggregatingSetList (AggregatingSet () a) a Source #

Same as set. This arrow is designed to be injected by locally built AggregtingSet arrow.

bkey :: AggregatingPowerSet (Record Flat r) (Record Aggregated (Maybe r)) Source #

Same as bkey. This arrow is designed to be injected by local flat-records.

rollup :: AggregatingPowerSet () a -> AggregateKey a Source #

Same as rollup. Finalize locally built AggregatingPowerSet.

cube :: AggregatingPowerSet () a -> AggregateKey a Source #

Same as cube. Finalize locally built AggregatingPowerSet.

orderBy' :: Monad m => Order -> Nulls -> Orderings c m (Record c t) () Source #

Same as orderBy'. The result arrow is designed to be injected by local projected records.

orderBy :: Monad m => Order -> Orderings c m (Record c t) () Source #

Same as orderBy. The result arrow is designed to be injected by local projected records.

asc :: Monad m => Orderings c m (Record c t) () Source #

Same as asc. The result arrow is designed to be injected by local projected records.

desc :: Monad m => Orderings c m (Record c t) () Source #

Same as desc. The result arrow is designed to be injected by local projected records.

partitionBy :: Window c (Record c r) () Source #

Same as partitionBy. The result arrow is designed to be injected by local projected records.

over :: SqlContext c => Record OverWindow a -> Window c () () -> Record c a infix 8 Source #

Same as over. Make record of window function result using built Window arrow.

assign :: Monad m => AssignTarget r v -> Assignings r m (Record Flat v) () Source #

Make AssignTarget into arrow which is designed to be injected by assignees of local projected record.

update' :: TableDerivable r => Config -> AssignStatement r (PlaceHolders p) -> Update p Source #

Same as update'. Make Update from assigning statement arrow using configuration.

update :: TableDerivable r => AssignStatement r (PlaceHolders p) -> Update p Source #

Same as update. Make Update from assigning statement arrow.

updateNoPH :: TableDerivable r => AssignStatement r () -> Update () Source #

Same as updateNoPH. Make Update from assigning statement arrow.

updateAllColumn' :: (PersistableWidth r, TableDerivable r) => Config -> RestrictedStatement r (PlaceHolders p) -> Update (r, p) Source #

Same as updateAllColumn'. Make Update from restrected statement arrow.

updateAllColumn :: (PersistableWidth r, TableDerivable r) => RestrictedStatement r (PlaceHolders p) -> Update (r, p) Source #

Same as updateAllColumn. Make Update from restrected statement arrow.

updateAllColumnNoPH :: (PersistableWidth r, TableDerivable r) => RestrictedStatement r () -> Update r Source #

Same as updateAllColumnNoPH. Make Update from restrected statement arrow.

insertValue' :: TableDerivable r => Config -> Register r (PlaceHolders p) -> Insert p Source #

Same as insertValue'. Make Insert from register arrow using configuration.

insertValue :: TableDerivable r => Register r (PlaceHolders p) -> Insert p Source #

Same as insertValue. Make Insert from register arrow.

insertValueNoPH :: TableDerivable r => Register r () -> Insert () Source #

Same as insertValueNoPH. Make Insert from register arrow.

delete' :: TableDerivable r => Config -> RestrictedStatement r (PlaceHolders p) -> Delete p Source #

Same as delete'. Make Update from restrict statement arrow using configuration.

delete :: TableDerivable r => RestrictedStatement r (PlaceHolders p) -> Delete p Source #

Same as delete. Make Update from restrict statement arrow.

deleteNoPH :: TableDerivable r => RestrictedStatement r () -> Delete () Source #

Same as deleteNoPH. Make Update from restrict statement arrow.

data QueryA m a b Source #

Arrow to build queries.

Instances
Monad m => Arrow (QueryA m) Source # 
Instance details

Defined in Database.Relational.Arrow

Methods

arr :: (b -> c) -> QueryA m b c #

first :: QueryA m b c -> QueryA m (b, d) (c, d) #

second :: QueryA m b c -> QueryA m (d, b) (d, c) #

(***) :: QueryA m b c -> QueryA m b' c' -> QueryA m (b, b') (c, c') #

(&&&) :: QueryA m b c -> QueryA m b c' -> QueryA m b (c, c') #

Monad m => Category (QueryA m :: * -> * -> *) Source # 
Instance details

Defined in Database.Relational.Arrow

Methods

id :: QueryA m a a #

(.) :: QueryA m b c -> QueryA m a b -> QueryA m a c #

type QuerySimple = QueryA QuerySimple Source #

Arrow type corresponding to QuerySimple

type QueryAggregate = QueryA QueryAggregate Source #

Arrow type corresponding to QueryAggregate

type QueryUnique = QueryA QueryUnique Source #

Arrow type corresponding to QueryUnique

type AggregatingSet = QueryA AggregatingSet Source #

Arrow type corresponding to AggregatingSet

type Orderings c m = QueryA (Orderings c m) Source #

Arrow type corresponding to Orderings

type Window c = QueryA (Window c) Source #

Arrow type corresponding to Window

type Assignings r m = QueryA (Assignings r m) Source #

Arrow type corresponding to Assignings

type AssignStatement r a = Assignings r Restrict (Record Flat r) a Source #

Arrow type corresponding to AssignStatement

type Register r a = QueryA (Register r) () a Source #

Arrow type corresponding to Register

type RestrictedStatement r a = QueryA Restrict (Record Flat r) a Source #

Arrow type corresponding to RestrictedStatement

Deprecated

derivedUpdate' :: TableDerivable r => Config -> AssignStatement r (PlaceHolders p) -> Update p Source #

Deprecated: use update' instead of this.

Same as update'. Make Update from assigning statement arrow using configuration.

derivedUpdate :: TableDerivable r => AssignStatement r (PlaceHolders p) -> Update p Source #

Deprecated: use update instead of this.

Deprecated.

derivedInsertValue' :: TableDerivable r => Config -> Register r (PlaceHolders p) -> Insert p Source #

Deprecated: use insertValue' instead of this.

Deprecated.

derivedInsertValue :: TableDerivable r => Register r (PlaceHolders p) -> Insert p Source #

Deprecated: use insertValue instead of this.

Deprecated.

derivedDelete' :: TableDerivable r => Config -> RestrictedStatement r (PlaceHolders p) -> Delete p Source #

Deprecated: use derivedDelete' instead of this.

Deprecated.

derivedDelete :: TableDerivable r => RestrictedStatement r (PlaceHolders p) -> Delete p Source #

Deprecated: use derivedDelete instead of this.

Deprecated.