h,      !"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~                                        1.7.0.0  Safe-Inferred)*1'rel8 is a kind that parameterises aggregations. Aggregations parameterised by  are analogous to  5 (i.e, they can only produce results on a non-empty )) whereas aggregations parameterised by  are analagous to  (given a non-empty) query, they return the identity values of the aggregation functions. Safe-Inferred01b Safe-Inferred1rel8Map a  Type -> Type function over the Type1-kinded type variables in of a type constructor.None01P Safe-Inferred)*1Nonerel8An ordering expression for a(. Primitive orderings are defined with  and , and you can combine Order via its various instances.A common pattern is to use 1 to combine multiple orderings in sequence, and  to select individual columns.None Safe-Inferred)*/0L Safe-Inferredz Safe-Inferred Safe-Inferred1 Safe-Inferred)*/1rel8The Sql type class describes both null and not null database values, constrained by a specific class.For example, if you see  Sql DBEq a<, this means any database type that supports equality, and a can either be exactly an a, or it could also be Maybe a.rel8 Nullable a means that rel8 is able to check if the type a is a type that can take null values or not.rel8Homonullable a b means that both a and b can be null, or neither a or b can be null.rel8 nullify a means a cannot take null as a value.  Safe-Inferred%&rel8A name of an object (such as a table, view, function or sequence) qualified by an optional schema. In the absence of an explicit schema, the connection's  search_path will be used implicitly. rel8+The schema that this object belongs to. If #, whatever is on the connection's  search_path will be used. rel8The name of the object.rel8 Constructs s with   set to .  Safe-Inferred%'9 rel8The schema for a table. This is used to specify the name and schema that a table belongs to (the FROM part of a SQL query), along with the schema of the columns within this table.For each selectable table in your database, you should provide a  TableSchema. in order to interact with the table via Rel8.rel84The columns of the table. Typically you would use a  ' data type here, parameterized by the ! context.rel8The name of the table. " Safe-Inferred" # Safe-Inferred5$ Safe-Inferred"(j% Safe-Inferred/01&None%'9rel81How to deserialize from PostgreSQL's text format.rel83How to deserialize from PostgreSQL's binary format.rel8Apply a parser to .This can be used if the data stored in the database should only be subset of a given :. The parser is applied when deserializing rows returned.NoneD'None%&'0rel8:How to encode a single Haskell value as an SQL expression.rel8-How to serialize to PostgreSQL's text format.rel8/How to serialize to PostgreSQL's binary format.NoneT( Safe-Inferred%&rel8 A PostgreSQL type consists of a  (name, schema), and optional  and .  will usually be [], but a type like  numeric(6, 2) will have  ["6", "2"].  is always 0 for non-array types.rel83If this is an array type, the depth of that array (1 for [], 2 for [][], etc).rel8-Any modifiers applied to the underlying type.rel8"The name (and schema) of the type.rel8 Constructs s with schema set to ,  set to [] and  set to 0.)None')*#) rel8TypeInformation describes how to encode and decode a Haskell type to and from database queries. The typeName is the name of the type in the database, which is used to accurately type literals. "rel8The name of the SQL type.#rel8The delimiter that is used in PostgreSQL's text format in arrays of this type (this is almost always ',').$rel87How to deserialize a PostgreSQL result back to Haskell.%rel8/How to serialize a Haskell value to PostgreSQL.&rel8Simultaneously map over how a type is both encoded and decoded, while retaining the name of the type. This operation is useful if you want to essentially newtype another *.The mapping is required to be total. If you have a partial mapping, see '.'rel8Apply a parser to  .This can be used if the data stored in the database should only be subset of a given  . The parser is applied when deserializing rows returned - the encoder assumes that the input data is already in the appropriate form.&' !$#%"+ Safe-Inferred)*#^, Safe-Inferred#-None "%'()*# .None"#/ Safe-Inferred"$0None "%)(rel8Haskell types that can be represented as expressions in a database. There should be an instance of DBType6 for all column types in your database schema (e.g., int,  timestamptz, etc).Rel8 comes with stock instances for most default types in PostgreSQL, so you should only need to derive instances of this class for custom database types, such as types defined in PostgreSQL extensions, or custom domain types.rel8Corresponds to inetrel8Corresponds to jsonbrel8Corresponds to uuidrel8Corresponds to bytearel8Corresponds to bytearel8Corresponds to citextrel8Corresponds to citextrel8Corresponds to textrel8Corresponds to textrel8Corresponds to intervalrel8Corresponds to timerel8Corresponds to  timestamprel8Corresponds to daterel8Corresponds to  timestamptzrel8Corresponds to numeric(1000, logAA n)rel8Corresponds to numericrel8Corresponds to float8 and double precisionrel8Corresponds to float4 and realrel8Corresponds to int8rel8Corresponds to int4rel8Corresponds to int2rel8Corresponds to charrel8Corresponds to bool()1None"%*o*rel8A deriving-via helper type for column types that store a Haskell value using a JSON encoding described by aeson's  and  type classes.*+,2None"%*-rel8Like 3, but works for jsonb columns.-./4None+0rel8Database types that can be compared for equality in queries. If a type is an instance of 0, it means we can compare expressions for equality using the SQL = operator.05None-1rel8-The class of database types that support the min aggregation function.2rel8-The class of database types that support the max aggregation function.3rel8-The class of database types that support the <, <=, > and >= operators.2136None 1/ 4rel8-The class of database types that support the / operator.5rel8-The class of database types that support the / operator.6rel8The class of database types that can be coerced to from integral expressions. This is a Rel8 concept, and allows us to provide 7.7rel8-The class of database types that support the +, *, - operators, and the abs, negate, sign functions.45678None%1=38rel8Types that are sum types, where each constructor is unary (that is, has no fields).9rel8DBEnum: contains the necessary metadata to describe a PostgreSQL enum type.:rel87Map Haskell values to the corresponding element of the enum type. The default implementation of this method will use the exact name of the Haskell constructors.;rel8The name of the PostgreSQL enum type that a maps to.<rel8-List of all possible values of the enum type.=rel8A deriving-via helper type for column types that store an "enum" type (in Haskell terms, a sum type where all constructors are nullary) using a Postgres enum type.Note that this should map to a specific type in your database's schema (explicitly created with CREATE TYPE ... AS ENUM). Use 9 to specify the name of this Postgres type and the names of the individual values. If left unspecified, the names of the values of the Postgres enum are assumed to match exactly exactly the names of the constructors of the Haskell type (up to and including case sensitivity).9?:@9;:<=>8;None3<None ')*14Arel8The Result7 context is the context used for decoded query results.When a query is executed against a PostgreSQL database, Rel8 parses the returned rows, decoding each row into the Result context.A=None16#Brel8/This type family is used to specify columns in Rel8ables. In  Column f a, f is the context of the column (which should be left polymorphic in Rel8able definitions), and a is the type of the column.B>None 1=7rel8)A HField type for indexing into HProduct.Crel8A HTable is a functor-indexed/higher-kinded data type that is representable (/), constrainable (), and specified ().This is an internal concept for Rel8, and you should not need to define instances yourself or specify this constraint.?@ABCCDNone)*-/1383 ENone%&')*/1<>8rel8 Transform a  by allowing it to be null.FNone %&19GNone019X HNone-19 INone19JNone1==Drel8Tables are one of the foundational elements of Rel8, and describe data types that have a finite number of columns. Each of these columns contains data under a shared context, and contexts describe how to interpret the metadata about a column to a particular Haskell type. In Rel8, we have contexts for expressions (the K context), aggregations (the L context), insert values (the M contex), among others.?In typical usage of Rel8 you don't need to derive instances of D. yourself, as anything that's an instance of   is always a D.Erel8The C1 functor that describes the schema of this table.Frel8=The common context that all columns use as an interpretation.Grel8The  FromExprs type family maps a type in the Expr, context to the corresponding Haskell type.NNOOPMQPDEFGHJKILRNone 1?Qrel8Q from to a b means that a and b are D s, in the from and to contexts respectively, which share the same underlying structure. In other words, b is a version of a transposed from the from context to the to context (and vice versa).QSNone 1?OTNone%&')*/19<>? UNone1?VNone1@WNone 1@uRrel8.A special context used in the construction of Xs.RYNoneC5Srel8S p means that p is a kind of bifunctor on Z's that allows the mapping of a pair of W s over its underlying columns.Trel8Map a pair of Ws over p.Urel8U f means that f is a kind of functor on Z s that allows the mapping of a W over its underlying columns.Vrel8Map a W over f.Wrel8A W a b s is a special type of function a -> b whereby the resulting b> is guaranteed to be composed only from columns contained in a.Xrel8The constraint X a b ensures that W a b is a usable W.STUVXW[None 'F]rel89Cast an expression to a different type. Corresponds to a CAST() function call.^rel8Change the type of an \), without a cast. Even more unsafe than ],. Only use this if you are certain that the typeNames of a and b+ refer to exactly the same PostgreSQL type._rel8 Import a raw \] from opaleye, without a cast.This is an escape hatch, and can be used if Rel8 cannot adequately express the expression you need. If you find yourself using this function, please let us know, as it may indicate that something is missing from Rel8!`rel82Unsafely construct an expression from literal SQL.This is an escape hatch, and can be used if Rel8 cannot adequately express the expression you need. If you find yourself using this function, please let us know, as it may indicate that something is missing from Rel8!]^`_^None%'Garel8%Produce an expression from a literal.Note that you can usually use _, but litExpr6 can solve problems of inference in polymorphic code.a`None)*K hrel8The SQL false literal.irel8The SQL true literal.jrel8The SQL AND operator.krel8The SQL OR operator.lrel8The SQL NOT operator.mrel8Fold AND" over a collection of expressions.nrel8Fold OR" over a collection of expressions.orel8&Eliminate a boolean-valued expression.Corresponds to ab.prel8A multi-way ifthen&else statement. The first argument to caseExpr is a list of alternatives. The first alternative that is of the form  (true, x) will be returned. If no such alternative is found, a fallback expression is returned.Corresponds to a CASE expression in SQL.qrel8 Convert a Expr (Maybe Bool) to a  Expr Bool by treating Nothing as False(. This can be useful when combined with c, which expects a Bool, and produces expressions that optimize better than general case analysis. jmopqhlnikjdkefNone1P[rrel8!Lift an expression that can't be null to a type that might be null. This is an identity operation in terms of any generated query, and just modifies the query's type.srel8Assume that a nullable column's value is non-null. If the column is actually null, this will lead to runtime errors when you try to decode the value into Haskell, so you should prefer to use g$ unless you know what you're doing.rel8Like , but to eliminate null.trel8Like hi , but for null.urel8Like hj , but for null.vrel8Lift an operation on non-null$ values to an operation on possibly null values. When given null,  mapNull f returns null. This is like  for .wrel8Lift a binary operation on non-null; expressions to an equivalent binary operator on possibly null4 expressions. If either of the final arguments are null,  liftOpNull returns null. This is like  for .xrel8Corresponds to SQL null. utwvxrskNone%&Syrel8This type class is basically D \, where each column of the D is an argument to the function, but it also has an additional instance for ()) for calling functions with no arguments.zrel8z name arguments runs the PostgreSQL function name with the arguments  arguments returning an \ a.{rel8A less safe version of z0 that does not wrap the return value in a cast.|rel8Construct an expression by applying an infix binary operator to two operands.}rel8A less safe version of |0 that does not wrap the return value in a cast.|z}{ylNone1SDbcmNone(TYrel8A deriving-via helper type for column types that store a Haskell value using a Haskell's  and  type classes.YZ[nNone -1Tdrel8 The class of *s that form a semigroup. This class is purely a Rel8 concept, and exists to mirror the  Semigroup class.erel8An associative operation.deeopNone "1Ufrel8 The class of *s that form a semigroup. This class is purely a Rel8 concept, and exists to mirror the  class.fgqNone"1V\rel8Typed SQL expressions.\rNone'V9sNone'Xrel8 Serializable; witnesses the one-to-one correspondence between the type sql/, which contains SQL expressions, and the type haskell:, which contains the Haskell decoding of rows containing sql SQL expressions.rel8ToExprs exprs a is evidence that the types exprs and a* describe essentially the same type, but exprs is in the \ context, and a is a normal Haskell type.rel8Use lit2 to turn literal Haskell values into expressions. lit is capable of lifting single Exprs to full tables.tNone(Zrel8%An if-then-else expression on tables. bool x y p returns x if p is False, and returns y if p is True.rel8Produce a table expression from a list of alternatives. Returns the first table where the  Expr Bool expression is True>. If no alternatives are true, the given default is returned.rel8Like , but to eliminate null.uNone\~rel8Like  Alternative in Haskell, some D)s form a monoid on applicative functors.rel8The identity of .rel8Like Alt in Haskell. This class is purely a Rel8 concept, and allows you to take a choice between two tables. See also ~.For example, using  on v allows you to combine two tables and to return the first one that is a "just" MaybeTable.rel8#An associative binary operation on Ds.~dwNone)*1^rel8 Selects a b means that a is a schema (i.e., a D of  s) for the \ columns in b.rel8A Name is the name of a column, as it would be defined in a table's schema definition. You can construct names by using the OverloadedStrings extension and writing string literals. This is typically done when providing a  TableSchema value.xNone %'(-1_rel8Transform a table by adding CAST to all columns. This is most useful for finalising a SELECT or RETURNING statement, guaranteed that the output matches what is encoded in each columns TypeInformation.yNone'(1brel8Construct a table in the  context containing the names of all columns. Nested column names will be combined with /. See also: .rel8Construct a table in the  context containing the names of all columns. The supplied function can be used to transform column names.This function can be used to generically derive the columns for a  TableSchema. For example, myTableSchema :: TableSchema (MyTable Name) myTableSchema = TableSchema { columns = namesFromLabelsWith last } will construct a  TableSchema where each columns names exactly corresponds to the name of the Haskell field.zNoneb{None'b|None"%&')*h rel8The ON CONFLICT (...) DO UPDATE clause of an INSERT$ statement, also known as "upsert".When an existing row conflicts with a row proposed for insertion, ON CONFLICT DO UPDATE allows you to instead update this existing row. The conflicting row proposed for insertion is then "excluded", but its values can still be referenced from the SET and WHERE clauses of the UPDATE statement.Upsert in Postgres a "conflict target" to be specified @ this is the UNIQUE index from conflicts with which we would like to recover. Indexes are specified by listing the columns that comprise them along with an optional predicate in the case of partial indexes.rel8 Which rows to select for update.rel8 How to update each selected row.rel8)An optional predicate used to specify a  + operator. Note that this differs from SQL > as null3 will sort below any other value. For a version of > that exactly matches SQL, see .rel8Corresponds to the SQL >=+ operator. Note that this differs from SQL > as null3 will sort below any other value. For a version of >= that exactly matches SQL, see .rel8Corresponds to the SQL < operator. Returns null if either arguments are null.rel8Corresponds to the SQL <= operator. Returns null if either arguments are null.rel8Corresponds to the SQL > operator. Returns null if either arguments are null.rel8Corresponds to the SQL >= operator. Returns null if either arguments are null.rel8Given two expressions, return the expression that sorts less than the other.Corresponds to the SQL least() function.rel8Given two expressions, return the expression that sorts greater than the other.Corresponds to the SQL  greatest() function. NoneNoneNone()*4rel8&Compare two expressions for equality. This corresponds to the SQL IS NOT DISTINCT FROM operator, and will equate null values as true. This differs from = which would return null#. This operator matches Haskell's - operator. For an operator identical to SQL =, see .rel82Test if two expressions are different (not equal).This corresponds to the SQL IS DISTINCT FROM operator, and will return false when comparing two null$ values. This differs from ordinary <> which would return null'. This operator is closer to Haskell's - operator. For an operator identical to SQL <>, see .rel8Test if two expressions are equal. This operator is usually the best choice when forming join conditions, as PostgreSQL has a much harder time optimizing a join that has multiple  conditions.This corresponds to the SQL =+ operator, though it will always return a .rel8'Test if two expressions are different. This corresponds to the SQL <>+ operator, though it will always return a .rel8 Like the SQL IN8 operator, but implemented by folding over a list with  and k.None%(-1=rel8 The class of Ds that can be compared for equality. Equality on tables is defined by equality of all columns all columns, so this class means "all columns in a D have an instance of 0".rel8 Compare two Ds for equality. This corresponds to comparing all columns inside each table for equality, and combining all comparisons with AND.rel8 Test if two Ds are different. This corresponds to comparing all columns inside each table for inequality, and combining all comparisons with OR.None%(1=jrel8 The class of Tables that can be ordered. Ordering on tables is defined by their lexicographic ordering of all columns, so this class means "all columns in a Table have an instance of 3".rel8 Test if one Table sorts before another. Corresponds to comparing all columns with .rel8 Test if one Table sorts before, or is equal to, another. Corresponds to comparing all columns with .rel8 Test if one Table sorts after another. Corresponds to comparing all columns with .rel8 Test if one Table sorts after another. Corresponds to comparing all columns with .rel8 Given two Table0s, return the table that sorts before the other.rel8 Given two Table/s, return the table that sorts after the other.None '1 rel8 Construct an  for a Table by sorting all columns into ascending orders (any nullable columns will be sorted with  NULLS FIRST).rel8 Construct an  for a Table by sorting all columns into descending orders (any nullable columns will be sorted with  NULLS LAST).Nonerel8Combine the results of two queries of the same type, collapsing duplicates.  union a b" is the same as the SQL statement  a UNION b.rel8Combine the results of two queries of the same type, retaining duplicates.  unionAll a b" is the same as the SQL statement  a UNION ALL b.rel8>Find the intersection of two queries, collapsing duplicates. intersect a b" is the same as the SQL statement  a INTERSECT b.rel8=Find the intersection of two queries, retaining duplicates. intersectAll a b" is the same as the SQL statement a INTERSECT ALL b.rel8:Find the difference of two queries, collapsing duplicates  except a b# is the same as the SQL statement  a EXCEPT b.rel8;Find the difference of two queries, retaining duplicates.  exceptAll a b# is the same as the SQL statement a EXCEPT ALL b.Nonerel8The Query monad allows you to compose a SELECT7 query. This monad has semantics similar to the list ([]) monad.rel8 =  [].rel8 = .rel8 =  [].rel8 = .None)*12Nonerel8#Order the rows returned by a query.NoneUrel8 takes a  and fully evaluates it and caches the results thereof, and passes to a continuation a new  that simply looks up these cached results. It's usually best not to use this and to let the Postgres optimizer decide for itself what's best, but if you know what you're doing this can sometimes help to nudge it in a particular direction.1 is currently implemented in terms of Postgres'  9https://www.postgresql.org/docs/current/queries-with.html@WITH syntax, specifically the WITH _ AS MATERIALIZED (_)4 form introduced in PostgreSQL 12. This means that / can only be used with PostgreSQL 12 or newer.Nonerel8 allows the construction of recursive queries, using Postgres'  https://www.postgresql.org/docs/current/queries-with.html#QUERIES-WITH-RECURSIVEWITH RECURSIVE( under the hood. The first argument to  is what the Postgres documentation refers to as the "non-recursive term" and the second argument is the "recursive term", which is defined in terms of the result of the "non-recursive term".  uses  UNION ALL3 to combine the recursive and non-recursive terms.Denotionally,  s f is the smallest set of rows r such that r == s ` ` (r >>= f) Operationally,  s f" takes each row in an initial set s and supplies it to f, resulting in a new generation of rows which are added to the result set. Each row from this new generation is then fed back to f, and this process is repeated until a generation comes along for which f+ returns an empty set for each row therein.rel8 is like  but uses UNION instead of  UNION ALL3 to combine the recursive and non-recursive terms.Denotationally,  s f is the smallest set of rows r such that r == s `~ ` (r >>= f) Operationally,  s f takes each distinct row in an initial set s and supplies it to f?, resulting in a new generation of rows. Any rows returned by f that already exist in the result set are not considered part of this new generation by  (in contrast to ). This new generation is then added to the result set, and each row therein is then fed back to f, and this process is repeated until a generation comes along for which f= returns no rows that don't already exist in the result set.Nonerel8limit n select at most n rows from a query. limit n is equivalent to the SQL LIMIT n.rel8offset n drops the first n rows from a query. offset n is equivalent to the SQL OFFSET n.Nonerel8 takes a variable name, some expressions, and binds each of them to a new variable in the SQL. The a returned consists only of these variables. It's essentially a let" binding for Postgres expressions.Nonecrel8Select each row from a function that returns a relation. This is equivalent to FROM function(input).None)rel8 filter f x will be a zero-row query when f x is False, and will return x unchanged when f x is True. This is similar to , but as the predicate is separate from the argument, it is easy to use in a pipeline of  transformations.rel8-Drop any rows that don't match a predicate.  where_ expr is equivalent to the SQL  WHERE expr.Nonerel8 takes expressions that could potentially have side effects and "runs" them in the  monad. The returned expressions have no side effects and can safely be reused.Nonerel8?Select each row from a table definition. This is equivalent to  FROM table.None1Xrel8+Checks if a query returns at least one row.rel8 Query b yields no rows.rel8Like without$, but with a custom membership test.Nonerel8=Select all distinct rows from a query, removing duplicates.  distinct q% is equivalent to the SQL statement SELECT DISTINCT q.rel8Select all distinct rows from a query, where rows are equivalent according to a projection. If multiple rows have the same projection, it is unspecified which row will be returned. If this matters, use .rel8Select all distinct rows from a query, where rows are equivalent according to a projection. If there are multiple rows with the same projection, the first row according to the specified  will be returned.None"K rel8Cast 6 types to 7 types. For example, this can be useful if you need to turn an  Expr Int32 into an  Expr Double.rel8Cast 7 types to 54 types. For example, this can be useful to convert  Expr Float to  Expr Double.rel8Round a 5 to a 6, by rounding to the nearest larger integer.Corresponds to the  ceiling() function.rel8/Emulates the behaviour of the Haskell function  in PostgreSQL.rel8/Emulates the behaviour of the Haskell function  in PostgreSQL.rel8 Simultaneous  and .rel8.Perform integral division. Corresponds to the div()7 function in PostgreSQL, which behaves like Haskell's  rather than .rel8Corresponds to the mod()7 function in PostgreSQL, which behaves like Haskell's  rather than .rel8 Simultaneous  and .rel8Round a  DFractional to a 6. by rounding to the nearest smaller integer. Corresponds to the floor() function.rel8Round a 5 to a 6% by rounding to the nearest integer.Corresponds to the round() function.rel8Round a 5 to a 62 by rounding to the nearest integer towards zero.  Nonerel8Corresponds to the SQL DEFAULT expression.This \> is unsafe for numerous reasons, and should be used with care: This \ only makes sense in an INSERT or UPDATE statement.Rel8 is not able to verify that a particular column actually has a DEFAULT value. Trying to use  unsafeDefault6 where there is no default will cause a runtime crashDEFAULT values cannot be transformed. For example, the innocuous Rel8 code unsafeDefault + 1# will crash, despite type checking./Also note, PostgreSQL's syntax rules mean that DEFAULT can only appear in INSERT, expressions whose rows are specified using VALUES. This means that if the rows field of your M record doesn't look like  values [..], then  unsafeDefault won't work.Given all these caveats, we suggest avoiding the use of default values where possible, instead being explicit. A common scenario where default values are used is with auto-incrementing identifier columns. In this case, we suggest using  instead.None)*1ƣrel8An $ takes a collection of rows of type a, groups them, and transforms each group into a single row of type b). This corresponds to aggregators using GROUP BY0 in SQL. If given an empty collection of rows,  will have no groups and will therefore also return an empty collection of rows. is a special form of  parameterised by .rel8An  takes a ) producing a collection of rows of type a and transforms it into a ! producing a single row of type b. If the given  produces an empty collection of rows, then the single row in the resulting  contains the identity values of the aggregation functions comprising the  (i.e., 0 for ,  for , etc.). is a special form of  parameterised by .rel85 is the most general form of "aggregator", of which  and  are special cases. 1s are comprised of aggregation functions and/or GROUP BY clauses..Aggregation functions operating on individual K s such as  can be combined into 's operating on larger types using the ,  and  interfaces. Working with (s can sometimes be awkward so for every  we also provide a  which bundles an . For complex aggregations, we recommend using these functions along with  ApplicativeDo, BlockArguments, OverloadedRecordDot and RecordWildCards:  data Input f = Input { orderId :: Column f OrderId , customerId :: Column f CustomerId , productId :: Column f ProductId , quantity :: Column f Int64 , price :: Column f Scientific } deriving (Generic, Rel8able) totalPrice :: Input Expr -> Expr Scientific totalPrice input = fromIntegral input.quantity * input.price data Result f = Result { customerId :: Column f CustomerId , totalOrders :: Column f Int64 , productsOrdered :: Column f Int64 , totalPrice :: Column f Scientific } deriving (Generic, Rel8able) allResults :: Query (Result Expr) allResults = aggregate do customerId <- groupByOn (.customerId) totalOrders <- countDistinctOn (.orderId) productsOrdered <- countDistinctOn (.productId) totalPrice <- sumOn totalPrice pure Result {..} do order <- each orderSchema orderLine <- each orderLineSchema where_ $ order.id ==. orderLine.orderId pure Input { orderId = order.id , customerId = order.customerId , productId = orderLine.productId , quantity = orderLine.quantity , price = orderLine.price } rel8 turns an  into an .rel8Given a value to fall back on if given an empty collection of rows,  turns an  into an .None'1NoneǴrel8 allows the use use of custom aggregation functions or PostgreSQL aggregation functions which are not otherwise supported by Rel8.NoneDrel8)The class of data types that support the  string_agg() aggregation function.None 1rel8-The class of database types that support the sum() aggregation function.None "%'1פ+rel88Count the occurances of a single column. Corresponds to COUNT(a)rel8Applies . to the column selected by the given function.rel8Count the number of distinct occurrences of a single column. Corresponds to COUNT(DISTINCT a)rel8Applies . to the column selected by the given function.rel8Corresponds to COUNT(*).rel85A count of the number of times a given expression is true.rel8Applies . to the column selected by the given function.rel8Corresponds to bool_and.rel8Applies . to the column selected by the given function.rel8Corresponds to bool_or.rel8Applies . to the column selected by the given function.rel8Produce an aggregation for Expr a using the max function.rel8Applies . to the column selected by the given function.rel8Produce an aggregation for Expr a using the min function.rel8Applies . to the column selected by the given function.rel8Corresponds to sum. Note that in SQL, sum% is type changing - for example the sum of integer returns a bigint. Rel8 doesn't support this, and will add explicit casts back to the original input type. This can lead to overflows, and if you anticipate very large sums, you should upcast your input.rel8Applies . to the column selected by the given fucntion.rel8 is a combination of  and .rel8Corresponds to avg. Note that in SQL, avg& is type changing - for example, the avg of integer returns a numeric. Rel8 doesn't support this, and will add explicit casts back to the original input type. If you need a fractional result on an integral column, you should cast your input to  or  before calling .rel8Applies . to the column selected by the given fucntion.rel8Corresponds to  string_agg().rel8Applies . to the column selected by the given function.rel8Corresponds to  mode() WITHIN GROUP (ORDER BY _).rel8Applies . to the column selected by the given function.rel8Corresponds to ,percentile_disc(_) WITHIN GROUP (ORDER BY _).rel8Applies . to the column selected by the given function.rel8Corresponds to ,percentile_cont(_) WITHIN GROUP (ORDER BY _).rel8Applies / to the column selected by the given function.rel8Corresponds to !rank(_) WITHIN GROUP (ORDER BY _).rel8Corresponds to 'dense_rank(_) WITHIN GROUP (ORDER BY _).rel8Corresponds to )percent_rank(_) WITHIN GROUP (ORDER BY _).rel8Corresponds to &cume_dist(_) WITHIN GROUP (ORDER BY _).rel8$Aggregate a value by grouping by it.rel8Applies . to the column selected by the given function.rel8%Collect expressions values as a list.rel8Applies . to the column selected by the given function.rel8/Collect expressions values as a non-empty list.rel8Applies . to the column selected by the given function.rel8%Concatenate lists into a single list.rel8Applies . to the column selected by the given function.rel89Concatenate non-empty lists into a single non-empty list.rel8Applies . to the column selected by the given function.rel8 modifies an  to consider only distinct values of each particular column. Note that this "distinction" only happens within each column individually, not across all columns simultaneously.0None1>. None1<>gNone1<>ؚNone'19p rel8 MaybeTable t is the table t, but as the result of an outer join. If the outer join fails to match any rows, this is essentialy Nothing7, and if the outer join does match rows, this is like Just. Unfortunately, SQL makes it impossible to distinguish whether or not an outer join matched any rows based generally on the row contents - if you were to join a row entirely of nulls, you can't distinguish if you matched an all null row, or if the match failed. For this reason  MaybeTable contains an extra field - a "nullTag" - to track whether or not the outer join produced any rows.rel8 Check if a  MaybeTable is absent of any row. Like hi.rel8 Check if a  MaybeTable contains a row. Like hj.rel8Perform case analysis on a . Like .rel8The null table. Like .rel8Lift any table into . Like . Note you can also use .rel8h for s.rel8%Project a single expression out of a +. You can think of this operator like the 2 operator, but it also has the ability to return null.rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel8Has the same behavior as the Monad instance for Maybe.rel8Has the same behavior as the  Applicative instance for Maybe . See also: .rel83The name of the column to track whether a row is a  or .rel8Names of the columns in a.None1t rel8 NullTable t is the table t, but where all the columns in t have the possibility of being . This is very similar to v, except that it does not use an extra tag field, so it cannot distinguish between Nothing and  Just Nothing: if nested. In other words, if all of the columns of the t passed to  NullTable are already nullable, then  NullTable has no effect.rel8+Check if any of the non-nullable fields of a are  under the  . Returns  if a has no non-nullable fields.rel8The inverse of .rel8Like g.rel8The null table. Like .rel8Lift any table into . Like .rel8Assume that a  is non-null. Like .rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel8 Convert a  to a .rel8 Convert a  to a . Note that if the underlying a9 has no non-nullable fields, this is a lossy conversion. None'1Frel8A  NonEmptyTable) value contains one or more instances of a. You construct  NonEmptyTables with  or  nonEmptyAgg.rel8%Project a single expression out of a .rel8 Construct a  NonEmptyTable& from a non-empty list of expressions.rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel8Get the first element of a .rel8 i as extracts a single element from as , returning  if i is out of range. Note that although PostgreSQL array indexes are 1-based (by default), this function is always 0-based.rel8Get the last element of a .rel8Get the length of a rel81The names of the columns of elements of the list. None 1Grel8Nest a  list within a Rel8able.  HNonEmpty f a will produce a  a in the Expr context, and a  a in the A context.None'1rel8A  ListTable* value contains zero or more instances of a. You construct  ListTables with  or .rel8%Project a single expression out of a .rel8 Construct a  ListTable from a list of expressions.rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel8Get the first element of a  (or  if empty).rel8 i as extracts a single element from as , returning  if i is out of range. Note that although PostgreSQL array indexes are 1-based (by default), this function is always 0-based.rel8Get the last element of a  (or  if empty).rel8Get the length of a rel81The names of the columns of elements of the list. None '-I rel8Group equal tables together. This works by aggregating each column in the given table with  groupByExpr.For example, if we have a table of items, we could group the items by the order they belong to: itemsByOrder :: Query (OrderId Expr, ListTable Expr (Item Expr)) itemsByOrder = aggregate do orderId <- groupByOn (.orderId) items <- listAgg pure (orderId, items) do each itemSchema rel8Applies / to the columns selected by the given function.rel8 allows an  to filter out rows from the input query before considering them for aggregation. Note that because the predicate supplied to  could return  for every row,  needs an  as opposed to an , so that it can return a default value in such a case. For a variant of  that can work with s, see .rel8Aggregate rows into a single row containing an array of all aggregated rows. This can be used to associate multiple rows with a single row, without changing the over cardinality of the query. This allows you to essentially return a tree-like structure from queries.For example, if we have a table of orders and each orders contains multiple items, we could aggregate the table of orders, pairing each order with its items: ordersWithItems :: Query (Order Expr, ListTable Expr (Item Expr)) ordersWithItems = do order <- each orderSchema items <- aggregate listAgg (itemsFromOrder order) return (order, items) rel8Applies / to the columns selected by the given function.rel8Like 6, but the result is guaranteed to be a non-empty list.rel8Applies / to the columns selected by the given function.rel8%Concatenate lists into a single list.rel8Applies , to the list selected by the given function.rel89Concatenate non-empty lists into a single non-empty list.rel8Applies 7 to the non-empty list selected by the given function.rel8/Order the values within each aggregation in an  using the given ordering. This is only relevant for aggregations that depend on the order they get their elements, like  and . None 14rel8Nest a list within a Rel8able.  HList f a will produce a  a in the Expr context, and a [a] in the A context.None"rel8 a as tests whether a is an element of the list as.rel8 a as tests whether a& is an element of the non-empty list as.Nonerel8 Filter a  that might return null to a  without any nulls.Corresponds to h.rel8 Filter a  that might return  nullTable to a  without any  nullTables.Corresponds to h.None 1rel8Nest a Null value within a Rel8able.  HNull f a will produce a  a in the Expr context, and a  a in the A context.Nonexrel8 A variant of  that can be used with an  (upgrading it to an  in the process). It returns 3 in the case where the predicate matches zero rows.rel8 upgrades an  into an  by having it return 4 when aggregating over an empty collection of rows.rel8Lift an  to operate on a . If the input query has  i!s, they are folded into a single a by the given aggregator @ in the case where the input query is all s, the  's fallback a is returned.rel8Lift an  to operate on a . If the input query has  i!s, they are folded into a single  a by the given aggregator @ in the case where the input query is all  s, a single  row is returned.rel8#Lift an aggregator to operate on a .  nothingTables and  justTables are grouped separately.None'19rel8TheseTable a b0 is a Rel8 table that contains either the table a , the table b, or both tables a and b. You can construct  TheseTable s using ,  and .  TheseTable+s can be eliminated/pattern matched using . TheseTable( is operationally the same as Haskell's & type, but adapted to work with Rel8.rel8 Test if a  was constructed with .Corresponds to .rel8 Test if a  was constructed with .Corresponds to .rel8 Test if a  was constructed with .Corresponds to .rel8 Test if the a side of TheseTable a b is present.Corresponds to .rel8 Test if the b table of TheseTable a b is present.Corresponds to .rel8Attempt to project out the a table of a TheseTable a b.Corresponds to .rel8Attempt to project out the b table of a TheseTable a b.Corresponds to .rel8 Construct a  TheseTable from two s.rel8 Construct a  TheseTable. Corresponds to .rel8 Construct a  TheseTable. Corresponds to .rel8 Construct a  TheseTable. Corresponds to .rel8Pattern match on a . Corresponds to these.rel8Lift an  to operate on a . If the input query has  a!s, they are folded into a single c by the given aggregator @ in the case where the input query is all s or s, the  's fallback c is returned.rel8Lift an  to operate on a . If the input query has  a!s, they are folded into a single  c by the given aggregator @ in the case where the input query is all s or  s, a single  row is returned.rel8Lift an  to operate on a . If the input query has  b!s, they are folded into a single c by the given aggregator @ in the case where the input query is all s or s, the  's fallback c is returned.rel8Lift an  to operate on a . If the input query has  b!s, they are folded into a single  c by the given aggregator @ in the case where the input query is all s or  s, a single  row is returned.rel8Lift an  to operate on a  ThoseTable. If the input query has  a b!s, they are folded into a single c by the given aggregator @ in the case where the input query is all s or s, the  's fallback c is returned.rel8Lift an  to operate on a . If the input query has  a b!s, they are folded into a single  c by the given aggregator @ in the case where the input query is all s or  s, a single  row is returned.rel8Lift an  to operate on a . If the input query has  as or  a _s, the as are folded into a single c by the given aggregator @ in the case where the input query is all s, the  's fallback c is returned.rel8Lift an  to operate on an . If the input query has  as or  a _s, the as are folded into a single  c by the given aggregator @ in the case where the input query is all  s, a single  row is returned.rel8Lift an  to operate on a . If the input query has  bs or  _ bs, the bs are folded into a single c by the given aggregator @ in the case where the input query is all s, the  's fallback c is returned.rel8Lift an  to operate on an . If the input query has  bs or  _ bs, the bs are folded into a single  c by the given aggregator @ in the case where the input query is all  s, a single  row is returned.rel8(Lift a pair aggregators to operate on a . s, s are s are grouped separately.rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel84The name of the column to track the presence of the a table.rel84The name of the column to track the presence of the b table.rel8Names of the columns in the a table.rel8Names of the columns in the b table.None 1rel8Nest an  value within a Rel8able.  HThese f a b will produce a  a b in the Expr context, and a  a b in the A context.None')*rel8Convert a query that might return zero rows to a query that always returns at least one row.!To speak in more concrete terms,  is most useful to write  LEFT JOINs.rel8 Filter out /s, returning only the tables that are not-null.3This operation can be used to "undo" the effect of ), which operationally is like turning a  LEFT JOIN back into a full JOIN*. You can think of this as analogous to h.rel8Extend an optional query with another query. This is useful if you want to step through multiple  LEFT JOINs. Note that traverseMaybeTable takes a  a -> Query b function, which means you also have the ability to "expand" one row into multiple rows. If the  a -> Query b function returns no rows, then the resulting query will also have no rows. However, regardless of the given  a -> Query b function, if the input is  nothingTable", you will always get exactly one  nothingTable back.None(rel8 Apply an  to all rows returned by a  . If the  is empty, then a single "fallback" row is returned, composed of the identity elements of the constituent aggregation functions.rel8 Apply an  to all rows returned by a  . If the ' is empty, then zero rows are returned.rel8Count the number of rows returned by a query. Note that this is different from  countStar-, as even if the given query yields no rows,  countRows will return 0.None%&')*9 Jrel8 represents a single PostgreSQL statement. Most commonly, this is constructed using , ,  or .However, in addition to SELECT, INSERT, UPDATE and DELETE, PostgreSQL also supports compositions thereof via its statement-level WITH syntax (with some caveats). Each such "sub-statement" can reference the results of previous sub-statements.  provides a / instance that captures this "binding" pattern.!The caveat with this is that the  https://www.postgresql.org/docs/current/queries-with.html#QUERIES-WITH-MODIFYINGside-effects of these sub-statements are not visible to other sub-statements>; only the explicit results of previous sub-statements (from SELECTs or  RETURNING+ clauses) are visible. So, for example, an INSERT) into a table followed immediately by a SELECT therefrom will not return the inserted rows. However, it is possible to return the inserted rows using  RETURNING, ing this with the result of a SELECT6 from the same table will produce the desired result.An example of where this can be useful is if you want to delete rows from a table and simultaneously log their deletion in a log table. deleteFoo :: (Foo Expr -> Expr Bool) -> Statement () deleteFoo predicate = do foos <- delete Delete { from = fooSchema , using = pure () , deleteWhere = \_ -> predicate , returning = Returning id } insert Insert { into = deletedFooSchema , rows = do Foo {..} <- foos let deletedAt =  pure DeletedFoo {..} , onConflict = Abort , returning = NoReturning } None 19:; rel8Build a SELECT .None" None!Wrel8 Convert a  to a  containing a SELECT statement.None'*rel8 Convert a  to a runnable 7, disregarding the results of that statement (if any).  run_ :: Rel8. exprs -> Hasql. () () rel8 Convert a  to a runnable , returning the number of rows affected by that statement (for s, s or Rel8.delete's with ).  runN :: Rel8. () -> Hasql. ()  rel8 Convert a  to a runnable , processing the result of the statement as a single row. If the statement returns a number of rows other than 1, a runtime exception is thrown. run1 ::  exprs a => Rel8. ( exprs) -> Hasql. () a rel8 Convert a  to a runnable -, processing the result of the statement as  a single row. If the statement returns a number of rows other than 0 or 1, a runtime exception is thrown.  runMaybe ::  exprs a => Rel8. ( exprs) -> Hasql. () ( a) rel8 Convert a  to a runnable <, processing the result of the statement as a list of rows. run ::  exprs a => Rel8. ( exprs) -> Hasql. () [a] rel8 Convert a  to a runnable /, processing the result of the statement as a  of rows.  runVector ::  exprs a => Rel8. ( exprs) -> Hasql. () ( a) None ')*1(rel8M,  and  all support an optional  RETURNING clause.rel8No  RETURNING clauserel8 allows you to project out of the affected rows, which can be useful if you want to log exactly which rows were deleted, or to view a generated id (for example, if using a column with an autoincrementing counter via ).None %&')**rel8The constituent parts of an UPDATE statement.rel8What to return from the UPDATE statement.rel8 Which rows to select for update.rel8 How to update each selected row.rel8FROM clause @ this can be used to join against other tables, and its results can be referenced in the SET and WHERE clauses.rel8Which table to update.rel8 Build an UPDATE . None'-,rel8Given a  function that converts a  to a  , return a %-like function which instead takes a  parameterized  and converts it to a  preparable .The parameters i are sent to the database directly via PostgreSQL's binary format. For large amounts of data this can be significantly more efficient than embedding the values in the statement with _.None %&')*.rel8The constituent parts of a SQL INSERT statement.rel8)What information to return on completion.rel8What to do if the inserted rows conflict with data already in the table.rel8:The rows to insert. This can be an arbitrary query @ use  insert a static list of rows.rel8Which table to insert into.rel8 Build an INSERT . None0rel8Given a   and ,  createView runs a  CREATE VIEW statement that will save the given query as a view. This can be useful if you want to share Rel8 queries with other applications.rel8Given a   and , createOrReplaceView runs a CREATE OR REPLACE VIEW statement that will save the given query as a view, replacing the current view definition if it exists and adheres to the restrictions in place for replacing a view in PostgreSQL.None %&')*2rel8The constituent parts of a DELETE statement.rel8What to return from the DELETE statement.rel8+Which rows should be selected for deletion.rel8USING clause @ this can be used to join against other tables, and its results can be referenced in the WHERE clauserel8Which table to delete from.rel8Build a DELETE .None4Wrel8 Convert a  to a  containing a DELETE statement.rel8 Convert an  to a  containing an INSERT statement.rel8 Convert an  to a  containing an UPDATE statement.rel8 Convert a  to a  containing an SQL statement.rel8Convert a parameterized  to a  containing an SQL statement.None')*;rel8 Aggregate a  into a . If the supplied query returns 0 rows, this function will produce a , that returns one row containing the empty  ListTable. If the supplied Query does return rows, many& will return exactly one row, with a  ListTable collecting all returned rows.many is analogous to  from Control.Applicative.rel8 Aggregate a  into a . If the supplied query returns 0 rows, this function will produce a - that is empty - that is, will produce zero  NonEmptyTables. If the supplied Query does return rows, some% will return exactly one row, with a  NonEmptyTable collecting all returned rows.some is analogous to  from Control.Applicative.rel8 A version of # specialised to single expressions.rel8 A version of # specialised to single expressions.rel8 Expand a  into a :, where each row in the query is an element of the given  ListTable. catListTable is an inverse to .rel8 Expand a  into a :, where each row in the query is an element of the given  NonEmptyTable.catNonEmptyTable is an inverse to .rel81Expand an expression that contains a list into a ?, where each row in the query is an element of the given list.catList is an inverse to .rel8;Expand an expression that contains a non-empty list into a ?, where each row in the query is an element of the given list. catNonEmpty is an inverse to .None 1;rel8Nest a  value within a Rel8able.  HMaybe f a will produce a  a in the Expr context, and a  a in the A context.None1<><#None'149E rel8An EitherTable a b0 is a Rel8 table that contains either the table a or the table b. You can construct an  EitherTable using  and $, and eliminate/pattern match using .An  EitherTable( is operationally the same as Haskell's & type, but adapted to work with Rel8.rel8 Test if an  is a .rel8 Test if an  is a .rel8Pattern match/eliminate an  , by providing mappings from a  and .rel8Construct a left . Like .rel8Construct a right . Like .rel8Lift an  to operate on an . If the input query has  a!s, they are folded into a single c by the given aggregator @ in the case where the input query is all s, the  's fallback c is returned.rel8Lift an  to operate on an . If the input query has  a!s, they are folded into a single  c by the given aggregator @ in the case where the input query is all  s, a single  nothingTable row is returned.rel8Lift an  to operate on an . If the input query has  b!s, they are folded into a single c by the given aggregator @ in the case where the input query is all s, the  's fallback c is returned.rel8Lift an  to operate on an . If the input query has  b!s, they are folded into a single  c by the given aggregator @ in the case where the input query is all  s, a single  nothingTable row is returned.rel8)Lift a pair aggregators to operate on an .  leftTables and  rightTables are grouped separately.rel8 Construct a  in the , context. This can be useful if you have a : that you are storing in a table and need to construct a  TableSchema.rel83The name of the column to track whether a row is a  or .rel8Names of the columns in the a table.rel8Names of the columns in the b table.NoneGrel8Filter s, keeping only  leftTables.rel8Filter s, keeping only  rightTables.rel8bitraverseEitherTable f g x will pass all  leftTable s through f and all  rightTable s through g). The results are then lifted back into  leftTable and  rightTable#, respectively. This is similar to  bitraverse for . For example,:{ select do: x <- values (map lit [ Left True, Right (42 :: Int32) ]) bitraverseEitherTable (\y -> values [y, not_ y]) (\y -> pure (y * 100)) x:} [ Left True , Left False , Right 4200]None 1Hrel8Nest an  value within a Rel8able.  HEither f a b will produce a  a b in the Expr context, and a  a b in the A context.None)*I rel8Corresponds to a FULL OUTER JOIN between two queries. Nonek]!rel8A  k a is like a  a', except that each row also has a key k in addition to the value a. )s can be composed monadically just like *s, but the resulting join is more like a  NATURAL JOIN$ (based on the common key column(s) k ) than the  CROSS JOIN given by .Another way to think of  k a is as analogous to Map k a in the same way  a is analogous to [a]'. However, there's nothing stopping a  from containing multiple rows with the same key, so technically Map k (NonEmpty a) is more accurate.s can be created from s with  and  and converted back to s with  and 6 (though note the caveats that come with the latter).rel8Any  of key-value pairs (k, a) can be a  k a.rel8 Convert a  k a back into a  of key-value pairs.Note that the result of a 1 is undefined (will always return zero rows) on s constructed with  or  . So while toQuery . fromQuery is always id, fromQuery . toQuery is not.)A safer, more predictable alternative to  is to use  with an explicit set of keys: ;do k <- keys a <- lookup k tabulation pure (k, a) 7Having said that, in practice, most legitimate uses of  will have a well-defined . It would be possible in theory to encode the necessary invariants at the type level using an indexed monad, but we would lose the ability to use do0-notation, which is the main benefit of having  as a monad in the first place.In particular,  t is well-defined for any  t defined as t = fromQuery _.  t is also well-defined for any  t defined as  t = t' >>= _ or  t = t' *> _ where  t' is well-defined. There are other valid permutations too. Generally, anything that uses / at some point, unless wrapped in a top-level  or , will have a well-defined .rel8A  a can be treated as a  k a where the given a% values exist at every possible key k.rel8Run a Kleisli arrow in the the  monad "through" a . Useful for ing a .  ((>=. 30) . userAge) `through' usersById rel8 k t! returns the value(s) at the key k in the tabulation t.rel8 produces a "magic" < whereby the values within each group of keys in the given  is aggregated according to the given aggregator, and every other possible key contains a single "fallback" row is returned, composed of the identity elements of the constituent aggregation functions.rel8- aggregates the values within each key of a . There is an implicit GROUP BY on all the key columns.rel8 ensures a  has at most one value for each key, i.e., it drops duplicates. In general it keeps only the "first" value it encounters for each key, but note that "first" is undefined unless you first call .rel8 orders the values of a  within their respective keys. This specifies a defined order for 6. It also defines the order of the lists produced by  and .rel87 returns a count of how many entries are in the given  at each key.The resulting  is "magic" in that the value 08 exists at every possible key that wasn't in the given .rel8 produces a "magic" " whereby each entry in the given  is wrapped in 2, and every other possible key contains a single .This is used to implement .rel8 aggregates each entry with a particular key into a single entry with all of the values contained in a . can be used to give this  a defined order.The resulting  is "magic" in that the value 'Rel8.listTable []'8 exists at every possible key that wasn't in the given .rel8 aggregates each entry with a particular key into a single entry with all of the values contained in a . can be used to give this  a defined order.rel8 produces a "magic"  which contains the value  at each key in the given , and the value  at every other possible key.rel8 produces a  where a single ()9 row exists for every key that was present in the given .This is used to implement .rel8 produces a  where a single ()> row exists at every possible key that absent from the given .This is used to implement .rel8 Performs a NATURAL FULL OUTER JOIN! based on the common key columns. Analogous to .rel8 Performs a NATURAL FULL OUTER JOIN! based on the common key columns. Analogous to .rel8 Performs a NATURAL LEFT OUTER JOIN! based on the common key columns. Analogous to ./Note that you can achieve the same effect with  and the  instance for , i.e., this is just /\left right -> liftA2 (,) left (optional right). You can also use do -notation.rel8 Performs a NATURAL LEFT OUTER JOIN! based on the common key columns. Analogous to ./Note that you can achieve the same effect with  and the  instance for , i.e., this is just /\f left right -> liftA2 f left (optional right). You can also use do -notation.rel8 Performs a NATURAL RIGHT OUTER JOIN! based on the common key columns. Analogous to ./Note that you can achieve the same effect with  and the  instance for , i.e., this is just 6\left right -> liftA2 (flip (,)) right (optional left). You can also use do -notation.rel8 Performs a NATURAL RIGHT OUTER JOIN! based on the common key columns. Analogous to ./Note that you can achieve the same effect with  and the  instance for , i.e., this is just 6\f left right -> liftA2 (flip f) right (optional left). You can also use do -notation.rel8 Performs a NATURAL INNER JOIN! based on the common key columns. Analagous to .3Note that you can achieve the same effect with the  instance of , i.e., this is just  'liftA2 (,)'. You can also use do -notation.rel8 Performs a NATURAL INNER JOIN! based on the common key columns. Analagous to .3Note that you can achieve the same effect with the  instance of , i.e., this is just . You can also use do -notation.rel8 Performs a  https://en.wikipedia.org/wiki/Relational_algebra#Semijoin_%28%E2%8B%89%29%28%E2%8B%8A%29NATURAL SEMI JOIN" based on the common key columns.The result is a subset of the left tabulation where only entries which have a corresponding entry in the right tabulation are kept.0Note that you can achieve a similar effect with  and the  instance of , i.e., this is just $\left right -> left <* present right. You can also use do -notation.rel8 Performs a  https://en.wikipedia.org/wiki/Relational_algebra#Antijoin_%28%E2%96%B7%29NATURAL ANTI JOIN" based on the common key columns.The result is a subset of the left tabulation where only entries which do not have a corresponding entry in the right tabulation are kept.0Note that you can achieve a similar effect with  and the  instance of , i.e., this is just #\left right -> left <* absent right. You can also use do -notation.rel8 for s.rel8s can be produced with either  or ?, and in some cases we might want to treat these differently.  uses  to determine which type of  we have.rel8If  k a is Map k (NonEmpty a), then (<>) is unionWith (liftA2 (<>)).rel8If  k a is Map k (NonEmpty a), then ( |:) is unionWith (<>).rel8 pure =  . purerel8If  k a is Map k (NonEmpty a), then ( .) is intersectionWith (liftA2 ( *))None1lNone1l]None /01=q|rel8,This type class allows you to define custom Ds using higher-kinded data types. Higher-kinded data types are data types of the pattern: data MyType f = MyType { field1 :: Column f T1 OR HK1 f , field2 :: Column f T2 OR HK2 f , ... , fieldN :: Column f Tn OR HKn f } where Tn is any Haskell type, and HKn is any higher-kinded type.That is, higher-kinded data are records where all fields in the record are all either of the type  Column f T (for any T)), or are themselves higher-kinded data: Nested data Nested f = Nested { nested1 :: MyType f , nested2 :: MyType f } The Rel8able type class is used to give us a special mapping operation that lets us change the type parameter f.  Supplying Rel8able instancesThis type class should be derived generically for all table types in your project. To do this, enable the DeriveAnyClass and  DeriveGeneric language extensions: {-# LANGUAGE DeriveAnyClass, DeriveGeneric #-} data MyType f = MyType { fieldA :: Column f T } deriving ( GHC.Generics.Generic, Rel8able ) rel8 The kind of  types None-1qNone'(/1rF None1rNone1rNone 1s"None1syNone"%'()*-1wrel8 is used to associate composite type metadata with a Haskell type.rel83The names of all fields in the composite type that a maps to.rel8$The name of the composite type that a maps to.rel8A deriving-via helper type for column types that store a Haskell product type in a single Postgres column using a Postgres composite type.Note that this must map to a specific extant type in your database's schema (created with  CREATE TYPE). Use  to specify the name of this Postgres type and the names of the individual fields (for projecting with ).rel8 Collapse a " into a PostgreSQL composite type. values are represented in queries by having a column for each field in the corresponding Haskell type.  collapses these columns into a single column expression, by combining them into a PostgreSQL composite type.rel8Expand a composite type into a . is the inverse of .None1wNone|Mrel8In PostgreSQL, window functions must specify the "window" or "partition" over which they operate. The syntax for this looks like: *SUM(salary) OVER (PARTITION BY department). The Rel8 type ) represents everything that comes after OVER. is a , so s created with  and  orderWindowBy can be combined using .rel8 is an applicative functor that represents expressions that contain   (salary >$< ) rel8Restricts a window function to operate only the group of rows that share the same value(s) for the given expression(s).rel8Controls the order in which rows are processed by window functions. This does not need to match the ordering of the overall query.None~Yrel82 runs a query composed of expressions containing  80 !$#%"-./*+,fg4567213YZ[de()*+,-./YZ[=>9:;rel8< is used to allow the collection of a variety of different  TableSchemas under a single type, like: userTable :: TableSchema (User Name) orderTable :: TableSchema (Order Name) tables :: [SomeTableSchema] tables = [SomeTableSchema userTable, SomeTable orderTable] This is used by  schemaErrors to conveniently group every table an application relies on for typechecking the postgresql schemas together in a single batch.rel8 shows an example CREATE TABLE statement for the table. This does not show relationships like primary or foreign keys, but can still be useful to see what types rel8( will expect of the underlying database.In the event that multiple columns have the same name, this will fail silently. To handle that case, see rel8 shows an example CREATE TABLE statement for the table. This does not show relationships like primary or foreign keys, but can still be useful to see what types rel8 will expect of the underlying database.In the event that multiple columns have the same name, this will return a map of names to the labels identifying the column. rel8 pShowTable is a helper function which takes a grid of text and prints it as a table, with padding so that cells are lined in columns, and a bordered header for the first rowrel8 checks whether the provided schemas have the correct PostgreSQL column names and types to allow reading and writing from their equivalent Haskell types, returning a list of errors if that is not the case. The function does not crash on encountering a bug, instead leaving it to the caller to decide how to respond. A schema is valid if: )for every existing field, the types match3all non-nullable columns are present in the hs type1no nonexistent columns are present in the hs type5no two columns in the same schema share the same nameIt's still possible for a valid schema to allow invalid data, for instance, if using an ADT, which can introduce restrictions on which values are allowed for the column representing the tag, and introduce restrictions on which columns are non-null depending on the value of the tag. However, if the schema is valid rel8 shouldn't be able to write invalid data to the table.However, it is possible for migrations to cause valid data to become invalid in ways not detectable by this function, if the migration code changes the schema correctly but doesn't handle the value-level constraints correctly. So it is a good idea to both read from the tables and check the schema for errors in a transaction during the migration. The former will catch value-level bugs, while the latter will help ensure the schema is set up correctly to be able to insert new data.This function does nothing to check that the conflict target of an Upsert? are valid for the schema, nor can it prevent invalid uses of  unsafeDefault. However, it should be enough to catch the most likely errors.   &&&&&&'''''((((())))))))0*0131313222455566668888888898:<=>JZJJJJJJJJJPJNJOJQRWYYYYYXYmmmqK[[[[^llnnpp``````````fffffffkkkkkuuuuww!yyx||||||||||sss_tbttg~}c7vMMMMMM                                             g"#$$$$$%%((+++,----------./////00000000000000000000000;;;;;;<<<<<=>>>>>>?>@>A>B>C>>>>>>>>>>DDDDDDDDDDDEEEEEEEEFFFFFGGGGGGGGGHHHHHHHHHHHIIIJJJJJJJSSSSTTTTTTTTTTTTTUVWWY[[[[[[[[[[[^^fhffffklllllqKrssww!xxxxxxxxxxxxxyyyz{|                             vv v                                                                                                         rel8-1.7.0.0-inplaceRel8 Rel8.Decoder Rel8.Encoder Rel8.ArrayRel8.Expr.TimeRel8.Expr.Text Rel8.Expr.Num Rel8.TabulateRel8.Table.Verifyrel8Rel8.Aggregate.FoldData.Semigroup.FoldablefoldMap1QueryRel8.FCFRel8.Generic.MapRel8.Generic.RecordRel8.Kind.Algebra Rel8.OrderascdescData.Functor.Contravariant>$<Rel8.Query.OpaleyeRel8.Schema.DictRel8.Schema.EscapeRel8.Schema.KindRel8.Schema.HTable.ProductRel8.Schema.NullRel8.Schema.QualifiedNameRel8.Schema.TableRel8ableNameRel8.Type.Builder.ByteStringRel8.Type.Builder.FoldRel8.Type.Builder.TimeRel8.Type.DecimalRel8.Type.DecoderRel8.Type.EncoderRel8.Type.NameRel8.Type.InformationDBTypeRel8.Type.NullableRel8.Type.ParserRel8.Type.ArrayRel8.Type.Parser.ByteStringRel8.Type.Parser.Time Rel8.TypeRel8.Type.JSONEncodedRel8.Type.JSONBEncoded JSONEncoded Rel8.Type.Eq Rel8.Type.Ord Rel8.Type.Num fromIntegralRel8.Type.Enum $dmenumValue $dmenumerateRel8.Schema.SpecRel8.Schema.Result Rel8.ColumnRel8.Schema.HTable $dmhdicts $dmhfield $dmhspecs $dmhtabulate $dmhtraverseRel8.Schema.HTable.MapTableRel8.Schema.HTable.NullifyRel8.Schema.HTable.LabelRel8.Generic.Table.Record Rel8.Generic.Construction.RecordRel8.Schema.HTable.Identity Rel8.TableExpr AggregateInsert$dmfromColumns $dmfromResult $dmtoColumns $dmtoResultRel8.Table.TransposeRel8.Table.ColsRel8.Schema.HTable.VectorizeRel8.Schema.HTable.NonEmptyRel8.Schema.HTable.ListRel8.Schema.Field ProjectionRel8.Table.ProjectionTableRel8.Expr.OpaleyeOpaleyePrimExprRel8.Expr.SerializelitRel8.Expr.Bool Data.Boolboolwhere_32Rel8.Expr.Nullnullable Data.Maybe isNothingisJustRel8.Expr.FunctionRel8.Expr.ArrayRel8.Type.ReadShowRel8.Type.Semigroup6Rel8.Type.Monoid Rel8.ExprRel8.Table.UndefinedRel8.Table.SerializeRel8.Table.BoolRel8.Table.Alternative MaybeTableRel8.Schema.NameRel8.Table.OpaleyeRel8.Table.NameRel8.Statement.WhereRel8.Statement.SetRel8.Statement.OnConflictRel8.Query.ValuesunionRel8.Kind.ContextRel8.Schema.Context.NullifyRel8.Expr.SubscriptRel8.Expr.ShowRel8.Expr.SequenceRel8.Expr.ReadRel8.Expr.Order Rel8.Expr.Ord4Rel8.Expr.NonEmptyRel8.Expr.List Rel8.Expr.Eq Rel8.Table.Eq $dmeqTableRel8.Table.Ord $dmordTableRel8.Table.OrderRel8.Query.Set Rel8.QueryRel8.Statement.RowsRel8.Query.OrderRel8.Query.MaterializeRel8.Query.LoopunionAllRel8.Query.LimitRel8.Query.RebindRel8.Query.FunctionRel8.Query.Filter Control.MonadguardRel8.Query.EvaluateRel8.Query.EachRel8.Query.ExistsRel8.Query.DistinctPreludedivmodquotremRel8.Expr.DefaultnextvalRel8.AggregatesumfalseorsumOnData.ProfunctorlmapRel8.Table.NullifyRel8.Aggregate.FunctionRel8.Type.String Rel8.Type.SumRel8.Expr.Aggregate filterWhereData.Scientific Scientific Rel8.Type.TagRel8.Schema.HTable.TheseRel8.Schema.HTable.MaybeRel8.Table.Maybe fromMaybetraverseMaybeTableRel8.Table.NullnullnullifyunsafeUnnullifyRel8.Table.NonEmptysome nullTableRel8.Column.NonEmptyRel8.Table.ListmanylistAggRel8.Table.AggregatefilterWhereOptional stringAggRel8.Column.ListRel8.Query.Null catMaybesRel8.Column.NullRel8.Table.Aggregate.MaybeRel8.Table.TheseData.These.CombinatorsisThisisThatisThesehasHerehasTherejustHere justThere justTableRel8.Column.TheseRel8.Query.MaybeRel8.Query.Aggregate Aggregator1Rel8.StatementselectinsertupdatedeletenowRel8.Statement.SelectRel8.Statement.UsingRel8.Query.SQLRel8.Statement.RunHasql Statement NoReturningRel8.Statement.ReturningUpdateDeleteRel8.Statement.UpdateRel8.Statement.PreparedrunRel8.Statement.InsertvaluesRel8.Statement.ViewRel8.Statement.DeleteRel8.Statement.SQLRel8.Query.ListControl.ApplicativeRel8.Column.MaybeRel8.Schema.HTable.EitherRel8.Table.EitherRel8.Query.EitherRel8.Column.EitherRel8.Query.Thesefilter nothingTabletrueData.Semialignalign alignWithrpadZip rpadZipWithlpadZip lpadZipWithzipzipWithQ materialize1Rel8.Generic.Table.ADTRel8.Generic.TableRel8.Generic.Rel8able$dmgfromColumns$dmgfromResult $dmgtoColumns $dmgtoResultRel8.Generic.Construction.ADTRel8.Generic.ConstructionRel8.Table.HKDRel8.Column.LiftRel8.Table.ADTRel8.Table.Rel8ableRel8.Type.CompositeRel8.Column.ADT Rel8.WindowRel8.Query.WindowwindowRel8.Table.Window cumulative aggregateRel8.Expr.WindoworderPartitionByRel8.Query.IndexedFoldSemiFullOrderSqlNullable HomonullableNotNull QualifiedNameschemaname TableSchemacolumnsDecodertextbinaryParser parseDecoderEncoderquoteTypeName arrayDepth modifiersTypeInformationtypeName delimiterdecodeencodemapTypeInformationparseTypeInformationtypeInformationfromJSONEncoded JSONBEncodedfromJSONBEncodedDBEqDBMinDBMaxDBOrd DBFloating DBFractional DBIntegralDBNumEnumableDBEnum enumValue enumTypeName enumerateEnumResultColumnHTableColumnsContext FromExprs Transpose toColumns fromColumns fromResulttoResult TransposesField Biprojectable biproject Projectableproject ProjectingReadShow fromReadShowunsafeCastExprunsafeCoerceExprunsafePrimExpr unsafeLiterallitExprlistOf nonEmptyOf DBSemigroup<>.DBMonoid memptyExpr&&.||.not_and_or_boolExprcaseExprcoalesceisNull isNonNullmapNull liftOpNull Argumentsfunction rawFunctionbinaryOperatorrawBinaryOperatorAlternativeTable emptyTableAltTable<|>:SelectsnamesFromLabelsnamesFromLabelsWith castTableUpsert updateWhereset predicateindex OnConflictAbort DoNothingDoUpdateunsafeSubscriptunsafeSubscripts SerializableToExprs head1Expr index1Expr last1Expr length1ExprheadExpr indexExprlastExpr lengthExprtodaytoDayfromDayaddDaysdiffDays subtractDaysaddTimediffTime subtractTime scaleIntervalsecondsecondsminuteminuteshourhoursdaydaysweekweeksmonthmonthsyearyears++.~.~*!~!~* bitLength charLengthlower octetLengthupperasciibtrimchrconvert convertFrom convertToinitcapleftlengthlengthEncodinglpadltrimmd5pgClientEncoding quoteIdent quoteLiteral quoteNullable regexpReplaceregexpSplitToArrayrepeatreplacereverserightrpadrtrim splitPartstrpossubstr translatelikeilike unsafeDefaultcase_ nullsFirst nullsLast<.<=.>.>=.?>=? leastExpr greatestExpr==./=.==?/=?in_EqTableeqTable==:/=:OrdTableordTable<:<=:>:>=:leastgreatestascTable descTable intersect intersectAllexcept exceptAllorderByloop loopDistinctlimitoffsetrebind queryFunctionevaluateeachexistspresentabsentwithwithBywithout withoutBydistinct distinctOn distinctOnBy realToFracceilingdivModquotRemfloorroundtruncate Aggregator Aggregator' toAggregator1 toAggregatoraggregateFunctionrawAggregateFunctionDBStringDBSumcountcountOn countDistinctcountDistinctOn countStar countWhere countWhereOnandandOnorOnmaxmaxOnminminOnsumWhereavgavgOnmodemodeOn percentile percentileOnpercentileContinuouspercentileContinuousOnhypotheticalRankhypotheticalDenseRankhypotheticalPercentRankhypotheticalCumeDist listAggExpr listAggExprOnnonEmptyAggExprnonEmptyAggExprOn listCatExpr listCatExprOnnonEmptyCatExprnonEmptyCatExprOndistinctAggregateisNothingTable isJustTable maybeTablefromMaybeTable$?nameMaybeTable NullTable isNullTableisNonNullTable nullableTable nullifyTableunsafeUnnullifyTable nameNullTable toMaybeTable toNullTable NonEmptyTable$+ nonEmptyTablenameNonEmptyTablehead1index1last1length1 HNonEmpty ListTable$* listTable nameListTableheadlastgroupBy groupByOn listAggOn nonEmptyAgg nonEmptyAggOnlistCat listCatOn nonEmptyCat nonEmptyCatOnorderAggregateByHListelemelem1catNull catNullTableHNulloptionalAggregateaggregateJustTableaggregateJustTable1aggregateMaybeTable TheseTable isThisTable isThatTable isThoseTable hasHereTable hasThereTable justHereTablejustThereTablealignMaybeTable thisTable thatTable thoseTable theseTableaggregateThisTableaggregateThisTable1aggregateThatTableaggregateThatTable1aggregateThoseTableaggregateThoseTable1aggregateHereTableaggregateHereTable1aggregateThereTableaggregateThereTable1aggregateTheseTablenameTheseTableHTheseoptional catMaybeTable aggregate1 countRows showQueryrun_runNrun1runMaybe runVector Returning returningfromtargetprepared onConflictrowsinto createViewcreateOrReplaceView deleteWhereusing showDelete showInsert showUpdate showStatementshowPreparedStatementmanyExprsomeExpr catListTablecatNonEmptyTablecatList catNonEmptyHMaybe EitherTable isLeftTable isRightTable eitherTable leftTable rightTableaggregateLeftTableaggregateLeftTable1aggregateRightTableaggregateRightTable1aggregateEitherTablenameEitherTable keepLeftTablekeepRightTablebitraverseEitherTableHEitheralignBy keepHereTable loseHereTablekeepThereTableloseThereTable keepThisTable loseThisTable keepThatTable loseThatTablekeepThoseTableloseThoseTablebitraverseTheseTable Tabulation fromQuerytoQuery liftQuerythroughlookuporder leftAlign leftAlignWith rightAlignrightAlignWith similarity difference$fMonoidPredicate$fSemigroupPredicate$fContravariantPredicate$fMonoidTabulation$fSemigroupTabulation$fAlternativeTableTabulation$fAltTableTabulation$fMonadTabulation$fBindTabulation$fApplicativeTabulation$fApplyTabulation$fProjectableTabulation$fFunctorTabulation$fBifunctorTabulation$fBiprojectableTabulation KRel8ableNameHKDDeconstructHKD ConstructHKDBuildHKDHKDableHKDbuildHKD constructHKDdeconstructHKDnameHKDLiftNameADTDeconstructADT ConstructADTBuildADTADTableADTbuildADT constructADTdeconstructADTnameADT DBCompositecompositeFieldscompositeTypeName Compositecompose decomposeHADT PartitionWindowover partitionBy rowNumberrank denseRank percentRankcumeDistntile currentRowlaglagOnleadleadOn firstValue firstValueOn lastValue lastValueOnnthValue nthValueOnindexedSomeTableSchemashowCreateTablecheckedShowCreateTablegetSchemaErrors$fDBTypeRelkind$fShowTypeInfo$fShowTableInfo$fShowColumnInfo$fShowColumnError$fShowCheckEnv $fGenericCast$fRel8ableCast$fGenericPGTable$fRel8ablePGTable$fGenericAttribute$fRel8ableAttribute$fGenericPGCast$fRel8ablePGCast$fGenericPGNamespace$fRel8ablePGNamespace$fGenericPGType$fRel8ablePGType$fGenericPGAttribute$fRel8ablePGAttribute$fGenericPGClass$fRel8ablePGClass $fDBTypeOid $fDBEqOid $fShowOid $fShowRelkind $fDBEqRelkind $fShowCast$fShowAttribute $fShowPGTable $fShowPGCast$fShowPGNamespace $fShowPGType$fShowPGAttribute $fShowPGClassbase Data.FoldablefoldMapFallbackEmptyEvalExpIdMapGMapGRecord GRecordablegrecord gunrecordRecordunrecordAlgebraProductSum KnownAlgebra algebraSingSAlgebraSProductSSumGHC.Base<> fromOpaleye mapOpaleye toOpaleyeunsafePeekQueryzipOpaleyeWithDictescapeHProductNullifyNullityNull Unnullify GHC.MaybeNothing$fIsStringQualifiedNameppQualifiedNameshowQualifiedNameshowQualifiedOperatorppTable bytestring interfoldMapcalendarDiffTime localTime timeOfDayutcTime resolution PowerOf10$fIsStringTypeName showTypeName NullableOrNot NonNullableparsearray arrayTypeNameextractArrayElementlistTypeInformationnonEmptyTypeInformationquoteArrayElement$fDBTypeIPRange $fDBTypeValue $fDBTypeUUID$fDBTypeByteString$fDBTypeByteString0 $fDBTypeCI $fDBTypeCI0 $fDBTypeText $fDBTypeText0$fDBTypeCalendarDiffTime$fDBTypeTimeOfDay$fDBTypeLocalTime $fDBTypeDay$fDBTypeUTCTime $fDBTypeFixed$fDBTypeScientific$fDBTypeDouble $fDBTypeFloat $fDBTypeInt64 $fDBTypeInt32 $fDBTypeInt16 $fDBTypeChar $fDBTypeBoolaeson-2.2.3.0-2aaacadf5014bf2546bebd07da3224a7fd2f86b0698e1386324a7e426d4094feData.Aeson.Types.ToJSONToJSONData.Aeson.Types.FromJSONFromJSON specificationSpecinfolabelsnullity nullifier unnullifier unvectorizer vectorizerTColumn HProductField htabulatehfieldhdictshspecshfoldMaphmap htabulateA htabulateP htraversePhtraversePWithField htraverse_HConstrainTableHField htraversehproject HMapTable unHMapTableHMapTableFieldMapSpecmapInfo Precompose precomposedghc-prim GHC.TypesTypehguardhnullifyhnulls hunnullifyHNullifyhlabelhrelabelhunlabelHLabelGColumnsGContext GSerialize gfromResult gtoResultGTable gfromColumnsgtable gtoColumns FromColumns GConstructGConstructable gconstruct gdeconstruct GConstructorGFields Representablegindex gtabulate ToColumns HIdentity unHIdentity CongruentTColumnsTContext TFromExprs TSerializeTTable TTransposefromColstoColsColshappendhcolumnhemptyhtraverseVectorP hunvectorize hvectorize hvectorizeAFirstgetFirst HVectorizeHNonEmptyTable HListTablefieldsapplycastExpr fromColumn fromPrimExpr mapPrimExpr scastExprsunsafeCastExprtoColumn toPrimExprtraverseFieldPtraversePrimExprzipPrimExprsWithslitExpr sparseValue nullableExprmaybefmapMaybeliftA2 nullableOfsnullunsafeLiftOpNull unsafeMapNull primFunctionsappendsappend1semptyslistOf snonEmptyOfGHC.ReadReadGHC.ShowShowMonoid undefined litHTableppColumn attributes binaryspec distinctspecexprsexprsWithNames fromOrderifPP relExprPPtable tableFields unpackspec valuesspecviewnamesFromLabelsWithA showLabels showNamesppWhereppSet ppOnConflictreturn Reifiable contextSingSContextSExprSFieldSNameSResultabsurdguardernullifiableOrNotNonNullifiabilityNFieldNResultNullifiabilityNExprNName Nullifiablenullifiabilitytime-1.12.2-7014Data.Time.Calendar.DaysDayshowreadsread shead1Expr sindex1Expr slast1Expr sheadExpr sindexExpr slastExpr GHC.Classes==/=TrueBool<<=>>= $fMonoidQuerymempty$fSemigroupQuery$fAlternativeTableQuery$fAltTableQueryRowsList RowsAffectedSingleVectorVoidhrebindinQuery Applicativeprofunctors-5.6.3-efc9a4499d0843f2684e698f21fc88a21a374aee026273be61a897b1a4e0c31eData.Profunctor.Unsafe Profunctorproduct-profunctors-0.11.1.1-e4aea7d95d4b5c806a39d421fa516f5d64777fee4a0283d1604f3b798112e93eData.Profunctor.Product.ClassProductProfunctorfilterWhereExplicitunsafeMakeAggregatoraggregateNullifyDouble stringAggOn groupByExpr groupByExprOn slistAggExpr slistCatExprsnonEmptyAggExprsnonEmptyCatExprisLeftisRight EitherTagIsLeftIsRightMaybeTagIsJustTag HTheseTablehherehhereTaghthere hthereTag HMaybeTablehjusthtagJustpure$$fMonadMaybeTable$fApplicativeMaybeTablemakeMaybeTableunsafeFromJustTablejusttagNonEmptythese-1.2.1-0e273ac3a11271a02fecebf97f043eb0106dd4dde4d7d4abe106c3beff7d8d10 Data.TheseTheseThisThatherethere aggregateUMonadppDecodeStatementstatementNoReturningstatementReturning ppPrimSelectppRowsppSelect OptimizedUnitppFromppUsingStringGHC.IntInt64 ppReturning runReturningppUpdateinputppInsertppIntoppDelete HEitherTablehlefthright Data.EitherEitherLeftRightpeek GColumnsADT GColumnsADT' GSerializeADTgfromResultADT gtoResultADTGSerializeADT' ggfromResult ggtoResultGAlgebra GGColumns GGSerializeGRep GFromExprs deserialize serialize GBuildADT GConstructADTGConstructableADT gbuildADT gconstructADTgdeconstructADT gunbuildADTGConstructorADT GConstructors GMakeableADTgmakeADTRepresentableConstructorsgcindex gctabulateRepresentableFieldsgfindex gftabulateggbuild ggconstruct ggdeconstructggdeconstructAggnameGGBuild GGBuildable GGConstructGGConstructable GGDeconstructGGNamedeconstructAHKD BuildableHKDConstructableHKDHKDRepdeconstructAADTADTRep BuildableADTConstructableADTlagExpr lagExprOnleadExpr leadExprOnfirstValueExprfirstValueExprOn lastValueExprlastValueExprOn nthValueExprnthValueExprOn pShowTable